Skip to content

Commit

Permalink
Fix GHC 7.10 warnings.
Browse files Browse the repository at this point in the history
  • Loading branch information
23Skidoo committed Aug 17, 2015
1 parent e000d6c commit dbe7ecb
Show file tree
Hide file tree
Showing 10 changed files with 41 additions and 11 deletions.
5 changes: 4 additions & 1 deletion Data/Vector.hs
Original file line number Diff line number Diff line change
Expand Up @@ -187,11 +187,14 @@ import Data.Typeable ( Typeable )
import Data.Data ( Data(..) )
import Text.Read ( Read(..), readListPrecDefault )

import Data.Monoid ( Monoid(..) )
import qualified Control.Applicative as Applicative
import qualified Data.Foldable as Foldable
import qualified Data.Traversable as Traversable

#if !MIN_VERSION_base(4,8,0)
import Data.Monoid ( Monoid(..) )
#endif

#if __GLASGOW_HASKELL__ >= 708
import qualified GHC.Exts as Exts (IsList(..))
#endif
Expand Down
2 changes: 1 addition & 1 deletion Data/Vector/Fusion/Bundle.hs
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,7 @@ type Bundle = M.Bundle Id
type MBundle = M.Bundle

inplace :: (forall m. Monad m => S.Stream m a -> S.Stream m b)
-> (Size -> Size) -> Bundle v a -> Bundle v b
-> (Size -> Size) -> Bundle v a -> Bundle v b
{-# INLINE_FUSED inplace #-}
inplace f g b = b `seq` M.fromStream (f (M.elements b)) (g (M.size b))

Expand Down
14 changes: 11 additions & 3 deletions Data/Vector/Fusion/Bundle/Monadic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -101,12 +101,20 @@ import Prelude hiding ( length, null,
scanl, scanl1,
enumFromTo, enumFromThenTo )

import Data.Int ( Int8, Int16, Int32, Int64 )
import Data.Word ( Word8, Word16, Word32, Word, Word64 )
import Data.Int ( Int8, Int16, Int32 )
import Data.Word ( Word8, Word16, Word32, Word64 )

#if !MIN_VERSION_base(4,8,0)
import Data.Word ( Word )
#endif

#include "vector.h"
#include "MachDeps.h"

#if WORD_SIZE_IN_BITS > 32
import Data.Int ( Int64 )
#endif

data Chunk v a = Chunk Int (forall m. (PrimMonad m, Vector v a) => Mutable v (PrimState m) a -> m ())

-- | Monadic streams
Expand Down Expand Up @@ -888,6 +896,7 @@ enumFromTo_big_word x y = x `seq` y `seq` fromStream (Stream step x) (Exact (len
:: Monad m => Integer -> Integer -> Bundle m v Integer #-}


#if WORD_SIZE_IN_BITS > 32

-- FIXME: the "too large" test is totally wrong
enumFromTo_big_int :: (Integral a, Monad m) => a -> a -> Bundle m v a
Expand All @@ -906,7 +915,6 @@ enumFromTo_big_int x y = x `seq` y `seq` fromStream (Stream step x) (Exact (len
step z | z <= y = return $ Yield z (z+1)
| otherwise = return $ Done

#if WORD_SIZE_IN_BITS > 32

{-# RULES

Expand Down
14 changes: 11 additions & 3 deletions Data/Vector/Fusion/Stream/Monadic.hs
Original file line number Diff line number Diff line change
Expand Up @@ -89,8 +89,12 @@ import Prelude hiding ( length, null,
scanl, scanl1,
enumFromTo, enumFromThenTo )

import Data.Int ( Int8, Int16, Int32, Int64 )
import Data.Int ( Int8, Int16, Int32 )
import Data.Word ( Word8, Word16, Word32, Word64 )

#if !MIN_VERSION_base(4,8,0)
import Data.Word ( Word8, Word16, Word32, Word, Word64 )
#endif

#if __GLASGOW_HASKELL__ >= 708
import GHC.Types ( SPEC(..) )
Expand All @@ -101,6 +105,10 @@ import GHC.Exts ( SpecConstrAnnotation(..) )
#include "vector.h"
#include "MachDeps.h"

#if WORD_SIZE_IN_BITS > 32
import Data.Int ( Int64 )
#endif

#if __GLASGOW_HASKELL__ < 708
data SPEC = SPEC | SPEC2
#if __GLASGOW_HASKELL__ >= 700
Expand Down Expand Up @@ -1403,6 +1411,8 @@ enumFromTo_big_word x y = x `seq` y `seq` Stream step x



#if WORD_SIZE_IN_BITS > 32

-- FIXME: the "too large" test is totally wrong
enumFromTo_big_int :: (Integral a, Monad m) => a -> a -> Stream m a
{-# INLINE_FUSED enumFromTo_big_int #-}
Expand All @@ -1412,8 +1422,6 @@ enumFromTo_big_int x y = x `seq` y `seq` Stream step x
step z | z <= y = return $ Yield z (z+1)
| otherwise = return $ Done

#if WORD_SIZE_IN_BITS > 32

{-# RULES

"enumFromTo<Int64> [Stream]"
Expand Down
4 changes: 3 additions & 1 deletion Data/Vector/Fusion/Util.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
-- |
-- Module : Data.Vector.Fusion.Util
-- Copyright : (c) Roman Leshchinskiy 2009
Expand All @@ -16,7 +17,9 @@ module Data.Vector.Fusion.Util (
delay_inline, delayed_min
) where

#if !MIN_VERSION_base(4,8,0)
import Control.Applicative (Applicative(..))
#endif

-- | Identity monad
newtype Id a = Id { unId :: a }
Expand Down Expand Up @@ -55,4 +58,3 @@ delay_inline f = f
delayed_min :: Int -> Int -> Int
{-# INLINE [0] delayed_min #-}
delayed_min m n = min m n

2 changes: 2 additions & 0 deletions Data/Vector/Primitive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -164,7 +164,9 @@ import Data.Typeable ( Typeable )
import Data.Data ( Data(..) )
import Text.Read ( Read(..), readListPrecDefault )

#if !MIN_VERSION_base(4,8,0)
import Data.Monoid ( Monoid(..) )
#endif

#if __GLASGOW_HASKELL__ >= 708
import qualified GHC.Exts as Exts
Expand Down
2 changes: 2 additions & 0 deletions Data/Vector/Storable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -169,7 +169,9 @@ import Data.Typeable ( Typeable )
import Data.Data ( Data(..) )
import Text.Read ( Read(..), readListPrecDefault )

#if !MIN_VERSION_base(4,8,0)
import Data.Monoid ( Monoid(..) )
#endif

#if __GLASGOW_HASKELL__ >= 708
import qualified GHC.Exts as Exts
Expand Down
2 changes: 2 additions & 0 deletions Data/Vector/Unboxed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -186,7 +186,9 @@ import Prelude hiding ( length, null,

import Text.Read ( Read(..), readListPrecDefault )

#if !MIN_VERSION_base(4,8,0)
import Data.Monoid ( Monoid(..) )
#endif

#if __GLASGOW_HASKELL__ >= 708
import qualified GHC.Exts as Exts (IsList(..))
Expand Down
6 changes: 5 additions & 1 deletion Data/Vector/Unboxed/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -30,10 +30,14 @@ import Control.DeepSeq ( NFData(rnf) )
import Control.Monad.Primitive
import Control.Monad ( liftM )

import Data.Word ( Word, Word8, Word16, Word32, Word64 )
import Data.Word ( Word8, Word16, Word32, Word64 )
import Data.Int ( Int8, Int16, Int32, Int64 )
import Data.Complex

#if !MIN_VERSION_base(4,8,0)
import Data.Word ( Word )
#endif

#if __GLASGOW_HASKELL__ >= 707
import Data.Typeable ( Typeable )
#else
Expand Down
1 change: 0 additions & 1 deletion include/vector.h
Original file line number Diff line number Diff line change
Expand Up @@ -18,4 +18,3 @@ import qualified Data.Vector.Internal.Check as Ck

#define PHASE_STREAM Please use "PHASE_FUSED" instead
#define INLINE_STREAM Please use "INLINE_FUSED" instead

0 comments on commit dbe7ecb

Please sign in to comment.