Skip to content

Commit 64d3016

Browse files
committed
Continuing fake GADT
Use in more functions, etc.
1 parent 44f6446 commit 64d3016

File tree

3 files changed

+113
-67
lines changed

3 files changed

+113
-67
lines changed

containers-tests/containers-tests.cabal

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -122,6 +122,7 @@ library
122122
Utils.Containers.Internal.StrictMaybe
123123
Utils.Containers.Internal.EqOrdUtil
124124

125+
Data.Sequence.Internal.Depth
125126
if impl(ghc >= 8.6)
126127
ghc-options: -Werror
127128

containers/containers.cabal

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,6 @@ Library
7575
Data.Graph
7676
Data.Sequence
7777
Data.Sequence.Internal
78-
Data.Sequence.Internal.Depth
7978
Data.Sequence.Internal.Sorting
8079
Data.Tree
8180

@@ -87,6 +86,7 @@ Library
8786
Utils.Containers.Internal.EqOrdUtil
8887
Utils.Containers.Internal.BitUtil
8988
Utils.Containers.Internal.BitQueue
89+
Data.Sequence.Internal.Depth
9090
Utils.Containers.Internal.StrictPair
9191

9292
include-dirs: include

containers/src/Data/Sequence/Internal.hs

Lines changed: 111 additions & 66 deletions
Original file line numberDiff line numberDiff line change
@@ -372,19 +372,39 @@ instance Functor Seq where
372372
x <$ s = replicate (length s) x
373373
#endif
374374

375-
fmapSeq :: (a -> b) -> Seq a -> Seq b
376-
fmapSeq f (Seq xs) = Seq (fmap (fmap f) xs)
377375
#ifdef __GLASGOW_HASKELL__
376+
fmapSeq :: forall a b. (a -> b) -> Seq a -> Seq b
377+
fmapSeq f (Seq t0) = Seq (fmapFT Bottom2 t0)
378+
where
379+
fmapBlob :: Depth2 (Elem a) t (Elem b) u -> t -> u
380+
fmapBlob Bottom2 (Elem a) = Elem (f a)
381+
fmapBlob (Deeper2 w) (Node2 s x y) = Node2 s (fmapBlob w x) (fmapBlob w y)
382+
fmapBlob (Deeper2 w) (Node3 s x y z) = Node3 s (fmapBlob w x) (fmapBlob w y) (fmapBlob w z)
383+
384+
fmapFT :: Depth2 (Elem a) t (Elem b) u -> FingerTree t -> FingerTree u
385+
fmapFT !_ EmptyT = EmptyT
386+
fmapFT w (Single t) = Single (fmapBlob w t)
387+
fmapFT w (Deep s pr m sf) =
388+
Deep s
389+
(fmap (fmapBlob w) pr)
390+
(fmapFT (Deeper2 w) m)
391+
(fmap (fmapBlob w) sf)
392+
378393
{-# NOINLINE [1] fmapSeq #-}
379394
{-# RULES
380395
"fmapSeq/fmapSeq" forall f g xs . fmapSeq f (fmapSeq g xs) = fmapSeq (f . g) xs
381396
"fmapSeq/coerce" fmapSeq coerce = coerce
382397
#-}
398+
399+
#else
400+
fmapSeq :: (a -> b) -> Seq a -> Seq b
401+
fmapSeq f (Seq xs) = Seq (fmap (fmap f) xs)
383402
#endif
384403

385-
--type Depth = Depth_ Elem Node
404+
#ifdef __GLASGOW_HASKELL__
386405
type Depth = Depth_ Node
387406
type Depth2 = Depth2_ Node
407+
#endif
388408

389409
instance Foldable Seq where
390410
#ifdef __GLASGOW_HASKELL__
@@ -407,25 +427,32 @@ instance Foldable Seq where
407427
foldr :: forall a b. (a -> b -> b) -> b -> Seq a -> b
408428
-- We define this explicitly so we can inline the foldMap. And we don't
409429
-- define it as a coercion of the FingerTree version because we want users
410-
-- to have the option of (effectively) inlining it explicitly.
430+
-- to have the option of (effectively) inlining it explicitly. Should we
431+
-- define this by hand to associate optimally? Or is GHC clever enough to
432+
-- do that for us?
411433
foldr f z t = appEndo (GHC.Exts.inline foldMap (coerce f) t) z
412434

413435
foldl :: forall b a. (b -> a -> b) -> b -> Seq a -> b
414-
-- Should we define this by hand to associate optimally? Or is GHC
415-
-- clever enough to do that for us?
416436
foldl f z t = appEndo (getDual (GHC.Exts.inline foldMap (Dual . Endo . flip f) t)) z
417437

418438
foldr' :: forall a b. (a -> b -> b) -> b -> Seq a -> b
419-
foldr' = coerce (foldr' :: (Elem a -> b -> b) -> b -> FingerTree (Elem a) -> b)
439+
foldr' f z0 = \ xs ->
440+
GHC.Exts.inline foldl (\ (k::b->b) (x::a) -> GHC.Exts.oneShot (\ (z::b) -> z `seq` k (f x z)))
441+
(id::b->b) xs z0
420442

421443
foldl' :: forall b a. (b -> a -> b) -> b -> Seq a -> b
422-
foldl' = coerce (foldl' :: (b -> Elem a -> b) -> b -> FingerTree (Elem a) -> b)
444+
foldl' f z0 = \ xs ->
445+
GHC.Exts.inline foldr (\ (x::a) (k::b->b) -> GHC.Exts.oneShot (\ (z::b) -> z `seq` k (f z x)))
446+
(id::b->b) xs z0
423447

