@@ -164,9 +164,9 @@ import Data.Functor (Functor(..))
164
164
import Data.Foldable (Foldable (foldl , foldl1 , foldr , foldr1 , foldMap , foldl' , foldr' , toList ))
165
165
#else
166
166
#if MIN_VERSION_base(4,6,0)
167
- import Data.Foldable (Foldable (foldl , foldl1 , foldr , foldr1 , foldMap , foldl' , foldr' ), toList )
167
+ import Data.Foldable (Foldable (foldl , foldl1 , foldr , foldr1 , foldMap , foldl' ), toList )
168
168
#else
169
- import Data.Foldable (Foldable (foldl , foldl1 , foldr , foldr1 , foldMap ), foldl' , foldr' , toList )
169
+ import Data.Foldable (Foldable (foldl , foldl1 , foldr , foldr1 , foldMap ), foldl' , toList )
170
170
#endif
171
171
#endif
172
172
import Data.Traversable
@@ -180,6 +180,7 @@ import Data.Data
180
180
#endif
181
181
#if __GLASGOW_HASKELL__ >= 708
182
182
import Data.Coerce
183
+ import qualified GHC.Exts
183
184
#define COERCE coerce
184
185
#else
185
186
#ifdef __GLASGOW_HASKELL__
@@ -192,9 +193,6 @@ import qualified Unsafe.Coerce
192
193
#if MIN_VERSION_base(4,8,0)
193
194
import Data.Functor.Identity (Identity (.. ))
194
195
#endif
195
- #ifdef __GLASGOW_HASKELL__
196
- import qualified GHC.Exts
197
- #endif
198
196
199
197
infixr 5 `consTree`
200
198
infixl 5 `snocTree`
@@ -246,6 +244,8 @@ instance Foldable Seq where
246
244
{-# INLINE length #-}
247
245
null = null
248
246
{-# INLINE null #-}
247
+ toList = toList
248
+ {-# INLINE toList #-}
249
249
#endif
250
250
251
251
instance Traversable Seq where
@@ -611,10 +611,6 @@ instance Applicative (State s) where
611
611
execState :: State s a -> s -> a
612
612
execState m x = snd (runState m x)
613
613
614
- -- | A helper method: a strict version of mapAccumL.
615
- mapAccumL' :: Traversable t => (a -> b -> (a , c )) -> a -> t b -> (a , t c )
616
- mapAccumL' f s t = runState (traverse (State . flip f) t) s
617
-
618
614
-- | 'applicativeTree' takes an Applicative-wrapped construction of a
619
615
-- piece of a FingerTree, assumed to always have the same size (which
620
616
-- is put in the second argument), and replicates it as many times as
@@ -1305,12 +1301,12 @@ adjustDigit f i (Four a b c d)
1305
1301
-- function that also depends on the element's index, and applies it to every
1306
1302
-- element in the sequence.
1307
1303
mapWithIndex :: (Int -> a -> b ) -> Seq a -> Seq b
1308
- mapWithIndex f (Seq xs) = Seq $ mapWithIndexTree (\ s (Elem a) -> Elem (f s a)) 0 xs
1304
+ mapWithIndex f' (Seq xs' ) = Seq $ mapWithIndexTree (\ s (Elem a) -> Elem (f' s a)) 0 xs'
1309
1305
where
1310
1306
{-# SPECIALIZE mapWithIndexTree :: (Int -> Elem y -> b) -> Int -> FingerTree (Elem y) -> FingerTree b #-}
1311
1307
{-# SPECIALIZE mapWithIndexTree :: (Int -> Node y -> b) -> Int -> FingerTree (Node y) -> FingerTree b #-}
1312
1308
mapWithIndexTree :: Sized a => (Int -> a -> b ) -> Int -> FingerTree a -> FingerTree b
1313
- mapWithIndexTree _f s Empty = s `seq` Empty
1309
+ mapWithIndexTree _ s Empty = s `seq` Empty
1314
1310
mapWithIndexTree f s (Single xs) = Single $ f s xs
1315
1311
mapWithIndexTree f s (Deep n pr m sf) = sPspr `seq` sPsprm `seq`
1316
1312
Deep n
@@ -1379,23 +1375,23 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg
1379
1375
create b{- tree_builder-} s{- tree_size-} i{- start_index-} trees = i `seq` s `seq` case trees of
1380
1376
1 -> Single $ b i
1381
1377
2 -> Deep (2 * s) (One (b i)) Empty (One (b (i+ s)))
1382
- 3 -> Deep (3 * s) (createTwo b s i) Empty (One (b (i+ 2 * s)))
1383
- 4 -> Deep (4 * s) (createTwo b s i) Empty (createTwo b s (i+ 2 * s))
1384
- 5 -> Deep (5 * s) (createThree b s i) Empty (createTwo b s (i+ 3 * s))
1385
- 6 -> Deep (6 * s) (createThree b s i) Empty (createThree b s (i+ 3 * s))
1378
+ 3 -> Deep (3 * s) (createTwo i) Empty (One (b (i+ 2 * s)))
1379
+ 4 -> Deep (4 * s) (createTwo i) Empty (createTwo (i+ 2 * s))
1380
+ 5 -> Deep (5 * s) (createThree i) Empty (createTwo (i+ 3 * s))
1381
+ 6 -> Deep (6 * s) (createThree i) Empty (createThree (i+ 3 * s))
1386
1382
_ -> case trees `quotRem` 3 of
1387
- (trees', 1 ) -> Deep (trees* s) (createTwo b s i)
1383
+ (trees', 1 ) -> Deep (trees* s) (createTwo i)
1388
1384
(create mb (3 * s) (i+ 2 * s) (trees'- 1 ))
1389
- (createTwo b s (i+ (2 + 3 * (trees'- 1 ))* s))
1390
- (trees', 2 ) -> Deep (trees* s) (createThree b s i)
1385
+ (createTwo (i+ (2 + 3 * (trees'- 1 ))* s))
1386
+ (trees', 2 ) -> Deep (trees* s) (createThree i)
1391
1387
(create mb (3 * s) (i+ 3 * s) (trees'- 1 ))
1392
- (createTwo b s (i+ (3 + 3 * (trees'- 1 ))* s))
1393
- (trees', 0 ) -> Deep (trees* s) (createThree b s i)
1388
+ (createTwo (i+ (3 + 3 * (trees'- 1 ))* s))
1389
+ (trees', _ ) -> Deep (trees* s) (createThree i)
1394
1390
(create mb (3 * s) (i+ 3 * s) (trees'- 2 ))
1395
- (createThree b s (i+ (3 + 3 * (trees'- 2 ))* s))
1391
+ (createThree (i+ (3 + 3 * (trees'- 2 ))* s))
1396
1392
where
1397
- createTwo b s i = Two (b i ) (b (i + s))
1398
- createThree b s i = Three (b i ) (b (i + s)) (b (i + s + s))
1393
+ createTwo j = Two (b j ) (b (j + s))
1394
+ createThree j = Three (b j ) (b (j + s)) (b (j + 2 * s))
1399
1395
mb j = Node3 (3 * s) (b j) (b (j + s)) (b (j + 2 * s))
1400
1396
1401
1397
-- Splitting
@@ -1884,8 +1880,8 @@ splitMap splt' = go
1884
1880
{-# SPECIALIZE splitMapTree :: (Int -> s -> (s,s)) -> (s -> Elem y -> b) -> s -> FingerTree (Elem y) -> FingerTree b #-}
1885
1881
{-# SPECIALIZE splitMapTree :: (Int -> s -> (s,s)) -> (s -> Node y -> b) -> s -> FingerTree (Node y) -> FingerTree b #-}
1886
1882
splitMapTree :: Sized a => (Int -> s -> (s ,s )) -> (s -> a -> b ) -> s -> FingerTree a -> FingerTree b
1887
- splitMapTree splt _f _s Empty = Empty
1888
- splitMapTree splt f s (Single xs) = Single $ f s xs
1883
+ splitMapTree _ _ _ Empty = Empty
1884
+ splitMapTree _ f s (Single xs) = Single $ f s xs
1889
1885
splitMapTree splt f s (Deep n pr m sf) = Deep n (splitMapDigit splt f prs pr) (splitMapTree splt (splitMapNode splt f) ms m) (splitMapDigit splt f sfs sf)
1890
1886
where
1891
1887
(prs, r) = splt (size pr) s
@@ -1894,7 +1890,7 @@ splitMap splt' = go
1894
1890
{-# SPECIALIZE splitMapDigit :: (Int -> s -> (s,s)) -> (s -> Elem y -> b) -> s -> Digit (Elem y) -> Digit b #-}
1895
1891
{-# SPECIALIZE splitMapDigit :: (Int -> s -> (s,s)) -> (s -> Node y -> b) -> s -> Digit (Node y) -> Digit b #-}
1896
1892
splitMapDigit :: Sized a => (Int -> s -> (s ,s )) -> (s -> a -> b ) -> s -> Digit a -> Digit b
1897
- splitMapDigit splt f s (One a) = One (f s a)
1893
+ splitMapDigit _ f s (One a) = One (f s a)
1898
1894
splitMapDigit splt f s (Two a b) = Two (f first a) (f second b)
1899
1895
where
1900
1896
(first, second) = splt (size a) s
0 commit comments