Skip to content

Commit b89264c

Browse files
committed
Big hammer
1 parent 8563d99 commit b89264c

File tree

1 file changed

+18
-16
lines changed
  • containers/src/Data/Sequence/Internal

1 file changed

+18
-16
lines changed

containers/src/Data/Sequence/Internal/Depth.hs

Lines changed: 18 additions & 16 deletions
Original file line numberDiff line numberDiff line change
@@ -33,8 +33,10 @@ module Data.Sequence.Internal.Depth
3333
, Depth2_ (Bottom2, Deeper2)
3434
) where
3535

36+
#if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
3637
import Data.Kind (Type)
3738
import Unsafe.Coerce (unsafeCoerce)
39+
#endif
3840

3941
-- @Depth_@ is an optimized representation of the following GADT:
4042
--
@@ -55,6 +57,15 @@ import Unsafe.Coerce (unsafeCoerce)
5557
-- arithmetic overflow on 64-bit systems requires somewhat absurdly long
5658
-- computations on sequences constructed with extensive amounts of internal
5759
-- sharing (e.g., using the '*>' operator repeatedly).
60+
#if !defined(MIN_VERSION_GLASGOW_HASKELL) || !MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
61+
-- Old versions of GHC would crash out in all sorts of weird ways with the fancy version,
62+
-- so we give a totally plain version here. We also use the plain one for MicroHS, for
63+
-- now, because I don't know what it wants.
64+
data Depth_ node a t where
65+
Bottom :: Depth_ node a a
66+
Deeper :: !(Depth_ node a t) -> Depth_ node a (node t)
67+
68+
#else
5869
newtype Depth_ (node :: Type -> Type) (a :: Type) (t :: Type)
5970
= Depth_ Word
6071
type role Depth_ nominal nominal nominal
@@ -64,9 +75,7 @@ pattern Bottom :: () => t ~ a => Depth_ node a t
6475
pattern Bottom <- (checkBottom -> AtBottom)
6576
where
6677
Bottom = Depth_ 0
67-
#if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
6878
{-# INLINE Bottom #-}
69-
#endif
7079

7180
-- | The depth is non-zero.
7281
pattern Deeper :: () => t ~ node t' => Depth_ node a t' -> Depth_ node a t
@@ -75,9 +84,7 @@ pattern Deeper d <- (checkBottom -> NotBottom d)
7584
Deeper (Depth_ d)
7685
| d == maxBound = error "Depth overflow"
7786
| otherwise = Depth_ (d + 1)
78-
#if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
7987
{-# INLINE Deeper #-}
80-
#endif
8188

8289
{-# COMPLETE Bottom, Deeper #-}
8390

@@ -88,20 +95,22 @@ data CheckedBottom node a t where
8895
checkBottom :: Depth_ node a t -> CheckedBottom node a t
8996
checkBottom (Depth_ 0) = unsafeCoerce AtBottom
9097
checkBottom (Depth_ d) = unsafeCoerce (NotBottom (Depth_ (d - 1)))
91-
#if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
9298
{-# INLINE checkBottom #-}
93-
#else
94-
{-# NOINLINE checkBottom #-}
95-
#endif
9699

100+
#endif
97101

98102
-- | A version of 'Depth_' for implementing traversals. Conceptually,
99103
--
100104
-- @
101105
-- data Depth2_ node a t b u where
102106
-- Bottom2 :: Depth2_ node a a b b
103-
-- Deeper2 :: !(Depth2_ node a t b u) -> Depth_ node a (node t) b (node u)
107+
-- Deeper2 :: !(Depth2_ node a t b u) -> Depth2_ node a (node t) b (node u)
104108
-- @
109+
#if !defined(MIN_VERSION_GLASGOW_HASKELL) || !MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
110+
data Depth2_ node a t b u where
111+
Bottom2 :: Depth2_ node a a b b
112+
Deeper2 :: !(Depth2_ node a t b u) -> Depth2_ node a (node t) b (node u)
113+
#else
105114
newtype Depth2_ (node :: Type -> Type) (a :: Type) (t :: Type) (b :: Type) (u :: Type)
106115
= Depth2_ Word
107116
type role Depth2_ nominal nominal nominal nominal nominal
@@ -111,9 +120,7 @@ pattern Bottom2 :: () => (t ~ a, u ~ b) => Depth2_ node a t b u
111120
pattern Bottom2 <- (checkBottom2 -> AtBottom2)
112121
where
113122
Bottom2 = Depth2_ 0
114-
#if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
115123
{-# INLINE Bottom2 #-}
116-
#endif
117124

118125
-- | The depth is non-zero.
119126
pattern Deeper2 :: () => (t ~ node t', u ~ node u') => Depth2_ node a t' b u' -> Depth2_ node a t b u
@@ -122,9 +129,7 @@ pattern Deeper2 d <- (checkBottom2 -> NotBottom2 d)
122129
Deeper2 (Depth2_ d)
123130
| d == maxBound = error "Depth2 overflow"
124131
| otherwise = Depth2_ (d + 1)
125-
#if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
126132
{-# INLINE Deeper2 #-}
127-
#endif
128133

129134
{-# COMPLETE Bottom2, Deeper2 #-}
130135

@@ -135,8 +140,5 @@ data CheckedBottom2 node a t b u where
135140
checkBottom2 :: Depth2_ node a t b u -> CheckedBottom2 node a t b u
136141
checkBottom2 (Depth2_ 0) = unsafeCoerce AtBottom2
137142
checkBottom2 (Depth2_ d) = unsafeCoerce (NotBottom2 (Depth2_ (d - 1)))
138-
#if MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
139143
{-# INLINE checkBottom2 #-}
140-
#else
141-
{-# NOINLINE checkBottom2 #-}
142144
#endif

0 commit comments

Comments
 (0)