424448
foldr1 :: forall a. (a -> a -> a) -> Seq a -> a
425-
foldr1 = coerce (foldr1 :: (Elem a -> Elem a -> Elem a) -> FingerTree (Elem a) -> Elem a)
449+
foldr1 _f Empty = error "foldr1: empty sequence"
450+
foldr1 f (xs :|> x) = foldr f x xs
426451

427452
foldl1 :: forall a. (a -> a -> a) -> Seq a -> a
428-
foldl1 = coerce (foldl1 :: (Elem a -> Elem a -> Elem a) -> FingerTree (Elem a) -> Elem a)
453+
foldl1 _f Empty = error "foldl1: empty sequence"
454+
foldl1 f (x :<| xs) = foldl f x xs
455+
429456
#else
430457
foldMap f (Seq xs) = foldMap (f . getElem) xs
431458

@@ -1124,33 +1151,7 @@ instance Sized a => Sized (FingerTree a) where
11241151
size (Single x) = size x
11251152
size (Deep v _ _ _) = v
11261153

1127-
-- We don't fold FingerTrees directly, but instead coerce them to
1128-
-- Seqs and fold those. This seems backwards! Why do it? We certainly
1129-
-- *could* fold FingerTrees directly, but we'd need a slightly different
1130-
-- version of the Depth GADT to do so. While that's not a big deal,
1131-
-- it is a bit annoying. Note: we need the current version of Depth
1132-
-- to deal with the Sized issues for indexed folds.
11331154
instance Foldable FingerTree where
1134-
#ifdef __GLASGOW_HASKELL__
1135-
foldMap :: forall m a. Monoid m => (a -> m) -> FingerTree a -> m
1136-
foldMap f = foldMapFT Bottom
1137-
where
1138-
foldMapBlob :: Depth a t -> t -> m
1139-
foldMapBlob Bottom a = f a
1140-
foldMapBlob (Deeper w) (Node2 _ x y) = foldMapBlob w x <> foldMapBlob w y
1141-
foldMapBlob (Deeper w) (Node3 _ x y z) = foldMapBlob w x <> foldMapBlob w y <> foldMapBlob w z
1142-
1143-
foldMapFT :: Depth a t -> FingerTree t -> m
1144-
foldMapFT !_ EmptyT = mempty
1145-
foldMapFT w (Single t) = foldMapBlob w t
1146-
foldMapFT w (Deep _ pr m sf) =
1147-
foldMap (foldMapBlob w) pr
1148-
<> foldMapFT (Deeper w) m
1149-
<> foldMap (foldMapBlob w) sf
1150-
1151-
-- foldMap = coerce (foldMap :: (a -> m) -> Seq a -> m)
1152-
{-# INLINABLE foldMap #-}
1153-
#else
11541155
foldMap _ EmptyT = mempty
11551156
foldMap f' (Single x') = f' x'
11561157
foldMap f' (Deep _ pr' m' sf') =
@@ -1177,8 +1178,11 @@ instance Foldable FingerTree where
11771178

