@@ -179,7 +179,6 @@ module Data.Sequence.Internal (
179
179
node2 ,
180
180
node3 ,
181
181
#endif
182
- bongo
183
182
) where
184
183
185
184
import Utils.Containers.Internal.Prelude hiding (
@@ -3454,6 +3453,48 @@ foldMapWithIndex f' (Seq xs') = foldMapWithIndexTreeE (lift_elem f') 0 xs'
3454
3453
-- access to the index of each element.
3455
3454
--
3456
3455
-- @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
3457
3498
traverseWithIndex :: Applicative f => (Int -> a -> f b ) -> Seq a -> f (Seq b )
3458
3499
traverseWithIndex f' (Seq xs') = Seq <$> traverseWithIndexTreeE (\ s (Elem a) -> Elem <$> f' s a) 0 xs'
3459
3500
where
@@ -3491,24 +3532,6 @@ traverseWithIndex f' (Seq xs') = Seq <$> traverseWithIndexTreeE (\s (Elem a) ->
3491
3532
traverseWithIndexDigitN :: Applicative f => (Int -> Node a -> f b ) -> Int -> Digit (Node a ) -> f (Digit b )
3492
3533
traverseWithIndexDigitN f i t = traverseWithIndexDigit f i t
3493
3534
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
-
3512
3535
traverseWithIndexNodeE :: Applicative f => (Int -> Elem a -> f b ) -> Int -> Node (Elem a ) -> f (Node b )
3513
3536
traverseWithIndexNodeE f i t = traverseWithIndexNode f i t
3514
3537
@@ -3526,21 +3549,27 @@ traverseWithIndex f' (Seq xs') = Seq <$> traverseWithIndexTreeE (\s (Elem a) ->
3526
3549
! sPsa = s + size a
3527
3550
! sPsab = sPsa + size b
3528
3551
3529
-
3530
- #ifdef __GLASGOW_HASKELL__
3531
- {-# INLINABLE [1] traverseWithIndex #-}
3532
- #else
3533
3552
{-# INLINE [1] traverseWithIndex #-}
3534
3553
#endif
3535
3554
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
+
3544
3573
{-
3545
3574
It might be nice to be able to rewrite
3546
3575
@@ -5149,12 +5178,79 @@ zipWith f s1 s2 = zipWith' f s1' s2'
5149
5178
s1' = take minLen s1
5150
5179
s2' = take minLen s2
5151
5180
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
5152
5247
-- | A version of zipWith that assumes the sequences have the same length.
5153
5248
zipWith' :: (a -> b -> c ) -> Seq a -> Seq b -> Seq c
5154
5249
zipWith' f s1 s2 = splitMap uncheckedSplitAt goLeaf s2 s1
5155
5250
where
5156
5251
goLeaf (Seq (Single (Elem b))) a = f a b
5157
5252
goLeaf _ _ = error " Data.Sequence.zipWith'.goLeaf internal error: not a singleton"
5253
+ #endif
5158
5254
5159
5255
-- | \( O(\min(n_1,n_2,n_3)) \). 'zip3' takes three sequences and returns a
5160
5256
-- sequence of triples, analogous to 'zip'.
@@ -5200,7 +5296,3 @@ fromList2 n = execState (replicateA n (State ht))
5200
5296
where
5201
5297
ht (x: xs) = (xs, x)
5202
5298
ht [] = error " fromList2: short list"
5203
-
5204
- {-# NOINLINE bongo #-}
5205
- bongo :: Seq [a ] -> [a ]
5206
- bongo xs = GHC.Exts. inline foldMap id xs
0 commit comments