1
+ {- OPTIONS_GHC -ddump-simpl #-}
1
2
{-# LANGUAGE CPP #-}
2
3
#include "containers.h"
3
4
{-# LANGUAGE BangPatterns #-}
7
8
{-# LANGUAGE DeriveLift #-}
8
9
{-# LANGUAGE StandaloneDeriving #-}
9
10
{-# LANGUAGE FlexibleInstances #-}
11
+ {-# LANGUAGE GADTs #-}
10
12
{-# LANGUAGE InstanceSigs #-}
11
13
{-# LANGUAGE ScopedTypeVariables #-}
12
14
{-# LANGUAGE TemplateHaskellQuotes #-}
@@ -177,6 +179,7 @@ module Data.Sequence.Internal (
177
179
node2 ,
178
180
node3 ,
179
181
#endif
182
+ bongo
180
183
) where
181
184
182
185
import Utils.Containers.Internal.Prelude hiding (
@@ -194,7 +197,7 @@ import Control.Applicative ((<$>), (<**>), Alternative,
194
197
import qualified Control.Applicative as Applicative
195
198
import Control.DeepSeq (NFData (rnf ),NFData1 (liftRnf ))
196
199
import Control.Monad (MonadPlus (.. ))
197
- import Data.Monoid (Monoid (.. ))
200
+ import Data.Monoid (Monoid (.. ), Endo ( .. ), Dual ( .. ) )
198
201
import Data.Functor (Functor (.. ))
199
202
import Utils.Containers.Internal.State (State (.. ), execState )
200
203
import Data.Foldable (foldr' , toList )
@@ -234,6 +237,7 @@ import Data.Functor.Identity (Identity(..))
234
237
import Utils.Containers.Internal.StrictPair (StrictPair (.. ), toPair )
235
238
import Control.Monad.Zip (MonadZip (.. ))
236
239
import Control.Monad.Fix (MonadFix (.. ), fix )
240
+ import Data.Sequence.Internal.Depth (Depth_ (.. ), Depth2_ (.. ))
237
241
238
242
default ()
239
243
@@ -378,16 +382,38 @@ fmapSeq f (Seq xs) = Seq (fmap (fmap f) xs)
378
382
#-}
379
383
#endif
380
384
385
+ -- type Depth = Depth_ Elem Node
386
+ type Depth = Depth_ Node
387
+ type Depth2 = Depth2_ Node
388
+
381
389
instance Foldable Seq where
382
390
#ifdef __GLASGOW_HASKELL__
383
391
foldMap :: forall m a . Monoid m => (a -> m ) -> Seq a -> m
384
- foldMap = coerce (foldMap :: (Elem a -> m ) -> FingerTree (Elem a ) -> m )
392
+ foldMap f (Seq t0) = foldMapFT Bottom t0
393
+ where
394
+ foldMapBlob :: Depth (Elem a ) t -> t -> m
395
+ foldMapBlob Bottom (Elem a) = f a
396
+ foldMapBlob (Deeper w) (Node2 _ x y) = foldMapBlob w x <> foldMapBlob w y
397
+ foldMapBlob (Deeper w) (Node3 _ x y z) = foldMapBlob w x <> foldMapBlob w y <> foldMapBlob w z
398
+
399
+ foldMapFT :: Depth (Elem a ) t -> FingerTree t -> m
400
+ foldMapFT ! _ EmptyT = mempty
401
+ foldMapFT w (Single t) = foldMapBlob w t
402
+ foldMapFT w (Deep _ pr m sf) =
403
+ foldMap (foldMapBlob w) pr
404
+ <> foldMapFT (Deeper w) m
405
+ <> foldMap (foldMapBlob w) sf
385
406
386
407
foldr :: forall a b . (a -> b -> b ) -> b -> Seq a -> b
387
- foldr = coerce (foldr :: (Elem a -> b -> b ) -> b -> FingerTree (Elem a ) -> b )
408
+ -- We define this explicitly so we can inline the foldMap. And we don't
409
+ -- define it as a coercion of the FingerTree version because we want users
410
+ -- to have the option of (effectively) inlining it explicitly.
411
+ foldr f z t = appEndo (GHC.Exts. inline foldMap (coerce f) t) z
388
412
389
413
foldl :: forall b a . (b -> a -> b ) -> b -> Seq a -> b
390
- foldl = coerce (foldl :: (b -> Elem a -> b ) -> b -> FingerTree (Elem a ) -> b )
414
+ -- Should we define this by hand to associate optimally? Or is GHC
415
+ -- clever enough to do that for us?
416
+ foldl f z t = appEndo (getDual (GHC.Exts. inline foldMap (Dual . Endo . flip f) t)) z
391
417
392
418
foldr' :: forall a b . (a -> b -> b ) -> b -> Seq a -> b
393
419
foldr' = coerce (foldr' :: (Elem a -> b -> b ) -> b -> FingerTree (Elem a ) -> b )
@@ -426,7 +452,37 @@ instance Foldable Seq where
426
452
instance Traversable Seq where
427
453
#if __GLASGOW_HASKELL__
428
454
{-# INLINABLE traverse #-}
429
- #endif
455
+ traverse :: forall f a b . Applicative f => (a -> f b ) -> Seq a -> f (Seq b )
456
+ traverse f (Seq t0) = Seq <$> traverseFT Bottom2 t0
457
+ where
458
+ traverseFT :: Depth2 (Elem a ) t (Elem b ) u -> FingerTree t -> f (FingerTree u )
459
+ traverseFT ! _ EmptyT = pure EmptyT
460
+ traverseFT w (Single t) = Single <$> traverseBlob w t
461
+ traverseFT w (Deep s pr m sf) = liftA3 (Deep s)
462
+ (traverse (traverseBlob w) pr)
463
+ (traverseFT (Deeper2 w) m)
464
+ (traverse (traverseBlob w) sf)
465
+
466
+ -- Traverse a 2-3 tree, given its height.
467
+ traverseBlob :: Depth2 (Elem a ) t (Elem b ) u -> t -> f u
468
+ traverseBlob Bottom2 (Elem a) = Elem <$> f a
469
+
470
+ -- We have a special case here to avoid needing to `fmap Elem` over
471
+ -- each of the leaves, in case that's not free in the relevant functor.
472
+ -- We still end up using extra fmaps for the very first level of the
473
+ -- FingerTree and the Seq constructor. While we *could* avoid that,
474
+ -- doing so requires a good bit of extra code to save *at most* nine
475
+ -- fmap applications for the sequence. It would also save on Depth
476
+ -- comparisons, but I doubt that matters very much.
477
+ traverseBlob (Deeper2 Bottom2 ) (Node2 s (Elem x) (Elem y))
478
+ = liftA2 (\ x' y' -> Node2 s (Elem x') (Elem y')) (f x) (f y)
479
+ traverseBlob (Deeper2 Bottom2 ) (Node3 s (Elem x) (Elem y) (Elem z))
480
+ = liftA3 (\ x' y' z' -> Node3 s (Elem x') (Elem y') (Elem z'))
481
+ (f x) (f y) (f z)
482
+
483
+ traverseBlob (Deeper2 w) (Node2 s x y) = liftA2 (Node2 s) (traverseBlob w x) (traverseBlob w y)
484
+ traverseBlob (Deeper2 w) (Node3 s x y z) = liftA3 (Node3 s) (traverseBlob w x) (traverseBlob w y) (traverseBlob w z)
485
+ #else
430
486
traverse _ (Seq EmptyT ) = pure (Seq EmptyT )
431
487
traverse f' (Seq (Single (Elem x'))) =
432
488
(\ x'' -> Seq (Single (Elem x''))) <$> f' x'
@@ -498,6 +554,7 @@ instance Traversable Seq where
498
554
:: Applicative f
499
555
=> (Node a -> f (Node b )) -> Node (Node a ) -> f (Node (Node b ))
500
556
traverseNodeN f t = traverse f t
557
+ #endif
501
558
502
559
instance NFData a => NFData (Seq a ) where
503
560
rnf (Seq xs) = rnf xs
@@ -1067,7 +1124,33 @@ instance Sized a => Sized (FingerTree a) where
1067
1124
size (Single x) = size x
1068
1125
size (Deep v _ _ _) = v
1069
1126
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.
1070
1133
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
1071
1154
foldMap _ EmptyT = mempty
1072
1155
foldMap f' (Single x') = f' x'
1073
1156
foldMap f' (Deep _ pr' m' sf') =
@@ -1094,8 +1177,6 @@ instance Foldable FingerTree where
1094
1177
1095
1178
foldMapNodeN :: Monoid m => (Node a -> m ) -> Node (Node a ) -> m
1096
1179
foldMapNodeN f t = foldNode (<>) f t
1097
- #if __GLASGOW_HASKELL__
1098
- {-# INLINABLE foldMap #-}
1099
1180
#endif
1100
1181
1101
1182
foldr _ z' EmptyT = z'
@@ -1265,7 +1346,7 @@ foldDigit _ f (One a) = f a
1265
1346
foldDigit (<+>) f (Two a b) = f a <+> f b
1266
1347
foldDigit (<+>) f (Three a b c) = f a <+> f b <+> f c
1267
1348
foldDigit (<+>) f (Four a b c d) = f a <+> f b <+> f c <+> f d
1268
- {-# INLINE foldDigit #-}
1349
+ {-# INLINABLE foldDigit #-}
1269
1350
1270
1351
instance Foldable Digit where
1271
1352
foldMap = foldDigit mappend
@@ -3234,15 +3315,56 @@ foldWithIndexNode (<+>) f s (Node3 _ a b c) = f s a <+> f sPsa b <+> f sPsab c
3234
3315
-- element in the sequence.
3235
3316
--
3236
3317
-- @since 0.5.8
3237
- foldMapWithIndex :: Monoid m => (Int -> a -> m ) -> Seq a -> m
3318
+ foldMapWithIndex :: forall m a . Monoid m => (Int -> a -> m ) -> Seq a -> m
3319
+ #ifdef __GLASGOW_HASKELL__
3320
+ foldMapWithIndex f (Seq t) = foldMapWithIndexFT Bottom 0 t
3321
+ where
3322
+ foldMapWithIndexFT :: Depth (Elem a ) t -> Int -> FingerTree t -> m
3323
+ foldMapWithIndexFT ! _ ! _ EmptyT = mempty
3324
+ foldMapWithIndexFT d s (Single xs) = foldMapWithIndexBlob d s xs
3325
+ foldMapWithIndexFT d s (Deep _ pr m sf) = case depthSized d of { Sizzy ->
3326
+ foldWithIndexDigit (<>) (foldMapWithIndexBlob d) s pr <>
3327
+ foldMapWithIndexFT (Deeper d) sPspr m <>
3328
+ foldWithIndexDigit (<>) (foldMapWithIndexBlob d) sPsprm sf
3329
+ where
3330
+ ! sPspr = s + size pr
3331
+ ! sPsprm = sPspr + size m
3332
+ }
3333
+
3334
+ foldMapWithIndexBlob :: Depth (Elem a ) t -> Int -> t -> m
3335
+ foldMapWithIndexBlob Bottom k (Elem a) = f k a
3336
+ foldMapWithIndexBlob (Deeper yop) k (Node2 _s t1 t2) =
3337
+ foldMapWithIndexBlob yop k t1 <>
3338
+ foldMapWithIndexBlob yop (k + sizeBlob yop t1) t2
3339
+ foldMapWithIndexBlob (Deeper yop) k (Node3 _s t1 t2 t3) =
3340
+ foldMapWithIndexBlob yop k t1 <>
3341
+ foldMapWithIndexBlob yop (k + st1) t2 <>
3342
+ foldMapWithIndexBlob yop (k + st1t2) t3
3343
+ where
3344
+ st1 = sizeBlob yop t1
3345
+ st1t2 = st1 + sizeBlob yop t2
3346
+ {-# INLINABLE foldMapWithIndex #-}
3347
+
3348
+ data Sizzy a where
3349
+ Sizzy :: Sized a => Sizzy a
3350
+
3351
+ depthSized :: Depth (Elem a ) t -> Sizzy t
3352
+ depthSized Bottom = Sizzy
3353
+ depthSized (Deeper _) = Sizzy
3354
+
3355
+ sizeBlob :: Depth (Elem a ) t -> t -> Int
3356
+ sizeBlob Bottom = size
3357
+ sizeBlob (Deeper _) = size
3358
+
3359
+ #else
3238
3360
foldMapWithIndex f' (Seq xs') = foldMapWithIndexTreeE (lift_elem f') 0 xs'
3239
3361
where
3240
3362
lift_elem :: (Int -> a -> m ) -> (Int -> Elem a -> m )
3241
- #ifdef __GLASGOW_HASKELL__
3363
+ # ifdef __GLASGOW_HASKELL__
3242
3364
lift_elem g = coerce g
3243
- #else
3365
+ # else
3244
3366
lift_elem g = \ s (Elem a) -> g s a
3245
- #endif
3367
+ # endif
3246
3368
{-# INLINE lift_elem #-}
3247
3369
-- We have to specialize these functions by hand, unfortunately, because
3248
3370
-- GHC does not specialize until *all* instances are determined.
@@ -3281,9 +3403,6 @@ foldMapWithIndex f' (Seq xs') = foldMapWithIndexTreeE (lift_elem f') 0 xs'
3281
3403
3282
3404
foldMapWithIndexNodeN :: Monoid m => (Int -> Node a -> m ) -> Int -> Node (Node a ) -> m
3283
3405
foldMapWithIndexNodeN f i t = foldWithIndexNode (<>) f i t
3284
-
3285
- #if __GLASGOW_HASKELL__
3286
- {-# INLINABLE foldMapWithIndex #-}
3287
3406
#endif
3288
3407
3289
3408
-- | 'traverseWithIndex' is a version of 'traverse' that also offers
@@ -5036,3 +5155,7 @@ fromList2 n = execState (replicateA n (State ht))
5036
5155
where
5037
5156
ht (x: xs) = (xs, x)
5038
5157
ht [] = error " fromList2: short list"
5158
+
5159
+ {-# NOINLINE bongo #-}
5160
+ bongo :: Seq [a ] -> [a ]
5161
+ bongo xs = GHC.Exts. inline foldMap id xs
0 commit comments