11781179
foldMapNodeN :: Monoid m => (Node a -> m) -> Node (Node a) -> m
11791180
foldMapNodeN f t = foldNode (<>) f t
1181+
#if __GLASGOW_HASKELL__
1182+
{-# INLINABLE foldMap #-}
11801183
#endif
11811184

1185+
11821186
foldr _ z' EmptyT = z'
11831187
foldr f' z' (Single x') = x' `f'` z'
11841188
foldr f' z' (Deep _ pr' m' sf') =
@@ -3223,6 +3227,49 @@ delDigit f i (Four a b c d)
32233227
-- | A generalization of 'fmap', 'mapWithIndex' takes a mapping
32243228
-- function that also depends on the element's index, and applies it to every
32253229
-- element in the sequence.
3230+
#ifdef __GLASGOW_HASKELL__
3231+
mapWithIndex :: forall a b. (Int -> a -> b) -> Seq a -> Seq b
3232+
mapWithIndex f (Seq t) = Seq $ mapWithIndexFT Bottom2 0 t
3233+
where
3234+
mapWithIndexFT :: Depth2 (Elem a) t (Elem b) u -> Int -> FingerTree t -> FingerTree u
3235+
mapWithIndexFT !_ !_ EmptyT = EmptyT
3236+
mapWithIndexFT d s (Single xs) = Single $ mapWithIndexBlob d s xs
3237+
mapWithIndexFT d s (Deep s' pr m sf) = case depthSized2 d of { Sizzy ->
3238+
Deep s'
3239+
(mapWithIndexDigit (mapWithIndexBlob d) s pr)
3240+
(mapWithIndexFT (Deeper2 d) sPspr m)
3241+
(mapWithIndexDigit (mapWithIndexBlob d) sPsprm sf)
3242+
where
3243+
!sPspr = s + size pr
3244+
!sPsprm = sPspr + size m
3245+
}
3246+
3247+
mapWithIndexBlob :: Depth2 (Elem a) t (Elem b) u -> Int -> t -> u
3248+
mapWithIndexBlob Bottom2 k (Elem a) = Elem (f k a)
3249+
mapWithIndexBlob (Deeper2 yop) k (Node2 s t1 t2) =
3250+
Node2 s
3251+
(mapWithIndexBlob yop k t1)
3252+
(mapWithIndexBlob yop (k + sizeBlob2 yop t1) t2)
3253+
mapWithIndexBlob (Deeper2 yop) k (Node3 s t1 t2 t3) =
3254+
Node3 s
3255+
(mapWithIndexBlob yop k t1)
3256+
(mapWithIndexBlob yop (k + st1) t2)
3257+
(mapWithIndexBlob yop (k + st1t2) t3)
3258+
where
3259+
st1 = sizeBlob2 yop t1
3260+
st1t2 = st1 + sizeBlob2 yop t2
3261+
3262+
{-# NOINLINE [1] mapWithIndex #-}
3263+
3264+
{-# RULES
3265+
"mapWithIndex/mapWithIndex" forall f g xs . mapWithIndex f (mapWithIndex g xs) =
3266+
mapWithIndex (\k a -> f k (g k a)) xs
3267+
"mapWithIndex/fmapSeq" forall f g xs . mapWithIndex f (fmapSeq g xs) =
3268+
mapWithIndex (\k a -> f k (g a)) xs
3269+
"fmapSeq/mapWithIndex" forall f g xs . fmapSeq f (mapWithIndex g xs) =
3270+
mapWithIndex (\k a -> f (g k a)) xs
3271+
#-}
3272+
#else
32263273
mapWithIndex :: (Int -> a -> b) -> Seq a -> Seq b
32273274
mapWithIndex f' (Seq xs') = Seq $ mapWithIndexTree (\s (Elem a) -> Elem (f' s a)) 0 xs'
32283275
where
@@ -3240,25 +3287,6 @@ mapWithIndex f' (Seq xs') = Seq $ mapWithIndexTree (\s (Elem a) -> Elem (f' s a)
32403287
!sPspr = s + size pr
32413288
!sPsprm = sPspr + size m
32423289

3243-
{-# SPECIALIZE mapWithIndexDigit :: (Int -> Elem y -> b) -> Int -> Digit (Elem y) -> Digit b #-}
3244-
{-# SPECIALIZE mapWithIndexDigit :: (Int -> Node y -> b) -> Int -> Digit (Node y) -> Digit b #-}
3245-
mapWithIndexDigit :: Sized a => (Int -> a -> b) -> Int -> Digit a -> Digit b
3246-
mapWithIndexDigit f !s (One a) = One (f s a)
3247-
mapWithIndexDigit f s (Two a b) = Two (f s a) (f sPsa b)
3248-
where
3249-
!sPsa = s + size a
3250-
mapWithIndexDigit f s (Three a b c) =
3251-
Three (f s a) (f sPsa b) (f sPsab c)
3252-
where
3253-
!sPsa = s + size a
3254-
!sPsab = sPsa + size b
3255-
mapWithIndexDigit f s (Four a b c d) =
3256-
Four (f s a) (f sPsa b) (f sPsab c) (f sPsabc d)
3257-
where
3258-
!sPsa = s + size a
3259-
!sPsab = sPsa + size b
3260-
!sPsabc = sPsab + size c
3261-
32623290
{-# SPECIALIZE mapWithIndexNode :: (Int -> Elem y -> b) -> Int -> Node (Elem y) -> Node b #-}
32633291
{-# SPECIALIZE mapWithIndexNode :: (Int -> Node y -> b) -> Int -> Node (Node y) -> Node b #-}
32643292
mapWithIndexNode :: Sized a => (Int -> a -> b) -> Int -> Node a -> Node b
@@ -3270,19 +3298,28 @@ mapWithIndex f' (Seq xs') = Seq $ mapWithIndexTree (\s (Elem a) -> Elem (f' s a)
32703298
where
32713299
!sPsa = s + size a
32723300
!sPsab = sPsa + size b
3273-
3274-
#ifdef __GLASGOW_HASKELL__
3275-
{-# NOINLINE [1] mapWithIndex #-}
3276-
{-# RULES
3277-
"mapWithIndex/mapWithIndex" forall f g xs . mapWithIndex f (mapWithIndex g xs) =
3278-
mapWithIndex (\k a -> f k (g k a)) xs
3279-
"mapWithIndex/fmapSeq" forall f g xs . mapWithIndex f (fmapSeq g xs) =
3280-
mapWithIndex (\k a -> f k (g a)) xs
3281-
"fmapSeq/mapWithIndex" forall f g xs . fmapSeq f (mapWithIndex g xs) =
3282-
mapWithIndex (\k a -> f (g k a)) xs
3283-
#-}
32843301
#endif
32853302

3303+
{-# SPECIALIZE mapWithIndexDigit :: (Int -> Elem a -> b) -> Int -> Digit (Elem a) -> Digit b #-}
3304+
{-# SPECIALIZE mapWithIndexDigit :: (Int -> Node a -> b) -> Int -> Digit (Node a) -> Digit b #-}
3305+
mapWithIndexDigit :: Sized x => (Int -> x -> y) -> Int -> Digit x -> Digit y
3306+
mapWithIndexDigit f !s (One a) = One (f s a)
3307+
mapWithIndexDigit f s (Two a b) = Two (f s a) (f sPsa b)
3308+
where
3309+
!sPsa = s + size a
3310+
mapWithIndexDigit f s (Three a b c) =
3311+
Three (f s a) (f sPsa b) (f sPsab c)
3312+
where
3313+
!sPsa = s + size a
3314+
!sPsab = sPsa + size b
3315+
mapWithIndexDigit f s (Four a b c d) =
3316+
Four (f s a) (f sPsa b) (f sPsab c) (f sPsabc d)
3317+
where
3318+
!sPsa = s + size a
3319+
!sPsab = sPsa + size b
3320+
!sPsabc = sPsab + size c
3321+
3322+
32863323
{-# INLINE foldWithIndexDigit #-}
32873324
foldWithIndexDigit :: Sized a => (b -> b -> b) -> (Int -> a -> b) -> Int -> Digit a -> b
32883325
foldWithIndexDigit _ f !s (One a) = f s a
@@ -3352,10 +3389,18 @@ depthSized :: Depth (Elem a) t -> Sizzy t
33523389
depthSized Bottom = Sizzy
33533390
depthSized (Deeper _) = Sizzy
33543391

3392+
depthSized2 :: Depth2 (Elem a) t (Elem b) u -> Sizzy t
3393+
depthSized2 Bottom2 = Sizzy
3394+
depthSized2 (Deeper2 _) = Sizzy
3395+
33553396
sizeBlob :: Depth (Elem a) t -> t -> Int
33563397
sizeBlob Bottom = size
33573398
sizeBlob (Deeper _) = size
33583399

3400+
sizeBlob2 :: Depth2 (Elem a) t (Elem b) u -> t -> Int
3401+
sizeBlob2 Bottom2 = size
3402+
sizeBlob2 (Deeper2 _) = size
3403+
33593404
#else
33603405
foldMapWithIndex f' (Seq xs') = foldMapWithIndexTreeE (lift_elem f') 0 xs'
33613406
where

0 commit comments

Comments
 (0)