@@ -80,7 +80,7 @@ import Data.Vector.Generic.Base
80
80
import qualified Data.Vector.Generic.Mutable.Base as M
81
81
import Data.Vector.Fusion.Bundle.Size
82
82
import Data.Vector.Fusion.Util ( Box (.. ), delay_inline )
83
- import Data.Vector.Fusion.Stream.Monadic ( Stream (.. ), Step (.. ), SPEC ( .. ) )
83
+ import Data.Vector.Fusion.Stream.Monadic ( Stream (.. ), Step (.. ) )
84
84
import qualified Data.Vector.Fusion.Stream.Monadic as S
85
85
import Control.Monad.Primitive
86
86
@@ -118,7 +118,7 @@ data Bundle m v a = Bundle { sElems :: Stream m a
118
118
119
119
fromStream :: Monad m => Stream m a -> Size -> Bundle m v a
120
120
{-# INLINE fromStream #-}
121
- fromStream (Stream step s ) sz = Bundle (Stream step s ) (Stream step' s ) Nothing sz
121
+ fromStream (Stream step t ) sz = Bundle (Stream step t ) (Stream step' t ) Nothing sz
122
122
where
123
123
step' s = do r <- step s
124
124
return $ fmap (\ x -> Chunk 1 (\ v -> M. basicUnsafeWrite v 0 x)) r
@@ -291,7 +291,7 @@ mapM_ :: Monad m => (a -> m b) -> Bundle m v a -> m ()
291
291
mapM_ m = S. mapM_ m . sElems
292
292
293
293
-- | Transform a 'Bundle' to use a different monad
294
- trans :: (Monad m , Monad m' ) => (forall a . m a -> m' a )
294
+ trans :: (Monad m , Monad m' ) => (forall z . m z -> m' z )
295
295
-> Bundle m v a -> Bundle m' v a
296
296
{-# INLINE_FUSED trans #-}
297
297
trans f Bundle {sElems = s, sChunks = cs, sVector = v, sSize = n}
@@ -754,7 +754,7 @@ enumFromTo_small x y = x `seq` y `seq` fromStream (Stream step x) (Exact n)
754
754
n = delay_inline max (fromIntegral y - fromIntegral x + 1 ) 0
755
755
756
756
{-# INLINE_INNER step #-}
757
- step x | x <= y = return $ Yield x (x + 1 )
757
+ step z | z <= y = return $ Yield z (z + 1 )
758
758
| otherwise = return $ Done
759
759
760
760
{-# RULES
@@ -803,31 +803,31 @@ enumFromTo_int x y = x `seq` y `seq` fromStream (Stream step x) (Exact (len x y)
803
803
where
804
804
{-# INLINE [0] len #-}
805
805
len :: Int -> Int -> Int
806
- len x y | x > y = 0
806
+ len u v | u > v = 0
807
807
| otherwise = BOUNDS_CHECK (check) " enumFromTo" " vector too large"
808
808
(n > 0 )
809
809
$ n
810
810
where
811
- n = y - x + 1
811
+ n = v - u + 1
812
812
813
813
{-# INLINE_INNER step #-}
814
- step x | x <= y = return $ Yield x (x + 1 )
814
+ step z | z <= y = return $ Yield z (z + 1 )
815
815
| otherwise = return $ Done
816
816
817
817
enumFromTo_intlike :: (Integral a , Monad m ) => a -> a -> Bundle m v a
818
818
{-# INLINE_FUSED enumFromTo_intlike #-}
819
819
enumFromTo_intlike x y = x `seq` y `seq` fromStream (Stream step x) (Exact (len x y))
820
820
where
821
821
{-# INLINE [0] len #-}
822
- len x y | x > y = 0
822
+ len u v | u > v = 0
823
823
| otherwise = BOUNDS_CHECK (check) " enumFromTo" " vector too large"
824
824
(n > 0 )
825
825
$ fromIntegral n
826
826
where
827
- n = y - x + 1
827
+ n = v - u + 1
828
828
829
829
{-# INLINE_INNER step #-}
830
- step x | x <= y = return $ Yield x (x + 1 )
830
+ step z | z <= y = return $ Yield z (z + 1 )
831
831
| otherwise = return $ Done
832
832
833
833
{-# RULES
@@ -854,15 +854,15 @@ enumFromTo_big_word :: (Integral a, Monad m) => a -> a -> Bundle m v a
854
854
enumFromTo_big_word x y = x `seq` y `seq` fromStream (Stream step x) (Exact (len x y))
855
855
where
856
856
{-# INLINE [0] len #-}
857
- len x y | x > y = 0
857
+ len u v | u > v = 0
858
858
| otherwise = BOUNDS_CHECK (check) " enumFromTo" " vector too large"
859
859
(n < fromIntegral (maxBound :: Int ))
860
860
$ fromIntegral (n+ 1 )
861
861
where
862
- n = y - x
862
+ n = v - u
863
863
864
864
{-# INLINE_INNER step #-}
865
- step x | x <= y = return $ Yield x (x + 1 )
865
+ step z | z <= y = return $ Yield z (z + 1 )
866
866
| otherwise = return $ Done
867
867
868
868
{-# RULES
@@ -894,15 +894,15 @@ enumFromTo_big_int :: (Integral a, Monad m) => a -> a -> Bundle m v a
894
894
enumFromTo_big_int x y = x `seq` y `seq` fromStream (Stream step x) (Exact (len x y))
895
895
where
896
896
{-# INLINE [0] len #-}
897
- len x y | x > y = 0
897
+ len u v | u > v = 0
898
898
| otherwise = BOUNDS_CHECK (check) " enumFromTo" " vector too large"
899
899
(n > 0 && n <= fromIntegral (maxBound :: Int ))
900
900
$ fromIntegral n
901
901
where
902
- n = y - x + 1
902
+ n = v - u + 1
903
903
904
904
{-# INLINE_INNER step #-}
905
- step x | x <= y = return $ Yield x (x + 1 )
905
+ step z | z <= y = return $ Yield z (z + 1 )
906
906
| otherwise = return $ Done
907
907
908
908
#if WORD_SIZE_IN_BITS > 32
@@ -926,7 +926,7 @@ enumFromTo_char x y = x `seq` y `seq` fromStream (Stream step xn) (Exact n)
926
926
n = delay_inline max 0 (yn - xn + 1 )
927
927
928
928
{-# INLINE_INNER step #-}
929
- step xn | xn <= yn = return $ Yield (unsafeChr xn ) (xn + 1 )
929
+ step zn | zn <= yn = return $ Yield (unsafeChr zn ) (zn + 1 )
930
930
| otherwise = return $ Done
931
931
932
932
{-# RULES
@@ -950,10 +950,11 @@ enumFromTo_double n m = n `seq` m `seq` fromStream (Stream step n) (Max (len n m
950
950
{-# INLINE [0] len #-}
951
951
len x y | x > y = 0
952
952
| otherwise = BOUNDS_CHECK (check) " enumFromTo" " vector too large"
953
- (n > 0 )
954
- $ fromIntegral n
953
+ (l > 0 )
954
+ $ fromIntegral l
955
955
where
956
- n = truncate (y- x)+ 2
956
+ l :: Integer
957
+ l = truncate (y- x)+ 2
957
958
958
959
{-# INLINE_INNER step #-}
959
960
step x | x <= lim = return $ Yield x (x+ 1 )
@@ -1025,12 +1026,12 @@ fromVector v = v `seq` n `seq` Bundle (Stream step 0)
1025
1026
1026
1027
fromVectors :: forall m v a . (Monad m , Vector v a ) => [v a ] -> Bundle m v a
1027
1028
{-# INLINE_FUSED fromVectors #-}
1028
- fromVectors vs = Bundle (Stream pstep (Left vs ))
1029
- (Stream vstep vs )
1029
+ fromVectors us = Bundle (Stream pstep (Left us ))
1030
+ (Stream vstep us )
1030
1031
Nothing
1031
1032
(Exact n)
1032
1033
where
1033
- n = List. foldl' (\ k v -> k + basicLength v) 0 vs
1034
+ n = List. foldl' (\ k v -> k + basicLength v) 0 us
1034
1035
1035
1036
pstep (Left [] ) = return Done
1036
1037
pstep (Left (v: vs)) = basicLength v `seq` return (Skip (Right (v,0 ,vs)))
@@ -1051,9 +1052,9 @@ fromVectors vs = Bundle (Stream pstep (Left vs))
1051
1052
1052
1053
concatVectors :: (Monad m , Vector v a ) => Bundle m u (v a ) -> Bundle m v a
1053
1054
{-# INLINE_FUSED concatVectors #-}
1054
- concatVectors Bundle {sElems = Stream step s }
1055
- = Bundle (Stream pstep (Left s ))
1056
- (Stream vstep s )
1055
+ concatVectors Bundle {sElems = Stream step t }
1056
+ = Bundle (Stream pstep (Left t ))
1057
+ (Stream vstep t )
1057
1058
Nothing
1058
1059
Unknown
1059
1060
where
0 commit comments