Skip to content

Commit 9399062

Browse files
committed
Add some more
1 parent 64d3016 commit 9399062

File tree

3 files changed

+135
-39
lines changed

3 files changed

+135
-39
lines changed

containers-tests/containers-tests.cabal

Lines changed: 0 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -106,7 +106,6 @@ library
106106
Data.Map.Strict.Internal
107107
Data.Sequence
108108
Data.Sequence.Internal
109-
Data.Sequence.Internal.Depth
110109
Data.Sequence.Internal.Sorting
111110
Data.Set
112111
Data.Set.Internal

containers/src/Data/Sequence/Internal.hs

Lines changed: 127 additions & 35 deletions
Original file line numberDiff line numberDiff line change
@@ -179,7 +179,6 @@ module Data.Sequence.Internal (
179179
node2,
180180
node3,
181181
#endif
182-
bongo
183182
) where
184183

185184
import Utils.Containers.Internal.Prelude hiding (
@@ -3454,6 +3453,48 @@ foldMapWithIndex f' (Seq xs') = foldMapWithIndexTreeE (lift_elem f') 0 xs'
34543453
-- access to the index of each element.
34553454
--
34563455
-- @since 0.5.8
3456+
#ifdef __GLASGOW_HASKELL__
3457+
traverseWithIndex :: forall f a b. Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b)
3458+
traverseWithIndex f (Seq t) = Seq <$> traverseWithIndexFT Bottom2 0 t
3459+
where
3460+
traverseWithIndexFT :: Depth2 (Elem a) t (Elem b) u -> Int -> FingerTree t -> f (FingerTree u)
3461+
traverseWithIndexFT !_ !_ EmptyT = pure EmptyT
3462+
traverseWithIndexFT d s (Single xs) = Single <$> traverseWithIndexBlob d s xs
3463+
traverseWithIndexFT d s (Deep s' pr m sf) = case depthSized2 d of { Sizzy ->
3464+
liftA3 (Deep s')
3465+
(traverseWithIndexDigit (traverseWithIndexBlob d) s pr)
3466+
(traverseWithIndexFT (Deeper2 d) sPspr m)
3467+
(traverseWithIndexDigit (traverseWithIndexBlob d) sPsprm sf)
3468+
where
3469+
!sPspr = s + size pr
3470+
!sPsprm = sPspr + size m
3471+
}
3472+
3473+
traverseWithIndexBlob :: Depth2 (Elem a) t (Elem b) u -> Int -> t -> f u
3474+
traverseWithIndexBlob Bottom2 k (Elem a) = Elem <$> f k a
3475+
traverseWithIndexBlob (Deeper2 yop) k (Node2 s t1 t2) =
3476+
liftA2 (Node2 s)
3477+
(traverseWithIndexBlob yop k t1)
3478+
(traverseWithIndexBlob yop (k + sizeBlob2 yop t1) t2)
3479+
traverseWithIndexBlob (Deeper2 yop) k (Node3 s t1 t2 t3) =
3480+
liftA3 (Node3 s)
3481+
(traverseWithIndexBlob yop k t1)
3482+
(traverseWithIndexBlob yop (k + st1) t2)
3483+
(traverseWithIndexBlob yop (k + st1t2) t3)
3484+
where
3485+
st1 = sizeBlob2 yop t1
3486+
st1t2 = st1 + sizeBlob2 yop t2
3487+
3488+
{-# INLINABLE [1] traverseWithIndex #-}
3489+
3490+
{-# RULES
3491+
"travWithIndex/mapWithIndex" forall f g xs . traverseWithIndex f (mapWithIndex g xs) =
3492+
traverseWithIndex (\k a -> f k (g k a)) xs
3493+
"travWithIndex/fmapSeq" forall f g xs . traverseWithIndex f (fmapSeq g xs) =
3494+
traverseWithIndex (\k a -> f k (g a)) xs
3495+
#-}
3496+
3497+
#else
34573498
traverseWithIndex :: Applicative f => (Int -> a -> f b) -> Seq a -> f (Seq b)
34583499
traverseWithIndex f' (Seq xs') = Seq <$> traverseWithIndexTreeE (\s (Elem a) -> Elem <$> f' s a) 0 xs'
34593500
where
@@ -3491,24 +3532,6 @@ traverseWithIndex f' (Seq xs') = Seq <$> traverseWithIndexTreeE (\s (Elem a) ->
34913532
traverseWithIndexDigitN :: Applicative f => (Int -> Node a -> f b) -> Int -> Digit (Node a) -> f (Digit b)
34923533
traverseWithIndexDigitN f i t = traverseWithIndexDigit f i t
34933534

3494-
{-# INLINE traverseWithIndexDigit #-}
3495-
traverseWithIndexDigit :: (Applicative f, Sized a) => (Int -> a -> f b) -> Int -> Digit a -> f (Digit b)
3496-
traverseWithIndexDigit f !s (One a) = One <$> f s a
3497-
traverseWithIndexDigit f s (Two a b) = liftA2 Two (f s a) (f sPsa b)
3498-
where
3499-
!sPsa = s + size a
3500-
traverseWithIndexDigit f s (Three a b c) =
3501-
liftA3 Three (f s a) (f sPsa b) (f sPsab c)
3502-
where
3503-
!sPsa = s + size a
3504-
!sPsab = sPsa + size b
3505-
traverseWithIndexDigit f s (Four a b c d) =
3506-
liftA3 Four (f s a) (f sPsa b) (f sPsab c) <*> f sPsabc d
3507-
where
3508-
!sPsa = s + size a
3509-
!sPsab = sPsa + size b
3510-
!sPsabc = sPsab + size c
3511-
35123535
traverseWithIndexNodeE :: Applicative f => (Int -> Elem a -> f b) -> Int -> Node (Elem a) -> f (Node b)
35133536
traverseWithIndexNodeE f i t = traverseWithIndexNode f i t
35143537

@@ -3526,21 +3549,27 @@ traverseWithIndex f' (Seq xs') = Seq <$> traverseWithIndexTreeE (\s (Elem a) ->
35263549
!sPsa = s + size a
35273550
!sPsab = sPsa + size b
35283551

3529-
3530-
#ifdef __GLASGOW_HASKELL__
3531-
{-# INLINABLE [1] traverseWithIndex #-}
3532-
#else
35333552
{-# INLINE [1] traverseWithIndex #-}
35343553
#endif
35353554

3536-
#ifdef __GLASGOW_HASKELL__
3537-
{-# RULES
3538-
"travWithIndex/mapWithIndex" forall f g xs . traverseWithIndex f (mapWithIndex g xs) =
3539-
traverseWithIndex (\k a -> f k (g k a)) xs
3540-
"travWithIndex/fmapSeq" forall f g xs . traverseWithIndex f (fmapSeq g xs) =
3541-
traverseWithIndex (\k a -> f k (g a)) xs
3542-
#-}
3543-
#endif
3555+
{-# INLINE traverseWithIndexDigit #-}
3556+
traverseWithIndexDigit :: (Applicative f, Sized a) => (Int -> a-> f b) -> Int -> Digit a -> f (Digit b)
3557+
traverseWithIndexDigit f !s (One a) = One <$> f s a
3558+
traverseWithIndexDigit f s (Two a b) = liftA2 Two (f s a) (f sPsa b)
3559+
where
3560+
!sPsa = s + size a
3561+
traverseWithIndexDigit f s (Three a b c) =
3562+
liftA3 Three (f s a) (f sPsa b) (f sPsab c)
3563+
where
3564+
!sPsa = s + size a
3565+
!sPsab = sPsa + size b
3566+
traverseWithIndexDigit f s (Four a b c d) =
3567+
liftA3 Four (f s a) (f sPsa b) (f sPsab c) <*> f sPsabc d
3568+
where
3569+
!sPsa = s + size a
3570+
!sPsab = sPsa + size b
3571+
!sPsabc = sPsab + size c
3572+
35443573
{-
35453574
It might be nice to be able to rewrite
35463575
@@ -5149,12 +5178,79 @@ zipWith f s1 s2 = zipWith' f s1' s2'
51495178
s1' = take minLen s1
51505179
s2' = take minLen s2
51515180

5181+
#ifdef __GLASGOW_HASKELL__
5182+
-- | A version of zipWith that assumes the sequences have the same length.
5183+
zipWith' :: forall a b c. (a -> b -> c) -> Seq a -> Seq b -> Seq c
5184+
zipWith' f = \(Seq t1) s2 -> Seq (zipFT Bottom2 t1 s2)
5185+
where
5186+
5187+
zipBlob :: Depth2 (Elem a) t (Elem c) v -> t -> Seq b -> v
5188+
zipBlob Bottom2 (Elem a) s2
5189+
| Seq (Single (Elem b)) <- s2 = Elem (f a b)
5190+
| otherwise = error "zipWith': invariant failure"
5191+
zipBlob (Deeper2 w) (Node2 s (x :: q) y) s2 = Node2 s (zipBlob w x s2l) (zipBlob w y s2r)
5192+
where
5193+
sz :: q -> Int
5194+
sz = case w of
5195+
Bottom2 -> size
5196+
Deeper2 _ -> size
5197+
(s2l, s2r) = splitAt (sz x) s2
5198+
zipBlob (Deeper2 w) (Node3 s (x :: q) y z) s2 = Node3 s (zipBlob w x s2l) (zipBlob w y s2c) (zipBlob w z s2r)
5199+
where
5200+
sz :: q -> Int
5201+
sz = case w of
5202+
Bottom2 -> size
5203+
Deeper2 _ -> size
5204+
(s2l, s2rem) = splitAt (sz x) s2
5205+
(s2c, s2r) = splitAt (sz y) s2rem
5206+
5207+
zipDigit :: forall t v. Depth2 (Elem a) t (Elem c) v -> Digit t -> Seq b -> Digit v
5208+
zipDigit p = \d s2 ->
5209+
case d of
5210+
One t -> One (zipBlob p t s2)
5211+
Two t u -> Two (zipBlob p t s2l) (zipBlob p u s2r)
5212+
where
5213+
(s2l, s2r) = splitAt (sz t) s2
5214+
Three t u v -> Three (zipBlob p t s2l) (zipBlob p u s2c) (zipBlob p v s2r)
5215+
where
5216+
(s2l, s2rem) = splitAt (sz t) s2
5217+
(s2c, s2r) = splitAt (sz u) s2rem
5218+
Four t u v w -> Four (zipBlob p t s21) (zipBlob p u s22) (zipBlob p v s23) (zipBlob p w s24)
5219+
where
5220+
(s2l, s2r) = splitAt (sz t + sz u) s2
5221+
(s21, s22) = splitAt (sz t) s2l
5222+
(s23, s24) = splitAt (sz v) s2r
5223+
where
5224+
sz :: t -> Int
5225+
sz = case p of
5226+
Bottom2 -> size
5227+
Deeper2 _ -> size
5228+
5229+
zipFT :: forall t v. Depth2 (Elem a) t (Elem c) v -> FingerTree t -> Seq b -> FingerTree v
5230+
zipFT !_ EmptyT !_ = EmptyT
5231+
zipFT w (Single t) s2 = Single (zipBlob w t s2)
5232+
zipFT w (Deep s pr m sf) s2 =
5233+
Deep s
5234+
(zipDigit w pr s2l)
5235+
(zipFT (Deeper2 w) m s2c)
5236+
(zipDigit w sf s2r)
5237+
where
5238+
szd :: Digit t -> Int
5239+
szd = case w of
5240+
Bottom2 -> size
5241+
Deeper2 _ -> size
5242+
(s2l, s2rem) = splitAt (szd pr) s2
5243+
(s2c, s2r) = splitAt (size m) s2rem
5244+
5245+
5246+
#else
51525247
-- | A version of zipWith that assumes the sequences have the same length.
51535248
zipWith' :: (a -> b -> c) -> Seq a -> Seq b -> Seq c
51545249
zipWith' f s1 s2 = splitMap uncheckedSplitAt goLeaf s2 s1
51555250
where
51565251
goLeaf (Seq (Single (Elem b))) a = f a b
51575252
goLeaf _ _ = error "Data.Sequence.zipWith'.goLeaf internal error: not a singleton"
5253+
#endif
51585254

51595255
-- | \( O(\min(n_1,n_2,n_3)) \). 'zip3' takes three sequences and returns a
51605256
-- sequence of triples, analogous to 'zip'.
@@ -5200,7 +5296,3 @@ fromList2 n = execState (replicateA n (State ht))
52005296
where
52015297
ht (x:xs) = (xs, x)
52025298
ht [] = error "fromList2: short list"
5203-
5204-
{-# NOINLINE bongo #-}
5205-
bongo :: Seq [a] -> [a]
5206-
bongo xs = GHC.Exts.inline foldMap id xs

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

Lines changed: 8 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,3 @@
1-
{-# OPTIONS_GHC -ddump-prep #-}
21
{-# LANGUAGE GADTs #-}
32
{-# LANGUAGE KindSignatures #-}
43
{-# LANGUAGE PatternSynonyms #-}
@@ -64,6 +63,7 @@ pattern Bottom :: () => t ~ a => Depth_ node a t
6463
pattern Bottom <- (checkBottom -> AtBottom)
6564
where
6665
Bottom = Depth_ 0
66+
{-# INLINE Bottom #-}
6767

6868
-- | The depth is non-zero.
6969
pattern Deeper :: () => t ~ node t' => Depth_ node a t' -> Depth_ node a t
@@ -72,6 +72,7 @@ pattern Deeper d <- (checkBottom -> NotBottom d)
7272
Deeper (Depth_ d)
7373
| d == maxBound = error "Depth overflow"
7474
| otherwise = Depth_ (d + 1)
75+
{-# INLINE Deeper #-}
7576

7677
{-# COMPLETE Bottom, Deeper #-}
7778

@@ -82,14 +83,15 @@ data CheckedBottom node a t where
8283
checkBottom :: Depth_ node a t -> CheckedBottom node a t
8384
checkBottom (Depth_ 0) = unsafeCoerce AtBottom
8485
checkBottom (Depth_ d) = unsafeCoerce (NotBottom (Depth_ (d - 1)))
86+
{-# INLINE checkBottom #-}
8587

8688

8789
-- | A version of 'Depth_' for implementing traversals. Conceptually,
8890
--
8991
-- @
9092
-- data Depth2_ node a t b u where
91-
-- Bottom2 :: Depth_ node a a b b
92-
-- Deeper2 :: !(Depth_ node a t b u) -> Depth_ node a (node t) b (node u)
93+
-- Bottom2 :: Depth2_ node a a b b
94+
-- Deeper2 :: !(Depth2_ node a t b u) -> Depth_ node a (node t) b (node u)
9395
-- @
9496
newtype Depth2_ (node :: Type -> Type) (a :: Type) (t :: Type) (b :: Type) (u :: Type)
9597
= Depth2_ Word
@@ -100,6 +102,7 @@ pattern Bottom2 :: () => (t ~ a, u ~ b) => Depth2_ node a t b u
100102
pattern Bottom2 <- (checkBottom2 -> AtBottom2)
101103
where
102104
Bottom2 = Depth2_ 0
105+
{-# INLINE Bottom2 #-}
103106

104107
-- | The depth is non-zero.
105108
pattern Deeper2 :: () => (t ~ node t', u ~ node u') => Depth2_ node a t' b u' -> Depth2_ node a t b u
@@ -108,6 +111,7 @@ pattern Deeper2 d <- (checkBottom2 -> NotBottom2 d)
108111
Deeper2 (Depth2_ d)
109112
| d == maxBound = error "Depth2 overflow"
110113
| otherwise = Depth2_ (d + 1)
114+
{-# INLINE Deeper2 #-}
111115

112116
{-# COMPLETE Bottom2, Deeper2 #-}
113117

@@ -118,3 +122,4 @@ data CheckedBottom2 node a t b u where
118122
checkBottom2 :: Depth2_ node a t b u -> CheckedBottom2 node a t b u
119123
checkBottom2 (Depth2_ 0) = unsafeCoerce AtBottom2
120124
checkBottom2 (Depth2_ d) = unsafeCoerce (NotBottom2 (Depth2_ (d - 1)))
125+
{-# INLINE checkBottom2 #-}

0 commit comments

Comments
 (0)