@@ -33,8 +33,10 @@ module Data.Sequence.Internal.Depth
33
33
, Depth2_ (Bottom2 , Deeper2 )
34
34
) where
35
35
36
+ #if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
36
37
import Data.Kind (Type )
37
38
import Unsafe.Coerce (unsafeCoerce )
39
+ #endif
38
40
39
41
-- @Depth_@ is an optimized representation of the following GADT:
40
42
--
@@ -55,6 +57,15 @@ import Unsafe.Coerce (unsafeCoerce)
55
57
-- arithmetic overflow on 64-bit systems requires somewhat absurdly long
56
58
-- computations on sequences constructed with extensive amounts of internal
57
59
-- 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
58
69
newtype Depth_ (node :: Type -> Type ) (a :: Type ) (t :: Type )
59
70
= Depth_ Word
60
71
type role Depth_ nominal nominal nominal
@@ -64,9 +75,7 @@ pattern Bottom :: () => t ~ a => Depth_ node a t
64
75
pattern Bottom <- (checkBottom -> AtBottom )
65
76
where
66
77
Bottom = Depth_ 0
67
- #if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
68
78
{-# INLINE Bottom #-}
69
- #endif
70
79
71
80
-- | The depth is non-zero.
72
81
pattern Deeper :: () => t ~ node t' => Depth_ node a t' -> Depth_ node a t
@@ -75,9 +84,7 @@ pattern Deeper d <- (checkBottom -> NotBottom d)
75
84
Deeper (Depth_ d)
76
85
| d == maxBound = error " Depth overflow"
77
86
| otherwise = Depth_ (d + 1 )
78
- #if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
79
87
{-# INLINE Deeper #-}
80
- #endif
81
88
82
89
{-# COMPLETE Bottom, Deeper #-}
83
90
@@ -88,20 +95,22 @@ data CheckedBottom node a t where
88
95
checkBottom :: Depth_ node a t -> CheckedBottom node a t
89
96
checkBottom (Depth_ 0 ) = unsafeCoerce AtBottom
90
97
checkBottom (Depth_ d) = unsafeCoerce (NotBottom (Depth_ (d - 1 )))
91
- #if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
92
98
{-# INLINE checkBottom #-}
93
- #else
94
- {-# NOINLINE checkBottom #-}
95
- #endif
96
99
100
+ #endif
97
101
98
102
-- | A version of 'Depth_' for implementing traversals. Conceptually,
99
103
--
100
104
-- @
101
105
-- data Depth2_ node a t b u where
102
106
-- 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)
104
108
-- @
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
105
114
newtype Depth2_ (node :: Type -> Type ) (a :: Type ) (t :: Type ) (b :: Type ) (u :: Type )
106
115
= Depth2_ Word
107
116
type role Depth2_ nominal nominal nominal nominal nominal
@@ -111,9 +120,7 @@ pattern Bottom2 :: () => (t ~ a, u ~ b) => Depth2_ node a t b u
111
120
pattern Bottom2 <- (checkBottom2 -> AtBottom2 )
112
121
where
113
122
Bottom2 = Depth2_ 0
114
- #if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
115
123
{-# INLINE Bottom2 #-}
116
- #endif
117
124
118
125
-- | The depth is non-zero.
119
126
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)
122
129
Deeper2 (Depth2_ d)
123
130
| d == maxBound = error " Depth2 overflow"
124
131
| otherwise = Depth2_ (d + 1 )
125
- #if defined(MIN_VERSION_GLASGOW_HASKELL) && MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
126
132
{-# INLINE Deeper2 #-}
127
- #endif
128
133
129
134
{-# COMPLETE Bottom2, Deeper2 #-}
130
135
@@ -135,8 +140,5 @@ data CheckedBottom2 node a t b u where
135
140
checkBottom2 :: Depth2_ node a t b u -> CheckedBottom2 node a t b u
136
141
checkBottom2 (Depth2_ 0 ) = unsafeCoerce AtBottom2
137
142
checkBottom2 (Depth2_ d) = unsafeCoerce (NotBottom2 (Depth2_ (d - 1 )))
138
- #if MIN_VERSION_GLASGOW_HASKELL(9,2,0,0)
139
143
{-# INLINE checkBottom2 #-}
140
- #else
141
- {-# NOINLINE checkBottom2 #-}
142
144
#endif
0 commit comments