Skip to content

Commit 610ebfb

Browse files
committed
Fix warnings.
1 parent 61eeeec commit 610ebfb

File tree

1 file changed

+22
-26
lines changed

1 file changed

+22
-26
lines changed

Data/Sequence.hs

Lines changed: 22 additions & 26 deletions
Original file line numberDiff line numberDiff line change
@@ -164,9 +164,9 @@ import Data.Functor (Functor(..))
164164
import Data.Foldable (Foldable(foldl, foldl1, foldr, foldr1, foldMap, foldl', foldr', toList))
165165
#else
166166
#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)
168168
#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)
170170
#endif
171171
#endif
172172
import Data.Traversable
@@ -180,6 +180,7 @@ import Data.Data
180180
#endif
181181
#if __GLASGOW_HASKELL__ >= 708
182182
import Data.Coerce
183+
import qualified GHC.Exts
183184
#define COERCE coerce
184185
#else
185186
#ifdef __GLASGOW_HASKELL__
@@ -192,9 +193,6 @@ import qualified Unsafe.Coerce
192193
#if MIN_VERSION_base(4,8,0)
193194
import Data.Functor.Identity (Identity(..))
194195
#endif
195-
#ifdef __GLASGOW_HASKELL__
196-
import qualified GHC.Exts
197-
#endif
198196

199197
infixr 5 `consTree`
200198
infixl 5 `snocTree`
@@ -246,6 +244,8 @@ instance Foldable Seq where
246244
{-# INLINE length #-}
247245
null = null
248246
{-# INLINE null #-}
247+
toList = toList
248+
{-# INLINE toList #-}
249249
#endif
250250

251251
instance Traversable Seq where
@@ -611,10 +611,6 @@ instance Applicative (State s) where
611611
execState :: State s a -> s -> a
612612
execState m x = snd (runState m x)
613613

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-
618614
-- | 'applicativeTree' takes an Applicative-wrapped construction of a
619615
-- piece of a FingerTree, assumed to always have the same size (which
620616
-- 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)
13051301
-- function that also depends on the element's index, and applies it to every
13061302
-- element in the sequence.
13071303
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'
13091305
where
13101306
{-# SPECIALIZE mapWithIndexTree :: (Int -> Elem y -> b) -> Int -> FingerTree (Elem y) -> FingerTree b #-}
13111307
{-# SPECIALIZE mapWithIndexTree :: (Int -> Node y -> b) -> Int -> FingerTree (Node y) -> FingerTree b #-}
13121308
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
13141310
mapWithIndexTree f s (Single xs) = Single $ f s xs
13151311
mapWithIndexTree f s (Deep n pr m sf) = sPspr `seq` sPsprm `seq`
13161312
Deep n
@@ -1379,23 +1375,23 @@ fromFunction len f | len < 0 = error "Data.Sequence.fromFunction called with neg
13791375
create b{-tree_builder-} s{-tree_size-} i{-start_index-} trees = i `seq` s `seq` case trees of
13801376
1 -> Single $ b i
13811377
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))
13861382
_ -> case trees `quotRem` 3 of
1387-
(trees', 1) -> Deep (trees*s) (createTwo b s i)
1383+
(trees', 1) -> Deep (trees*s) (createTwo i)
13881384
(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)
13911387
(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)
13941390
(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))
13961392
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))
13991395
mb j = Node3 (3*s) (b j) (b (j + s)) (b (j + 2*s))
14001396

14011397
-- Splitting
@@ -1884,8 +1880,8 @@ splitMap splt' = go
18841880
{-# SPECIALIZE splitMapTree :: (Int -> s -> (s,s)) -> (s -> Elem y -> b) -> s -> FingerTree (Elem y) -> FingerTree b #-}
18851881
{-# SPECIALIZE splitMapTree :: (Int -> s -> (s,s)) -> (s -> Node y -> b) -> s -> FingerTree (Node y) -> FingerTree b #-}
18861882
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
18891885
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)
18901886
where
18911887
(prs, r) = splt (size pr) s
@@ -1894,7 +1890,7 @@ splitMap splt' = go
18941890
{-# SPECIALIZE splitMapDigit :: (Int -> s -> (s,s)) -> (s -> Elem y -> b) -> s -> Digit (Elem y) -> Digit b #-}
18951891
{-# SPECIALIZE splitMapDigit :: (Int -> s -> (s,s)) -> (s -> Node y -> b) -> s -> Digit (Node y) -> Digit b #-}
18961892
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)
18981894
splitMapDigit splt f s (Two a b) = Two (f first a) (f second b)
18991895
where
19001896
(first, second) = splt (size a) s

0 commit comments

Comments
 (0)