Skip to content

Commit

Permalink
Add NFData instances
Browse files Browse the repository at this point in the history
  • Loading branch information
Shimuuar committed Mar 22, 2015
1 parent 6f40a8a commit cfdb51c
Show file tree
Hide file tree
Showing 6 changed files with 35 additions and 8 deletions.
13 changes: 12 additions & 1 deletion fixed-vector/Data/Vector/Fixed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -153,6 +153,7 @@ module Data.Vector.Fixed (
) where

import Control.Applicative (Applicative(..),(<$>))
import Control.DeepSeq (NFData(..))
import Data.Data (Typeable,Data)
import Data.Monoid (Monoid(..))
import qualified Data.Foldable as F
Expand All @@ -164,7 +165,7 @@ import Data.Vector.Fixed.Cont (Vector(..),VectorN,Dim,length,ContVec,vector,
import qualified Data.Vector.Fixed.Cont as C
import Data.Vector.Fixed.Internal

import Prelude (Show(..),Eq(..),Ord(..),Functor(..),id,(.),($))
import Prelude (Show(..),Eq(..),Ord(..),Functor(..),id,(.),($),seq)
-- Needed for doctest
import Prelude (Char)

Expand Down Expand Up @@ -242,6 +243,10 @@ data VecList n a where
Cons :: a -> VecList n a -> VecList (S n) a
deriving (Typeable)

instance (Arity n, NFData a) => NFData (VecList n a) where
rnf = foldl (\r a -> r `seq` rnf a) ()
{-# INLINE rnf #-}

-- Vector instance
type instance Dim (VecList n) = n

Expand Down Expand Up @@ -302,6 +307,9 @@ instance Monoid a => Monoid (Only a) where
mempty = Only mempty
Only a `mappend` Only b = Only $ mappend a b

instance NFData a => NFData (Only a) where
rnf (Only a) = rnf a

type instance Dim Only = S Z

instance Vector Only a where
Expand All @@ -321,6 +329,9 @@ instance T.Traversable Empty where
sequenceA Empty = pure Empty
traverse _ Empty = pure Empty

instance NFData (Empty a) where
rnf Empty = ()

type instance Dim Empty = Z

instance Vector Empty a where
Expand Down
6 changes: 5 additions & 1 deletion fixed-vector/Data/Vector/Fixed/Boxed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -20,13 +20,14 @@ module Data.Vector.Fixed.Boxed (
) where

import Control.Applicative (Applicative(..))
import Control.DeepSeq (NFData(..))
import Data.Primitive.Array
import Data.Monoid (Monoid(..))
import Data.Data
import qualified Data.Foldable as F
import qualified Data.Traversable as T
import Prelude (Show(..),Eq(..),Ord(..),Functor(..),Monad(..))
import Prelude ((++),($),($!),undefined,error)
import Prelude ((++),($),($!),undefined,error,seq)

import Data.Vector.Fixed hiding (index)
import Data.Vector.Fixed.Mutable
Expand Down Expand Up @@ -82,6 +83,9 @@ con_Vec = mkConstr ty_Vec "Vec" [] Prefix
instance (Arity n, Show a) => Show (Vec n a) where
show v = "fromList " ++ show (toList v)

instance (Arity n, NFData a) => NFData (Vec n a) where
rnf = foldl (\r a -> r `seq` rnf a) ()
{-# INLINE rnf #-}

type instance Mutable (Vec n) = MVec n

Expand Down
7 changes: 5 additions & 2 deletions fixed-vector/Data/Vector/Fixed/Primitive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,12 +24,13 @@ module Data.Vector.Fixed.Primitive (
) where

import Control.Monad
import Control.DeepSeq (NFData(..))
import Data.Data
import Data.Monoid (Monoid(..))
import Data.Primitive.ByteArray
import Data.Primitive
import Prelude (Show(..),Eq(..),Ord(..),Num(..))
import Prelude ((++),($),($!),undefined)
import Prelude ((++),($),($!),undefined,seq)


import Data.Vector.Fixed hiding (index)
Expand Down Expand Up @@ -71,7 +72,9 @@ type Vec5 = Vec (S (S (S (S (S Z)))))
instance (Arity n, Prim a, Show a) => Show (Vec n a) where
show v = "fromList " ++ show (toList v)


instance (Arity n, Prim a, NFData a) => NFData (Vec n a) where
rnf = foldl (\r a -> r `seq` rnf a) ()
{-# INLINE rnf #-}

type instance Mutable (Vec n) = MVec n

Expand Down
7 changes: 5 additions & 2 deletions fixed-vector/Data/Vector/Fixed/Storable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -26,6 +26,7 @@ module Data.Vector.Fixed.Storable (
) where

import Control.Monad.Primitive
import Control.DeepSeq (NFData(..))
import Data.Monoid (Monoid(..))
import Data.Data
import Foreign.Ptr (castPtr)
Expand All @@ -35,7 +36,7 @@ import Foreign.Marshal.Array ( advancePtr, copyArray, moveArray )
import GHC.ForeignPtr ( ForeignPtr(..), mallocPlainForeignPtrBytes )
import GHC.Ptr ( Ptr(..) )
import Prelude (Show(..),Eq(..),Ord(..),Num(..),Monad(..),IO,Int)
import Prelude ((++),(&&),(||),($),undefined)
import Prelude ((++),(&&),(||),($),undefined,seq)

import Data.Vector.Fixed hiding (index)
import Data.Vector.Fixed.Mutable
Expand Down Expand Up @@ -96,7 +97,9 @@ unsafeWith f (Vec fp) = f (getPtr fp)
instance (Arity n, Storable a, Show a) => Show (Vec n a) where
show v = "fromList " ++ show (toList v)


instance (Arity n, Storable a, NFData a) => NFData (Vec n a) where
rnf = foldl (\r a -> r `seq` rnf a) ()
{-# INLINE rnf #-}

type instance Mutable (Vec n) = MVec n

Expand Down
9 changes: 7 additions & 2 deletions fixed-vector/Data/Vector/Fixed/Unboxed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -24,15 +24,16 @@ module Data.Vector.Fixed.Unboxed(
) where

import Control.Monad
import Control.DeepSeq (NFData(..))
import Data.Complex
import Data.Monoid (Monoid(..))
import Data.Data
import Data.Int (Int8, Int16, Int32, Int64 )
import Data.Word (Word,Word8,Word16,Word32,Word64)
import Prelude (Show(..),Eq(..),Ord(..),Int,Double,Float,Char,Bool(..))
import Prelude ((++),(||),($),(.))
import Prelude ((++),(||),($),(.),seq)

import Data.Vector.Fixed (Dim,Vector(..),VectorN,S,Z,toList,eq,ord,replicate,zipWith)
import Data.Vector.Fixed (Dim,Vector(..),VectorN,S,Z,toList,eq,ord,replicate,zipWith,foldl)
import Data.Vector.Fixed.Mutable
import qualified Data.Vector.Fixed.Cont as C
import qualified Data.Vector.Fixed.Primitive as P
Expand Down Expand Up @@ -70,6 +71,10 @@ class (IVector (Vec n) a, MVector (MVec n) a) => Unbox n a
instance (Arity n, Show a, Unbox n a) => Show (Vec n a) where
show v = "fromList " ++ show (toList v)

instance (Arity n, Unbox n a, NFData a) => NFData (Vec n a) where
rnf = foldl (\r a -> r `seq` rnf a) ()
{-# INLINE rnf #-}

type instance Mutable (Vec n) = MVec n

type instance Dim (Vec n) = n
Expand Down
1 change: 1 addition & 0 deletions fixed-vector/fixed-vector.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -67,6 +67,7 @@ Library
Ghc-options: -Wall
Build-Depends:
base >=3 && <5,
deepseq,
primitive
Exposed-modules:
-- API
Expand Down

0 comments on commit cfdb51c

Please sign in to comment.