primitive-0.8.0.0/0000755000000000000000000000000007346545000012056 5ustar0000000000000000primitive-0.8.0.0/Control/Monad/0000755000000000000000000000000007346545000014534 5ustar0000000000000000primitive-0.8.0.0/Control/Monad/Primitive.hs0000644000000000000000000003014307346545000017041 0ustar0000000000000000{-# LANGUAGE CPP, MagicHash, UnboxedTuples, TypeFamilies #-} {-# LANGUAGE FlexibleContexts, FlexibleInstances, UndecidableInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# OPTIONS_GHC -fno-warn-deprecations #-} -- | -- Module : Control.Monad.Primitive -- Copyright : (c) Roman Leshchinskiy 2009 -- License : BSD-style -- -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- -- Primitive state-transformer monads. module Control.Monad.Primitive ( PrimMonad(..), RealWorld, primitive_, PrimBase(..), MonadPrim, MonadPrimBase, liftPrim, primToPrim, primToIO, primToST, ioToPrim, stToPrim, unsafePrimToPrim, unsafePrimToIO, unsafePrimToST, unsafeIOToPrim, unsafeSTToPrim, unsafeInlinePrim, unsafeInlineIO, unsafeInlineST, touch, keepAlive, evalPrim, unsafeInterleave, unsafeDupableInterleave, noDuplicate ) where import GHC.Exts ( State#, RealWorld, noDuplicate#, touch# #if defined(HAVE_KEEPALIVE) , keepAlive# #endif , unsafeCoerce#, realWorld#, seq# ) import GHC.IO ( IO(..) ) import GHC.ST ( ST(..) ) #if __GLASGOW_HASKELL__ >= 802 import qualified Control.Monad.ST.Lazy as L #endif import Control.Monad.Trans.Class (lift) import Control.Monad.Trans.Cont ( ContT ) import Control.Monad.Trans.Identity ( IdentityT (IdentityT) ) import Control.Monad.Trans.Maybe ( MaybeT ) import Control.Monad.Trans.Reader ( ReaderT ) import Control.Monad.Trans.State ( StateT ) import Control.Monad.Trans.Writer ( WriterT ) import Control.Monad.Trans.RWS ( RWST ) #if !MIN_VERSION_transformers(0,6,0) import Control.Monad.Trans.List ( ListT ) import Control.Monad.Trans.Error ( ErrorT, Error) #endif import Control.Monad.Trans.Except ( ExceptT ) #if MIN_VERSION_transformers(0,5,3) import Control.Monad.Trans.Accum ( AccumT ) import Control.Monad.Trans.Select ( SelectT ) #endif #if MIN_VERSION_transformers(0,5,6) import qualified Control.Monad.Trans.Writer.CPS as CPS import qualified Control.Monad.Trans.RWS.CPS as CPS #endif import qualified Control.Monad.Trans.RWS.Strict as Strict ( RWST ) import qualified Control.Monad.Trans.State.Strict as Strict ( StateT ) import qualified Control.Monad.Trans.Writer.Strict as Strict ( WriterT ) -- | Class of monads which can perform primitive state-transformer actions. class Monad m => PrimMonad m where -- | State token type. type PrimState m -- | Execute a primitive operation. primitive :: (State# (PrimState m) -> (# State# (PrimState m), a #)) -> m a -- | Class of primitive monads for state-transformer actions. -- -- Unlike 'PrimMonad', this typeclass requires that the @Monad@ be fully -- expressed as a state transformer, therefore disallowing other monad -- transformers on top of the base @IO@ or @ST@. -- -- @since 0.6.0.0 class PrimMonad m => PrimBase m where -- | Expose the internal structure of the monad. internal :: m a -> State# (PrimState m) -> (# State# (PrimState m), a #) -- | Execute a primitive operation with no result. primitive_ :: PrimMonad m => (State# (PrimState m) -> State# (PrimState m)) -> m () {-# INLINE primitive_ #-} primitive_ f = primitive (\s# -> case f s# of s'# -> (# s'#, () #)) instance PrimMonad IO where type PrimState IO = RealWorld primitive = IO {-# INLINE primitive #-} instance PrimBase IO where internal (IO p) = p {-# INLINE internal #-} -- | @since 0.6.3.0 instance PrimMonad m => PrimMonad (ContT r m) where type PrimState (ContT r m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} instance PrimMonad m => PrimMonad (IdentityT m) where type PrimState (IdentityT m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} -- | @since 0.6.2.0 instance PrimBase m => PrimBase (IdentityT m) where internal (IdentityT m) = internal m {-# INLINE internal #-} #if !MIN_VERSION_transformers(0,6,0) instance PrimMonad m => PrimMonad (ListT m) where type PrimState (ListT m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} instance (Error e, PrimMonad m) => PrimMonad (ErrorT e m) where type PrimState (ErrorT e m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} #endif instance PrimMonad m => PrimMonad (MaybeT m) where type PrimState (MaybeT m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} instance PrimMonad m => PrimMonad (ReaderT r m) where type PrimState (ReaderT r m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} instance PrimMonad m => PrimMonad (StateT s m) where type PrimState (StateT s m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} instance (Monoid w, PrimMonad m) => PrimMonad (WriterT w m) where type PrimState (WriterT w m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} #if MIN_VERSION_transformers(0,5,6) instance (Monoid w, PrimMonad m) => PrimMonad (CPS.WriterT w m) where type PrimState (CPS.WriterT w m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} #endif instance (Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) where type PrimState (RWST r w s m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} #if MIN_VERSION_transformers(0,5,6) instance (Monoid w, PrimMonad m) => PrimMonad (CPS.RWST r w s m) where type PrimState (CPS.RWST r w s m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} #endif instance PrimMonad m => PrimMonad (ExceptT e m) where type PrimState (ExceptT e m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} #if MIN_VERSION_transformers(0,5,3) -- | @since 0.6.3.0 instance ( Monoid w , PrimMonad m ) => PrimMonad (AccumT w m) where type PrimState (AccumT w m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} instance PrimMonad m => PrimMonad (SelectT r m) where type PrimState (SelectT r m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} #endif instance PrimMonad m => PrimMonad (Strict.StateT s m) where type PrimState (Strict.StateT s m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} instance (Monoid w, PrimMonad m) => PrimMonad (Strict.WriterT w m) where type PrimState (Strict.WriterT w m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} instance (Monoid w, PrimMonad m) => PrimMonad (Strict.RWST r w s m) where type PrimState (Strict.RWST r w s m) = PrimState m primitive = lift . primitive {-# INLINE primitive #-} instance PrimMonad (ST s) where type PrimState (ST s) = s primitive = ST {-# INLINE primitive #-} instance PrimBase (ST s) where internal (ST p) = p {-# INLINE internal #-} -- see https://gitlab.haskell.org/ghc/ghc/commit/2f5cb3d44d05e581b75a47fec222577dfa7a533e -- for why we only support an instance for ghc >= 8.2 #if __GLASGOW_HASKELL__ >= 802 -- @since 0.7.1.0 instance PrimMonad (L.ST s) where type PrimState (L.ST s) = s primitive = L.strictToLazyST . primitive {-# INLINE primitive #-} -- @since 0.7.1.0 instance PrimBase (L.ST s) where internal = internal . L.lazyToStrictST {-# INLINE internal #-} #endif -- | 'PrimMonad''s state token type can be annoying to handle -- in constraints. This typeclass lets users (visually) notice -- 'PrimState' equality constraints less, by witnessing that -- @s ~ 'PrimState' m@. class (PrimMonad m, s ~ PrimState m) => MonadPrim s m instance (PrimMonad m, s ~ PrimState m) => MonadPrim s m -- | 'PrimBase''s state token type can be annoying to handle -- in constraints. This typeclass lets users (visually) notice -- 'PrimState' equality constraints less, by witnessing that -- @s ~ 'PrimState' m@. class (PrimBase m, MonadPrim s m) => MonadPrimBase s m instance (PrimBase m, MonadPrim s m) => MonadPrimBase s m -- | Lifts a 'PrimBase' into another 'PrimMonad' with the same underlying state -- token type. liftPrim :: (PrimBase m1, PrimMonad m2, PrimState m1 ~ PrimState m2) => m1 a -> m2 a {-# INLINE liftPrim #-} liftPrim = primToPrim -- | Convert a 'PrimBase' to another monad with the same state token. primToPrim :: (PrimBase m1, PrimMonad m2, PrimState m1 ~ PrimState m2) => m1 a -> m2 a {-# INLINE primToPrim #-} primToPrim m = primitive (internal m) -- | Convert a 'PrimBase' with a 'RealWorld' state token to 'IO' primToIO :: (PrimBase m, PrimState m ~ RealWorld) => m a -> IO a {-# INLINE primToIO #-} primToIO = primToPrim -- | Convert a 'PrimBase' to 'ST' primToST :: PrimBase m => m a -> ST (PrimState m) a {-# INLINE primToST #-} primToST = primToPrim -- | Convert an 'IO' action to a 'PrimMonad'. -- -- @since 0.6.2.0 ioToPrim :: (PrimMonad m, PrimState m ~ RealWorld) => IO a -> m a {-# INLINE ioToPrim #-} ioToPrim = primToPrim -- | Convert an 'ST' action to a 'PrimMonad'. -- -- @since 0.6.2.0 stToPrim :: PrimMonad m => ST (PrimState m) a -> m a {-# INLINE stToPrim #-} stToPrim = primToPrim -- | Convert a 'PrimBase' to another monad with a possibly different state -- token. This operation is highly unsafe! unsafePrimToPrim :: (PrimBase m1, PrimMonad m2) => m1 a -> m2 a {-# INLINE unsafePrimToPrim #-} unsafePrimToPrim m = primitive (unsafeCoerce# (internal m)) -- | Convert any 'PrimBase' to 'ST' with an arbitrary state token. This -- operation is highly unsafe! unsafePrimToST :: PrimBase m => m a -> ST s a {-# INLINE unsafePrimToST #-} unsafePrimToST = unsafePrimToPrim -- | Convert any 'PrimBase' to 'IO'. This operation is highly unsafe! unsafePrimToIO :: PrimBase m => m a -> IO a {-# INLINE unsafePrimToIO #-} unsafePrimToIO = unsafePrimToPrim -- | Convert an 'ST' action with an arbitrary state token to any 'PrimMonad'. -- This operation is highly unsafe! -- -- @since 0.6.2.0 unsafeSTToPrim :: PrimMonad m => ST s a -> m a {-# INLINE unsafeSTToPrim #-} unsafeSTToPrim = unsafePrimToPrim -- | Convert an 'IO' action to any 'PrimMonad'. This operation is highly -- unsafe! -- -- @since 0.6.2.0 unsafeIOToPrim :: PrimMonad m => IO a -> m a {-# INLINE unsafeIOToPrim #-} unsafeIOToPrim = unsafePrimToPrim -- | See 'unsafeInlineIO'. This function is not recommended for the same -- reasons. unsafeInlinePrim :: PrimBase m => m a -> a {-# INLINE unsafeInlinePrim #-} unsafeInlinePrim m = unsafeInlineIO (unsafePrimToIO m) -- | Generally, do not use this function. It is the same as -- @accursedUnutterablePerformIO@ from @bytestring@ and is well behaved under -- narrow conditions. See the documentation of that function to get an idea -- of when this is sound. In most cases @GHC.IO.Unsafe.unsafeDupablePerformIO@ -- should be preferred. unsafeInlineIO :: IO a -> a {-# INLINE unsafeInlineIO #-} unsafeInlineIO m = case internal m realWorld# of (# _, r #) -> r -- | See 'unsafeInlineIO'. This function is not recommended for the same -- reasons. Prefer @runST@ when @s@ is free. unsafeInlineST :: ST s a -> a {-# INLINE unsafeInlineST #-} unsafeInlineST = unsafeInlinePrim touch :: PrimMonad m => a -> m () {-# INLINE touch #-} touch x = unsafePrimToPrim $ (primitive (\s -> case touch# x s of { s' -> (# s', () #) }) :: IO ()) keepAlive :: PrimBase m => a -> (a -> m r) -> m r #if defined(HAVE_KEEPALIVE) {-# INLINE keepAlive #-} keepAlive x k = unsafeIOToPrim $ primitive $ \s0 -> keepAlive# x s0 $ internal $ unsafePrimToIO $ k x #else {-# NOINLINE keepAlive #-} keepAlive x k = k x <* touch x #endif -- | Create an action to force a value; generalizes 'Control.Exception.evaluate' -- -- @since 0.6.2.0 evalPrim :: forall a m . PrimMonad m => a -> m a evalPrim a = primitive (\s -> seq# a s) noDuplicate :: PrimMonad m => m () #if __GLASGOW_HASKELL__ >= 802 noDuplicate = primitive $ \ s -> (# noDuplicate# s, () #) #else -- noDuplicate# was limited to RealWorld noDuplicate = unsafeIOToPrim $ primitive $ \s -> (# noDuplicate# s, () #) #endif unsafeInterleave, unsafeDupableInterleave :: PrimBase m => m a -> m a unsafeInterleave x = unsafeDupableInterleave (noDuplicate >> x) unsafeDupableInterleave x = primitive $ \ s -> let r' = case internal x s of (# _, r #) -> r in (# s, r' #) {-# INLINE unsafeInterleave #-} {-# NOINLINE unsafeDupableInterleave #-} -- See Note [unsafeDupableInterleaveIO should not be inlined] -- in GHC.IO.Unsafe primitive-0.8.0.0/Data/0000755000000000000000000000000007346545000012727 5ustar0000000000000000primitive-0.8.0.0/Data/Primitive.hs0000644000000000000000000000730507346545000015240 0ustar0000000000000000{-# LANGUAGE MagicHash #-} {-# OPTIONS_GHC -fno-warn-duplicate-exports #-} -- | -- Module : Data.Primitive -- Copyright : (c) Roman Leshchinskiy 2009-2012 -- License : BSD-style -- -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- -- Reexports all primitive operations. module Data.Primitive ( -- * Re-exports module Data.Primitive.Types , module Data.Primitive.Array , module Data.Primitive.ByteArray , module Data.Primitive.SmallArray , module Data.Primitive.PrimArray , module Data.Primitive.MutVar -- * Naming Conventions -- $namingConventions ) where import Data.Primitive.Types import Data.Primitive.Array import Data.Primitive.ByteArray import Data.Primitive.SmallArray import Data.Primitive.PrimArray import Data.Primitive.MutVar {- $namingConventions For historical reasons, this library embraces the practice of suffixing the name of a function with the type it operates on. For example, three of the variants of the array indexing function are: > indexArray :: Array a -> Int -> a > indexSmallArray :: SmallArray a -> Int -> a > indexPrimArray :: Prim a => PrimArray a -> Int -> a In a few places, where the language sounds more natural, the array type is instead used as a prefix. For example, "Data.Primitive.SmallArray" exports 'smallArrayFromList', which would sound unnatural if it used @SmallArray@ as a suffix instead. This library provides several functions for traversing, building, and filtering arrays. These functions are suffixed with an additional character to indicate the nature of their effectfulness: * No suffix: A non-effectful pass over the array. * @A@ suffix: An effectful pass over the array, where the effect is 'Applicative'. * @P@ suffix: An effectful pass over the array, where the effect is 'Control.Monad.Primitive.PrimMonad'. Additionally, an apostrophe can be used to indicate strictness in the elements. The variants with an apostrophe are used in "Data.Primitive.Array" but not in "Data.Primitive.PrimArray" since the array type it provides is always strict in the element anyway. For example, there are three variants of the function that filters elements from a primitive array. > filterPrimArray :: (Prim a ) => (a -> Bool) -> PrimArray a -> PrimArray a > filterPrimArrayA :: (Prim a, Applicative f) => (a -> f Bool) -> PrimArray a -> f (PrimArray a) > filterPrimArrayP :: (Prim a, PrimMonad m) => (a -> m Bool) -> PrimArray a -> m (PrimArray a) As long as the effectful context is a monad that is sufficiently affine, the behaviors of the 'Applicative' and 'Control.Monad.Primitive.PrimMonad' variants produce the same results and differ only in their strictness. Monads that are sufficiently affine include: * 'IO' and 'ST' * Any combination of 'MaybeT', 'ExceptT', 'StateT' and 'Writer' on top of another sufficiently affine monad. * Any Monad which does not include backtracking or other mechanisms where an effect can happen more than once is an affine Monad in the sense we care about. @ContT@, @LogicT@, @ListT@ are all examples of search/control monads which are NOT affine: they can run a sub computation more than once. There is one situation where the names deviate from effectful suffix convention described above. Throughout the haskell ecosystem, the 'Applicative' variant of 'map' is known as 'traverse', not @mapA@. Consequently, we adopt the following naming convention for mapping: > mapPrimArray :: (Prim a, Prim b) => (a -> b) -> PrimArray a -> PrimArray b > traversePrimArray :: (Applicative f, Prim a, Prim b) => (a -> f b) -> PrimArray a -> f (PrimArray b) > traversePrimArrayP :: (PrimMonad m, Prim a, Prim b) => (a -> m b) -> PrimArray a -> m (PrimArray b) -} primitive-0.8.0.0/Data/Primitive/0000755000000000000000000000000007346545000014677 5ustar0000000000000000primitive-0.8.0.0/Data/Primitive/Array.hs0000644000000000000000000007114107346545000016315 0ustar0000000000000000{-# LANGUAGE CPP, MagicHash, UnboxedTuples, DeriveDataTypeable, BangPatterns #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TemplateHaskellQuotes #-} -- | -- Module : Data.Primitive.Array -- Copyright : (c) Roman Leshchinskiy 2009-2012 -- License : BSD-style -- -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- -- Primitive arrays of boxed values. module Data.Primitive.Array ( Array(..), MutableArray(..), newArray, readArray, writeArray, indexArray, indexArrayM, indexArray##, freezeArray, thawArray, runArray, createArray, unsafeFreezeArray, unsafeThawArray, sameMutableArray, copyArray, copyMutableArray, cloneArray, cloneMutableArray, sizeofArray, sizeofMutableArray, emptyArray, fromListN, fromList, arrayFromListN, arrayFromList, mapArray', traverseArrayP ) where import Control.DeepSeq import Control.Monad.Primitive import GHC.Exts hiding (toList) import qualified GHC.Exts as Exts import Data.Typeable ( Typeable ) import Data.Data (Data(..), DataType, mkDataType, mkNoRepType, Constr, mkConstr, Fixity(..), constrIndex) import Control.Monad.ST (ST, runST) import Control.Applicative import Control.Monad (MonadPlus(..), when, liftM2) import qualified Control.Monad.Fail as Fail import Control.Monad.Fix import qualified Data.Foldable as Foldable import Control.Monad.Zip import Data.Foldable (Foldable(..), toList) import qualified GHC.ST as GHCST import qualified Data.Foldable as F import Data.Semigroup import Data.Functor.Identity #if !MIN_VERSION_base(4,10,0) import GHC.Base (runRW#) #endif import Text.Read (Read (..), parens, prec) import Text.ParserCombinators.ReadPrec (ReadPrec) import qualified Text.ParserCombinators.ReadPrec as RdPrc import Text.ParserCombinators.ReadP import Data.Functor.Classes (Eq1(..), Ord1(..), Show1(..), Read1(..)) import Language.Haskell.TH.Syntax (Lift (..)) -- | Boxed arrays. data Array a = Array { array# :: Array# a } deriving ( Typeable ) instance Lift a => Lift (Array a) where #if MIN_VERSION_template_haskell(2,16,0) liftTyped ary = case lst of [] -> [|| Array (emptyArray# (##)) ||] [x] -> [|| pure $! x ||] x : xs -> [|| unsafeArrayFromListN' len x xs ||] #else lift ary = case lst of [] -> [| Array (emptyArray# (##)) |] [x] -> [| pure $! x |] x : xs -> [| unsafeArrayFromListN' len x xs |] #endif where len = length ary lst = toList ary -- | Strictly create an array from a nonempty list (represented as -- a first element and a list of the rest) of a known length. If the length -- of the list does not match the given length, this makes demons fly -- out of your nose. We use it in the 'Lift' instance. If you edit the -- splice and break it, you get to keep both pieces. unsafeArrayFromListN' :: Int -> a -> [a] -> Array a unsafeArrayFromListN' n y ys = createArray n y $ \ma -> let go !_ix [] = return () go !ix (!x : xs) = do writeArray ma ix x go (ix+1) xs in go 1 ys #if MIN_VERSION_deepseq(1,4,3) instance NFData1 Array where liftRnf r = Foldable.foldl' (\_ -> r) () #endif instance NFData a => NFData (Array a) where rnf = Foldable.foldl' (\_ -> rnf) () -- | Mutable boxed arrays associated with a primitive state token. data MutableArray s a = MutableArray { marray# :: MutableArray# s a } deriving ( Typeable ) -- | The number of elements in an immutable array. sizeofArray :: Array a -> Int sizeofArray a = I# (sizeofArray# (array# a)) {-# INLINE sizeofArray #-} -- | The number of elements in a mutable array. sizeofMutableArray :: MutableArray s a -> Int sizeofMutableArray a = I# (sizeofMutableArray# (marray# a)) {-# INLINE sizeofMutableArray #-} -- | Create a new mutable array of the specified size and initialise all -- elements with the given value. -- -- /Note:/ this function does not check if the input is non-negative. newArray :: PrimMonad m => Int -> a -> m (MutableArray (PrimState m) a) {-# INLINE newArray #-} newArray (I# n#) x = primitive (\s# -> case newArray# n# x s# of (# s'#, arr# #) -> let ma = MutableArray arr# in (# s'# , ma #)) -- | Read a value from the array at the given index. -- -- /Note:/ this function does not do bounds checking. readArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> m a {-# INLINE readArray #-} readArray arr (I# i#) = primitive (readArray# (marray# arr) i#) -- | Write a value to the array at the given index. -- -- /Note:/ this function does not do bounds checking. writeArray :: PrimMonad m => MutableArray (PrimState m) a -> Int -> a -> m () {-# INLINE writeArray #-} writeArray arr (I# i#) x = primitive_ (writeArray# (marray# arr) i# x) -- | Read a value from the immutable array at the given index. -- -- /Note:/ this function does not do bounds checking. indexArray :: Array a -> Int -> a {-# INLINE indexArray #-} indexArray arr (I# i#) = case indexArray# (array# arr) i# of (# x #) -> x -- | Read a value from the immutable array at the given index, returning -- the result in an unboxed unary tuple. This is currently used to implement -- folds. -- -- /Note:/ this function does not do bounds checking. indexArray## :: Array a -> Int -> (# a #) indexArray## arr (I# i) = indexArray# (array# arr) i {-# INLINE indexArray## #-} -- | Monadically read a value from the immutable array at the given index. -- This allows us to be strict in the array while remaining lazy in the read -- element which is very useful for collective operations. Suppose we want to -- copy an array. We could do something like this: -- -- > copy marr arr ... = do ... -- > writeArray marr i (indexArray arr i) ... -- > ... -- -- But since the arrays are lazy, the calls to 'indexArray' will not be -- evaluated. Rather, @marr@ will be filled with thunks each of which would -- retain a reference to @arr@. This is definitely not what we want! -- -- With 'indexArrayM', we can instead write -- -- > copy marr arr ... = do ... -- > x <- indexArrayM arr i -- > writeArray marr i x -- > ... -- -- Now, indexing is executed immediately although the returned element is -- still not evaluated. -- -- /Note:/ this function does not do bounds checking. indexArrayM :: Monad m => Array a -> Int -> m a {-# INLINE indexArrayM #-} indexArrayM arr (I# i#) = case indexArray# (array# arr) i# of (# x #) -> return x -- | Create an immutable copy of a slice of an array. -- -- This operation makes a copy of the specified section, so it is safe to -- continue using the mutable array afterward. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. freezeArray :: PrimMonad m => MutableArray (PrimState m) a -- ^ source -> Int -- ^ offset -> Int -- ^ length -> m (Array a) {-# INLINE freezeArray #-} freezeArray (MutableArray ma#) (I# off#) (I# len#) = primitive $ \s -> case freezeArray# ma# off# len# s of (# s', a# #) -> (# s', Array a# #) -- | Convert a mutable array to an immutable one without copying. The -- array should not be modified after the conversion. unsafeFreezeArray :: PrimMonad m => MutableArray (PrimState m) a -> m (Array a) {-# INLINE unsafeFreezeArray #-} unsafeFreezeArray arr = primitive (\s# -> case unsafeFreezeArray# (marray# arr) s# of (# s'#, arr'# #) -> let a = Array arr'# in (# s'#, a #)) -- | Create a mutable array from a slice of an immutable array. -- -- This operation makes a copy of the specified slice, so it is safe to use the -- immutable array afterward. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. thawArray :: PrimMonad m => Array a -- ^ source -> Int -- ^ offset -> Int -- ^ length -> m (MutableArray (PrimState m) a) {-# INLINE thawArray #-} thawArray (Array a#) (I# off#) (I# len#) = primitive $ \s -> case thawArray# a# off# len# s of (# s', ma# #) -> (# s', MutableArray ma# #) -- | Convert an immutable array to an mutable one without copying. The -- immutable array should not be used after the conversion. unsafeThawArray :: PrimMonad m => Array a -> m (MutableArray (PrimState m) a) {-# INLINE unsafeThawArray #-} unsafeThawArray a = primitive (\s# -> case unsafeThawArray# (array# a) s# of (# s'#, arr'# #) -> let ma = MutableArray arr'# in (# s'#, ma #)) -- | Check whether the two arrays refer to the same memory block. sameMutableArray :: MutableArray s a -> MutableArray s a -> Bool {-# INLINE sameMutableArray #-} sameMutableArray arr brr = isTrue# (sameMutableArray# (marray# arr) (marray# brr)) -- | Copy a slice of an immutable array to a mutable array. -- -- /Note:/ this function does not do bounds or overlap checking. copyArray :: PrimMonad m => MutableArray (PrimState m) a -- ^ destination array -> Int -- ^ offset into destination array -> Array a -- ^ source array -> Int -- ^ offset into source array -> Int -- ^ number of elements to copy -> m () {-# INLINE copyArray #-} copyArray (MutableArray dst#) (I# doff#) (Array src#) (I# soff#) (I# len#) = primitive_ (copyArray# src# soff# dst# doff# len#) -- | Copy a slice of a mutable array to another array. The two arrays may overlap. -- -- /Note:/ this function does not do bounds or overlap checking. copyMutableArray :: PrimMonad m => MutableArray (PrimState m) a -- ^ destination array -> Int -- ^ offset into destination array -> MutableArray (PrimState m) a -- ^ source array -> Int -- ^ offset into source array -> Int -- ^ number of elements to copy -> m () {-# INLINE copyMutableArray #-} copyMutableArray (MutableArray dst#) (I# doff#) (MutableArray src#) (I# soff#) (I# len#) = primitive_ (copyMutableArray# src# soff# dst# doff# len#) -- | Return a newly allocated 'Array' with the specified subrange of the -- provided 'Array'. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. cloneArray :: Array a -- ^ source array -> Int -- ^ offset into destination array -> Int -- ^ number of elements to copy -> Array a {-# INLINE cloneArray #-} cloneArray (Array arr#) (I# off#) (I# len#) = case cloneArray# arr# off# len# of arr'# -> Array arr'# -- | Return a newly allocated 'MutableArray'. with the specified subrange of -- the provided 'MutableArray'. The provided 'MutableArray' should contain the -- full subrange specified by the two Ints, but this is not checked. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. cloneMutableArray :: PrimMonad m => MutableArray (PrimState m) a -- ^ source array -> Int -- ^ offset into destination array -> Int -- ^ number of elements to copy -> m (MutableArray (PrimState m) a) {-# INLINE cloneMutableArray #-} cloneMutableArray (MutableArray arr#) (I# off#) (I# len#) = primitive (\s# -> case cloneMutableArray# arr# off# len# s# of (# s'#, arr'# #) -> (# s'#, MutableArray arr'# #)) -- | The empty 'Array'. emptyArray :: Array a emptyArray = runST $ newArray 0 (die "emptyArray" "impossible") >>= unsafeFreezeArray {-# NOINLINE emptyArray #-} -- | Execute the monadic action and freeze the resulting array. -- -- > runArray m = runST $ m >>= unsafeFreezeArray runArray :: (forall s. ST s (MutableArray s a)) -> Array a runArray m = Array (runArray# m) runArray# :: (forall s. ST s (MutableArray s a)) -> Array# a runArray# m = case runRW# $ \s -> case unST m s of { (# s', MutableArray mary# #) -> unsafeFreezeArray# mary# s'} of (# _, ary# #) -> ary# unST :: ST s a -> State# s -> (# State# s, a #) unST (GHCST.ST f) = f emptyArray# :: (# #) -> Array# a emptyArray# _ = case emptyArray of Array ar -> ar {-# NOINLINE emptyArray# #-} -- | Create an array of the given size with a default value, -- apply the monadic function and freeze the result. If the -- size is 0, return 'emptyArray' (rather than a new copy thereof). -- -- > createArray 0 _ _ = emptyArray -- > createArray n x f = runArray $ do -- > mary <- newArray n x -- > f mary -- > pure mary createArray :: Int -> a -> (forall s. MutableArray s a -> ST s ()) -> Array a -- This low-level business is designed to work with GHC's worker-wrapper -- transformation. A lot of the time, we don't actually need an Array -- constructor. By putting it on the outside, and being careful about -- how we special-case the empty array, we can make GHC smarter about this. -- The only downside is that separately created 0-length arrays won't share -- their Array constructors, although they'll share their underlying -- Array#s. createArray 0 _ _ = Array (emptyArray# (# #)) createArray n x f = runArray $ do mary <- newArray n x f mary pure mary die :: String -> String -> a die fun problem = error $ "Data.Primitive.Array." ++ fun ++ ": " ++ problem arrayLiftEq :: (a -> b -> Bool) -> Array a -> Array b -> Bool arrayLiftEq p a1 a2 = sizeofArray a1 == sizeofArray a2 && loop (sizeofArray a1 - 1) where loop i | i < 0 = True | (# x1 #) <- indexArray## a1 i , (# x2 #) <- indexArray## a2 i , otherwise = p x1 x2 && loop (i - 1) instance Eq a => Eq (Array a) where a1 == a2 = arrayLiftEq (==) a1 a2 -- | @since 0.6.4.0 instance Eq1 Array where liftEq = arrayLiftEq instance Eq (MutableArray s a) where ma1 == ma2 = isTrue# (sameMutableArray# (marray# ma1) (marray# ma2)) arrayLiftCompare :: (a -> b -> Ordering) -> Array a -> Array b -> Ordering arrayLiftCompare elemCompare a1 a2 = loop 0 where mn = sizeofArray a1 `min` sizeofArray a2 loop i | i < mn , (# x1 #) <- indexArray## a1 i , (# x2 #) <- indexArray## a2 i = elemCompare x1 x2 `mappend` loop (i + 1) | otherwise = compare (sizeofArray a1) (sizeofArray a2) -- | Lexicographic ordering. Subject to change between major versions. instance Ord a => Ord (Array a) where compare a1 a2 = arrayLiftCompare compare a1 a2 -- | @since 0.6.4.0 instance Ord1 Array where liftCompare = arrayLiftCompare instance Foldable Array where -- Note: we perform the array lookups eagerly so we won't -- create thunks to perform lookups even if GHC can't see -- that the folding function is strict. foldr f = \z !ary -> let !sz = sizeofArray ary go i | i == sz = z | (# x #) <- indexArray## ary i = f x (go (i + 1)) in go 0 {-# INLINE foldr #-} foldl f = \z !ary -> let go i | i < 0 = z | (# x #) <- indexArray## ary i = f (go (i - 1)) x in go (sizeofArray ary - 1) {-# INLINE foldl #-} foldr1 f = \ !ary -> let !sz = sizeofArray ary - 1 go i = case indexArray## ary i of (# x #) | i == sz -> x | otherwise -> f x (go (i + 1)) in if sz < 0 then die "foldr1" "empty array" else go 0 {-# INLINE foldr1 #-} foldl1 f = \ !ary -> let !sz = sizeofArray ary - 1 go i = case indexArray## ary i of (# x #) | i == 0 -> x | otherwise -> f (go (i - 1)) x in if sz < 0 then die "foldl1" "empty array" else go sz {-# INLINE foldl1 #-} foldr' f = \z !ary -> let go i !acc | i == -1 = acc | (# x #) <- indexArray## ary i = go (i - 1) (f x acc) in go (sizeofArray ary - 1) z {-# INLINE foldr' #-} foldl' f = \z !ary -> let !sz = sizeofArray ary go i !acc | i == sz = acc | (# x #) <- indexArray## ary i = go (i + 1) (f acc x) in go 0 z {-# INLINE foldl' #-} null a = sizeofArray a == 0 {-# INLINE null #-} length = sizeofArray {-# INLINE length #-} maximum ary | sz == 0 = die "maximum" "empty array" | (# frst #) <- indexArray## ary 0 = go 1 frst where sz = sizeofArray ary go i !e | i == sz = e | (# x #) <- indexArray## ary i = go (i + 1) (max e x) {-# INLINE maximum #-} minimum ary | sz == 0 = die "minimum" "empty array" | (# frst #) <- indexArray## ary 0 = go 1 frst where sz = sizeofArray ary go i !e | i == sz = e | (# x #) <- indexArray## ary i = go (i + 1) (min e x) {-# INLINE minimum #-} sum = foldl' (+) 0 {-# INLINE sum #-} product = foldl' (*) 1 {-# INLINE product #-} newtype STA a = STA { _runSTA :: forall s. MutableArray# s a -> ST s (Array a) } runSTA :: Int -> STA a -> Array a runSTA !sz = \ (STA m) -> runST $ newArray_ sz >>= \ ar -> m (marray# ar) {-# INLINE runSTA #-} newArray_ :: Int -> ST s (MutableArray s a) newArray_ !n = newArray n badTraverseValue badTraverseValue :: a badTraverseValue = die "traverse" "bad indexing" {-# NOINLINE badTraverseValue #-} instance Traversable Array where traverse f = traverseArray f {-# INLINE traverse #-} traverseArray :: Applicative f => (a -> f b) -> Array a -> f (Array b) traverseArray f = \ !ary -> let !len = sizeofArray ary go !i | i == len = pure $ STA $ \mary -> unsafeFreezeArray (MutableArray mary) | (# x #) <- indexArray## ary i = liftA2 (\b (STA m) -> STA $ \mary -> writeArray (MutableArray mary) i b >> m mary) (f x) (go (i + 1)) in if len == 0 then pure emptyArray else runSTA len <$> go 0 {-# INLINE [1] traverseArray #-} {-# RULES "traverse/ST" forall (f :: a -> ST s b). traverseArray f = traverseArrayP f "traverse/IO" forall (f :: a -> IO b). traverseArray f = traverseArrayP f "traverse/Id" forall (f :: a -> Identity b). traverseArray f = (coerce :: (Array a -> Array (Identity b)) -> Array a -> Identity (Array b)) (fmap f) #-} -- | This is the fastest, most straightforward way to traverse -- an array, but it only works correctly with a sufficiently -- "affine" 'PrimMonad' instance. In particular, it must only produce -- /one/ result array. 'Control.Monad.Trans.List.ListT'-transformed -- monads, for example, will not work right at all. traverseArrayP :: PrimMonad m => (a -> m b) -> Array a -> m (Array b) traverseArrayP f = \ !ary -> let !sz = sizeofArray ary go !i !mary | i == sz = unsafeFreezeArray mary | otherwise = do a <- indexArrayM ary i b <- f a writeArray mary i b go (i + 1) mary in do mary <- newArray sz badTraverseValue go 0 mary {-# INLINE traverseArrayP #-} -- | Strict map over the elements of the array. mapArray' :: (a -> b) -> Array a -> Array b mapArray' f a = createArray (sizeofArray a) (die "mapArray'" "impossible") $ \mb -> let go i | i == sizeofArray a = return () | otherwise = do x <- indexArrayM a i -- We use indexArrayM here so that we will perform the -- indexing eagerly even if f is lazy. let !y = f x writeArray mb i y >> go (i + 1) in go 0 {-# INLINE mapArray' #-} -- | Create an array from a list of a known length. If the length -- of the list does not match the given length, this throws an exception. arrayFromListN :: Int -> [a] -> Array a arrayFromListN n l = createArray n (die "fromListN" "uninitialized element") $ \sma -> let go !ix [] = if ix == n then return () else die "fromListN" "list length less than specified size" go !ix (x : xs) = if ix < n then do writeArray sma ix x go (ix+1) xs else die "fromListN" "list length greater than specified size" in go 0 l -- | Create an array from a list. arrayFromList :: [a] -> Array a arrayFromList l = arrayFromListN (length l) l instance Exts.IsList (Array a) where type Item (Array a) = a fromListN = arrayFromListN fromList = arrayFromList toList = toList instance Functor Array where fmap f a = createArray (sizeofArray a) (die "fmap" "impossible") $ \mb -> let go i | i == sizeofArray a = return () | otherwise = do x <- indexArrayM a i writeArray mb i (f x) >> go (i + 1) in go 0 e <$ a = createArray (sizeofArray a) e (\ !_ -> pure ()) instance Applicative Array where pure x = runArray $ newArray 1 x ab <*> a = createArray (szab * sza) (die "<*>" "impossible") $ \mb -> let go1 i = when (i < szab) $ do f <- indexArrayM ab i go2 (i * sza) f 0 go1 (i + 1) go2 off f j = when (j < sza) $ do x <- indexArrayM a j writeArray mb (off + j) (f x) go2 off f (j + 1) in go1 0 where szab = sizeofArray ab; sza = sizeofArray a a *> b = createArray (sza * szb) (die "*>" "impossible") $ \mb -> let go i | i < sza = copyArray mb (i * szb) b 0 szb *> go (i + 1) | otherwise = return () in go 0 where sza = sizeofArray a; szb = sizeofArray b a <* b = createArray (sza * szb) (die "<*" "impossible") $ \ma -> let fill off i e | i < szb = writeArray ma (off + i) e >> fill off (i + 1) e | otherwise = return () go i | i < sza = do x <- indexArrayM a i fill (i * szb) 0 x >> go (i + 1) | otherwise = return () in go 0 where sza = sizeofArray a; szb = sizeofArray b instance Alternative Array where empty = emptyArray a1 <|> a2 = createArray (sza1 + sza2) (die "<|>" "impossible") $ \ma -> copyArray ma 0 a1 0 sza1 >> copyArray ma sza1 a2 0 sza2 where sza1 = sizeofArray a1; sza2 = sizeofArray a2 some a | sizeofArray a == 0 = emptyArray | otherwise = die "some" "infinite arrays are not well defined" many a | sizeofArray a == 0 = pure [] | otherwise = die "many" "infinite arrays are not well defined" data ArrayStack a = PushArray !(Array a) !(ArrayStack a) | EmptyStack -- See the note in SmallArray about how we might improve this. instance Monad Array where return = pure (>>) = (*>) ary >>= f = collect 0 EmptyStack (la - 1) where la = sizeofArray ary collect sz stk i | i < 0 = createArray sz (die ">>=" "impossible") $ fill 0 stk | (# x #) <- indexArray## ary i , let sb = f x lsb = sizeofArray sb -- If we don't perform this check, we could end up allocating -- a stack full of empty arrays if someone is filtering most -- things out. So we refrain from pushing empty arrays. = if lsb == 0 then collect sz stk (i - 1) else collect (sz + lsb) (PushArray sb stk) (i - 1) fill _ EmptyStack _ = return () fill off (PushArray sb sbs) smb | let lsb = sizeofArray sb = copyArray smb off sb 0 lsb *> fill (off + lsb) sbs smb #if !(MIN_VERSION_base(4,13,0)) fail = Fail.fail #endif instance Fail.MonadFail Array where fail _ = empty instance MonadPlus Array where mzero = empty mplus = (<|>) zipW :: String -> (a -> b -> c) -> Array a -> Array b -> Array c zipW s f aa ab = createArray mn (die s "impossible") $ \mc -> let go i | i < mn = do x <- indexArrayM aa i y <- indexArrayM ab i writeArray mc i (f x y) go (i + 1) | otherwise = return () in go 0 where mn = sizeofArray aa `min` sizeofArray ab {-# INLINE zipW #-} instance MonadZip Array where mzip aa ab = zipW "mzip" (,) aa ab mzipWith f aa ab = zipW "mzipWith" f aa ab munzip aab = runST $ do let sz = sizeofArray aab ma <- newArray sz (die "munzip" "impossible") mb <- newArray sz (die "munzip" "impossible") let go i | i < sz = do (a, b) <- indexArrayM aab i writeArray ma i a writeArray mb i b go (i + 1) go _ = return () go 0 (,) <$> unsafeFreezeArray ma <*> unsafeFreezeArray mb instance MonadFix Array where mfix f = createArray (sizeofArray (f err)) (die "mfix" "impossible") $ flip fix 0 $ \r !i !mary -> when (i < sz) $ do writeArray mary i (fix (\xi -> f xi `indexArray` i)) r (i + 1) mary where sz = sizeofArray (f err) err = error "mfix for Data.Primitive.Array applied to strict function." -- | @since 0.6.3.0 instance Semigroup (Array a) where (<>) = (<|>) sconcat = mconcat . F.toList stimes n arr = case compare n 0 of LT -> die "stimes" "negative multiplier" EQ -> empty GT -> createArray (n' * sizeofArray arr) (die "stimes" "impossible") $ \ma -> let go i = if i < n' then do copyArray ma (i * sizeofArray arr) arr 0 (sizeofArray arr) go (i + 1) else return () in go 0 where n' = fromIntegral n :: Int instance Monoid (Array a) where mempty = empty #if !(MIN_VERSION_base(4,11,0)) mappend = (<>) #endif mconcat l = createArray sz (die "mconcat" "impossible") $ \ma -> let go !_ [ ] = return () go off (a:as) = copyArray ma off a 0 (sizeofArray a) >> go (off + sizeofArray a) as in go 0 l where sz = sum . fmap sizeofArray $ l arrayLiftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Array a -> ShowS arrayLiftShowsPrec elemShowsPrec elemListShowsPrec p a = showParen (p > 10) $ showString "fromListN " . shows (sizeofArray a) . showString " " . listLiftShowsPrec elemShowsPrec elemListShowsPrec 11 (toList a) -- this need to be included for older ghcs listLiftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> [a] -> ShowS listLiftShowsPrec _ sl _ = sl instance Show a => Show (Array a) where showsPrec p a = arrayLiftShowsPrec showsPrec showList p a -- | @since 0.6.4.0 instance Show1 Array where liftShowsPrec = arrayLiftShowsPrec instance Read a => Read (Array a) where readPrec = arrayLiftReadPrec readPrec readListPrec -- | @since 0.6.4.0 instance Read1 Array where #if MIN_VERSION_base(4,10,0) liftReadPrec = arrayLiftReadPrec #else liftReadsPrec = arrayLiftReadsPrec #endif -- We're really forgiving here. We accept -- "[1,2,3]", "fromList [1,2,3]", and "fromListN 3 [1,2,3]". -- We consider fromListN with an invalid length to be an -- error, rather than a parse failure, because doing otherwise -- seems weird and likely to make debugging difficult. arrayLiftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Array a) arrayLiftReadPrec _ read_list = parens $ prec app_prec $ RdPrc.lift skipSpaces >> ((fromList <$> read_list) RdPrc.+++ do tag <- RdPrc.lift lexTag case tag of FromListTag -> fromList <$> read_list FromListNTag -> liftM2 fromListN readPrec read_list) where app_prec = 10 data Tag = FromListTag | FromListNTag -- Why don't we just use lexP? The general problem with lexP is that -- it doesn't always fail as fast as we might like. It will -- happily read to the end of an absurdly long lexeme (e.g., a 200MB string -- literal) before returning, at which point we'll immediately discard -- the result because it's not an identifier. Doing the job ourselves, we -- can see very quickly when we've run into a problem. We should also get -- a slight efficiency boost by going through the string just once. lexTag :: ReadP Tag lexTag = do _ <- string "fromList" s <- look case s of 'N':c:_ | '0' <= c && c <= '9' -> fail "" -- We have fromListN3 or similar | otherwise -> FromListNTag <$ get -- Skip the 'N' _ -> return FromListTag #if !MIN_VERSION_base(4,10,0) arrayLiftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Array a) arrayLiftReadsPrec reads_prec list_reads_prec = RdPrc.readPrec_to_S $ arrayLiftReadPrec (RdPrc.readS_to_Prec reads_prec) (RdPrc.readS_to_Prec (const list_reads_prec)) #endif arrayDataType :: DataType arrayDataType = mkDataType "Data.Primitive.Array.Array" [fromListConstr] fromListConstr :: Constr fromListConstr = mkConstr arrayDataType "fromList" [] Prefix instance Data a => Data (Array a) where toConstr _ = fromListConstr dataTypeOf _ = arrayDataType gunfold k z c = case constrIndex c of 1 -> k (z fromList) _ -> error "gunfold" gfoldl f z m = z fromList `f` toList m instance (Typeable s, Typeable a) => Data (MutableArray s a) where toConstr _ = error "toConstr" gunfold _ _ = error "gunfold" dataTypeOf _ = mkNoRepType "Data.Primitive.Array.MutableArray" primitive-0.8.0.0/Data/Primitive/ByteArray.hs0000644000000000000000000005763707346545000017157 0ustar0000000000000000{-# LANGUAGE BangPatterns, CPP, MagicHash, UnboxedTuples, UnliftedFFITypes, DeriveDataTypeable #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TemplateHaskellQuotes #-} -- | -- Module : Data.Primitive.ByteArray -- Copyright : (c) Roman Leshchinskiy 2009-2012 -- License : BSD-style -- -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- -- Primitive operations on byte arrays. Most functions in this module include -- an element type in their type signature and interpret the unit for offsets -- and lengths as that element. A few functions (e.g. 'copyByteArray', -- 'freezeByteArray') do not include an element type. Such functions -- interpret offsets and lengths as units of 8-bit words. module Data.Primitive.ByteArray ( -- * Types ByteArray(..), MutableByteArray(..), ByteArray#, MutableByteArray#, -- * Allocation newByteArray, newPinnedByteArray, newAlignedPinnedByteArray, resizeMutableByteArray, shrinkMutableByteArray, -- * Element access readByteArray, writeByteArray, indexByteArray, -- * Char Element Access -- $charElementAccess readCharArray, writeCharArray, indexCharArray, -- * Constructing emptyByteArray, byteArrayFromList, byteArrayFromListN, -- * Folding foldrByteArray, -- * Comparing compareByteArrays, -- * Freezing and thawing freezeByteArray, thawByteArray, runByteArray, unsafeFreezeByteArray, unsafeThawByteArray, -- * Block operations copyByteArray, copyMutableByteArray, copyByteArrayToPtr, copyMutableByteArrayToPtr, copyByteArrayToAddr, copyMutableByteArrayToAddr, copyPtrToMutableByteArray, moveByteArray, setByteArray, fillByteArray, cloneByteArray, cloneMutableByteArray, -- * Information sizeofByteArray, sizeofMutableByteArray, getSizeofMutableByteArray, sameMutableByteArray, #if __GLASGOW_HASKELL__ >= 802 isByteArrayPinned, isMutableByteArrayPinned, #endif byteArrayContents, mutableByteArrayContents ) where import Control.Monad.Primitive import Control.Monad.ST import Data.Primitive.Types #if MIN_VERSION_base(4,10,0) import qualified GHC.ST as GHCST #endif import Foreign.C.Types import Data.Word ( Word8 ) #if __GLASGOW_HASKELL__ >= 802 import qualified GHC.Exts as Exts #endif import GHC.Exts hiding (setByteArray#) #if __GLASGOW_HASKELL__ < 804 import System.IO.Unsafe (unsafeDupablePerformIO) #endif import Data.Array.Byte (ByteArray(..), MutableByteArray(..)) -- | Create a new mutable byte array of the specified size in bytes. -- -- /Note:/ this function does not check if the input is non-negative. newByteArray :: PrimMonad m => Int -> m (MutableByteArray (PrimState m)) {-# INLINE newByteArray #-} newByteArray (I# n#) = primitive (\s# -> case newByteArray# n# s# of (# s'#, arr# #) -> (# s'#, MutableByteArray arr# #)) -- | Create a /pinned/ byte array of the specified size in bytes. The garbage -- collector is guaranteed not to move it. -- -- /Note:/ this function does not check if the input is non-negative. newPinnedByteArray :: PrimMonad m => Int -> m (MutableByteArray (PrimState m)) {-# INLINE newPinnedByteArray #-} newPinnedByteArray (I# n#) = primitive (\s# -> case newPinnedByteArray# n# s# of (# s'#, arr# #) -> (# s'#, MutableByteArray arr# #)) -- | Create a /pinned/ byte array of the specified size in bytes and with the -- given alignment. The garbage collector is guaranteed not to move it. -- -- /Note:/ this function does not check if the input is non-negative. newAlignedPinnedByteArray :: PrimMonad m => Int -- ^ size -> Int -- ^ alignment -> m (MutableByteArray (PrimState m)) {-# INLINE newAlignedPinnedByteArray #-} newAlignedPinnedByteArray (I# n#) (I# k#) = primitive (\s# -> case newAlignedPinnedByteArray# n# k# s# of (# s'#, arr# #) -> (# s'#, MutableByteArray arr# #)) -- | Yield a pointer to the array's data. This operation is only safe on -- /pinned/ byte arrays allocated by 'newPinnedByteArray' or -- 'newAlignedPinnedByteArray'. byteArrayContents :: ByteArray -> Ptr Word8 {-# INLINE byteArrayContents #-} byteArrayContents (ByteArray arr#) = Ptr (byteArrayContents# arr#) -- | Yield a pointer to the array's data. This operation is only safe on -- /pinned/ byte arrays allocated by 'newPinnedByteArray' or -- 'newAlignedPinnedByteArray'. mutableByteArrayContents :: MutableByteArray s -> Ptr Word8 {-# INLINE mutableByteArrayContents #-} mutableByteArrayContents (MutableByteArray arr#) = Ptr (byteArrayContents# (unsafeCoerce# arr#)) -- | Check if the two arrays refer to the same memory block. sameMutableByteArray :: MutableByteArray s -> MutableByteArray s -> Bool {-# INLINE sameMutableByteArray #-} sameMutableByteArray (MutableByteArray arr#) (MutableByteArray brr#) = isTrue# (sameMutableByteArray# arr# brr#) -- | Resize a mutable byte array. The new size is given in bytes. -- -- This will either resize the array in-place or, if not possible, allocate the -- contents into a new, unpinned array and copy the original array's contents. -- -- To avoid undefined behaviour, the original 'MutableByteArray' shall not be -- accessed anymore after a 'resizeMutableByteArray' has been performed. -- Moreover, no reference to the old one should be kept in order to allow -- garbage collection of the original 'MutableByteArray' in case a new -- 'MutableByteArray' had to be allocated. -- -- @since 0.6.4.0 resizeMutableByteArray :: PrimMonad m => MutableByteArray (PrimState m) -> Int -> m (MutableByteArray (PrimState m)) {-# INLINE resizeMutableByteArray #-} resizeMutableByteArray (MutableByteArray arr#) (I# n#) = primitive (\s# -> case resizeMutableByteArray# arr# n# s# of (# s'#, arr'# #) -> (# s'#, MutableByteArray arr'# #)) -- | Get the size of a byte array in bytes. Unlike 'sizeofMutableByteArray', -- this function ensures sequencing in the presence of resizing. getSizeofMutableByteArray :: PrimMonad m => MutableByteArray (PrimState m) -> m Int {-# INLINE getSizeofMutableByteArray #-} #if __GLASGOW_HASKELL__ >= 801 getSizeofMutableByteArray (MutableByteArray arr#) = primitive (\s# -> case getSizeofMutableByteArray# arr# s# of (# s'#, n# #) -> (# s'#, I# n# #)) #else getSizeofMutableByteArray arr = return (sizeofMutableByteArray arr) #endif -- | Create an immutable copy of a slice of a byte array. The offset and -- length are given in bytes. -- -- This operation makes a copy of the specified section, so it is safe to -- continue using the mutable array afterward. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. freezeByteArray :: PrimMonad m => MutableByteArray (PrimState m) -- ^ source -> Int -- ^ offset in bytes -> Int -- ^ length in bytes -> m ByteArray {-# INLINE freezeByteArray #-} freezeByteArray !src !off !len = do dst <- newByteArray len copyMutableByteArray dst 0 src off len unsafeFreezeByteArray dst -- | Create a mutable byte array from a slice of an immutable byte array. -- The offset and length are given in bytes. -- -- This operation makes a copy of the specified slice, so it is safe to -- use the immutable array afterward. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. -- -- @since 0.7.2.0 thawByteArray :: PrimMonad m => ByteArray -- ^ source -> Int -- ^ offset in bytes -> Int -- ^ length in bytes -> m (MutableByteArray (PrimState m)) {-# INLINE thawByteArray #-} thawByteArray !src !off !len = do dst <- newByteArray len copyByteArray dst 0 src off len return dst -- | Convert a mutable byte array to an immutable one without copying. The -- array should not be modified after the conversion. unsafeFreezeByteArray :: PrimMonad m => MutableByteArray (PrimState m) -> m ByteArray {-# INLINE unsafeFreezeByteArray #-} unsafeFreezeByteArray (MutableByteArray arr#) = primitive (\s# -> case unsafeFreezeByteArray# arr# s# of (# s'#, arr'# #) -> (# s'#, ByteArray arr'# #)) -- | Convert an immutable byte array to a mutable one without copying. The -- original array should not be used after the conversion. unsafeThawByteArray :: PrimMonad m => ByteArray -> m (MutableByteArray (PrimState m)) {-# INLINE unsafeThawByteArray #-} unsafeThawByteArray (ByteArray arr#) = primitive (\s# -> (# s#, MutableByteArray (unsafeCoerce# arr#) #)) -- | Size of the byte array in bytes. sizeofByteArray :: ByteArray -> Int {-# INLINE sizeofByteArray #-} sizeofByteArray (ByteArray arr#) = I# (sizeofByteArray# arr#) -- | Size of the mutable byte array in bytes. This function\'s behavior -- is undefined if 'resizeMutableByteArray' is ever called on the mutable -- byte array given as the argument. Consequently, use of this function -- is discouraged. Prefer 'getSizeofMutableByteArray', which ensures correct -- sequencing in the presence of resizing. sizeofMutableByteArray :: MutableByteArray s -> Int {-# INLINE sizeofMutableByteArray #-} sizeofMutableByteArray (MutableByteArray arr#) = I# (sizeofMutableByteArray# arr#) -- | Shrink a mutable byte array. The new size is given in bytes. -- It must be smaller than the old size. The array will be resized in place. -- -- @since 0.7.1.0 shrinkMutableByteArray :: PrimMonad m => MutableByteArray (PrimState m) -> Int -- ^ new size -> m () {-# INLINE shrinkMutableByteArray #-} shrinkMutableByteArray (MutableByteArray arr#) (I# n#) = primitive_ (shrinkMutableByteArray# arr# n#) #if __GLASGOW_HASKELL__ >= 802 -- | Check whether or not the byte array is pinned. Pinned byte arrays cannot -- be moved by the garbage collector. It is safe to use 'byteArrayContents' on -- such byte arrays. -- -- Caution: This function is only available when compiling with GHC 8.2 or -- newer. -- -- @since 0.6.4.0 isByteArrayPinned :: ByteArray -> Bool {-# INLINE isByteArrayPinned #-} isByteArrayPinned (ByteArray arr#) = isTrue# (Exts.isByteArrayPinned# arr#) -- | Check whether or not the mutable byte array is pinned. -- -- Caution: This function is only available when compiling with GHC 8.2 or -- newer. -- -- @since 0.6.4.0 isMutableByteArrayPinned :: MutableByteArray s -> Bool {-# INLINE isMutableByteArrayPinned #-} isMutableByteArrayPinned (MutableByteArray marr#) = isTrue# (Exts.isMutableByteArrayPinned# marr#) #endif -- | Read a primitive value from the byte array. The offset is given in -- elements of type @a@ rather than in bytes. -- -- /Note:/ this function does not do bounds checking. indexByteArray :: Prim a => ByteArray -> Int -> a {-# INLINE indexByteArray #-} indexByteArray (ByteArray arr#) (I# i#) = indexByteArray# arr# i# -- | Read a primitive value from the byte array. The offset is given in -- elements of type @a@ rather than in bytes. -- -- /Note:/ this function does not do bounds checking. readByteArray :: (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> m a {-# INLINE readByteArray #-} readByteArray (MutableByteArray arr#) (I# i#) = primitive (readByteArray# arr# i#) -- | Write a primitive value to the byte array. The offset is given in -- elements of type @a@ rather than in bytes. -- -- /Note:/ this function does not do bounds checking. writeByteArray :: (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -> Int -> a -> m () {-# INLINE writeByteArray #-} writeByteArray (MutableByteArray arr#) (I# i#) x = primitive_ (writeByteArray# arr# i# x) -- | Right-fold over the elements of a 'ByteArray'. foldrByteArray :: forall a b. (Prim a) => (a -> b -> b) -> b -> ByteArray -> b {-# INLINE foldrByteArray #-} foldrByteArray f z arr = go 0 where go i | i < maxI = f (indexByteArray arr i) (go (i + 1)) | otherwise = z maxI = sizeofByteArray arr `quot` sizeOf (undefined :: a) -- | Create a 'ByteArray' from a list. -- -- @byteArrayFromList xs = `byteArrayFromListN` (length xs) xs@ byteArrayFromList :: Prim a => [a] -> ByteArray byteArrayFromList xs = byteArrayFromListN (length xs) xs -- | Create a 'ByteArray' from a list of a known length. If the length -- of the list does not match the given length, this throws an exception. byteArrayFromListN :: Prim a => Int -> [a] -> ByteArray byteArrayFromListN n ys = runST $ do marr <- newByteArray (n * sizeOf (head ys)) let go !ix [] = if ix == n then return () else die "byteArrayFromListN" "list length less than specified size" go !ix (x : xs) = if ix < n then do writeByteArray marr ix x go (ix + 1) xs else die "byteArrayFromListN" "list length greater than specified size" go 0 ys unsafeFreezeByteArray marr unI# :: Int -> Int# unI# (I# n#) = n# -- | Copy a slice of an immutable byte array to a mutable byte array. -- -- /Note:/ this function does not do bounds or overlap checking. copyByteArray :: PrimMonad m => MutableByteArray (PrimState m) -- ^ destination array -> Int -- ^ offset into destination array -> ByteArray -- ^ source array -> Int -- ^ offset into source array -> Int -- ^ number of bytes to copy -> m () {-# INLINE copyByteArray #-} copyByteArray (MutableByteArray dst#) doff (ByteArray src#) soff sz = primitive_ (copyByteArray# src# (unI# soff) dst# (unI# doff) (unI# sz)) -- | Copy a slice of a mutable byte array into another array. The two slices -- may not overlap. -- -- /Note:/ this function does not do bounds or overlap checking. copyMutableByteArray :: PrimMonad m => MutableByteArray (PrimState m) -- ^ destination array -> Int -- ^ offset into destination array -> MutableByteArray (PrimState m) -- ^ source array -> Int -- ^ offset into source array -> Int -- ^ number of bytes to copy -> m () {-# INLINE copyMutableByteArray #-} copyMutableByteArray (MutableByteArray dst#) doff (MutableByteArray src#) soff sz = primitive_ (copyMutableByteArray# src# (unI# soff) dst# (unI# doff) (unI# sz)) -- | Copy a slice of a byte array to an unmanaged pointer address. These must not -- overlap. The offset and length are given in elements, not in bytes. -- -- /Note:/ this function does not do bounds or overlap checking. -- -- @since 0.7.1.0 copyByteArrayToPtr :: forall m a. (PrimMonad m, Prim a) => Ptr a -- ^ destination -> ByteArray -- ^ source array -> Int -- ^ offset into source array, interpreted as elements of type @a@ -> Int -- ^ number of elements to copy -> m () {-# INLINE copyByteArrayToPtr #-} copyByteArrayToPtr (Ptr dst#) (ByteArray src#) soff sz = primitive_ (copyByteArrayToAddr# src# (unI# soff *# siz#) dst# (unI# sz *# siz#)) where siz# = sizeOf# (undefined :: a) -- | Copy from an unmanaged pointer address to a byte array. These must not -- overlap. The offset and length are given in elements, not in bytes. -- -- /Note:/ this function does not do bounds or overlap checking. copyPtrToMutableByteArray :: forall m a. (PrimMonad m, Prim a) => MutableByteArray (PrimState m) -- ^ destination array -> Int -- ^ destination offset given in elements of type @a@ -> Ptr a -- ^ source pointer -> Int -- ^ number of elements -> m () {-# INLINE copyPtrToMutableByteArray #-} copyPtrToMutableByteArray (MutableByteArray ba#) (I# doff#) (Ptr addr#) (I# n#) = primitive_ (copyAddrToByteArray# addr# ba# (doff# *# siz#) (n# *# siz#)) where siz# = sizeOf# (undefined :: a) -- | Copy a slice of a mutable byte array to an unmanaged pointer address. -- These must not overlap. The offset and length are given in elements, not -- in bytes. -- -- /Note:/ this function does not do bounds or overlap checking. -- -- @since 0.7.1.0 copyMutableByteArrayToPtr :: forall m a. (PrimMonad m, Prim a) => Ptr a -- ^ destination -> MutableByteArray (PrimState m) -- ^ source array -> Int -- ^ offset into source array, interpreted as elements of type @a@ -> Int -- ^ number of elements to copy -> m () {-# INLINE copyMutableByteArrayToPtr #-} copyMutableByteArrayToPtr (Ptr dst#) (MutableByteArray src#) soff sz = primitive_ (copyMutableByteArrayToAddr# src# (unI# soff *# siz#) dst# (unI# sz *# siz#)) where siz# = sizeOf# (undefined :: a) ------ --- These latter two should be DEPRECATED ----- -- | Copy a slice of a byte array to an unmanaged address. These must not -- overlap. -- -- Note: This function is just 'copyByteArrayToPtr' where @a@ is 'Word8'. -- -- @since 0.6.4.0 copyByteArrayToAddr :: PrimMonad m => Ptr Word8 -- ^ destination -> ByteArray -- ^ source array -> Int -- ^ offset into source array -> Int -- ^ number of bytes to copy -> m () {-# INLINE copyByteArrayToAddr #-} copyByteArrayToAddr (Ptr dst#) (ByteArray src#) soff sz = primitive_ (copyByteArrayToAddr# src# (unI# soff) dst# (unI# sz)) -- | Copy a slice of a mutable byte array to an unmanaged address. These must -- not overlap. -- -- Note: This function is just 'copyMutableByteArrayToPtr' where @a@ is 'Word8'. -- -- @since 0.6.4.0 copyMutableByteArrayToAddr :: PrimMonad m => Ptr Word8 -- ^ destination -> MutableByteArray (PrimState m) -- ^ source array -> Int -- ^ offset into source array -> Int -- ^ number of bytes to copy -> m () {-# INLINE copyMutableByteArrayToAddr #-} copyMutableByteArrayToAddr (Ptr dst#) (MutableByteArray src#) soff sz = primitive_ (copyMutableByteArrayToAddr# src# (unI# soff) dst# (unI# sz)) -- | Copy a slice of a mutable byte array into another, potentially -- overlapping array. moveByteArray :: PrimMonad m => MutableByteArray (PrimState m) -- ^ destination array -> Int -- ^ offset into destination array -> MutableByteArray (PrimState m) -- ^ source array -> Int -- ^ offset into source array -> Int -- ^ number of bytes to copy -> m () {-# INLINE moveByteArray #-} moveByteArray (MutableByteArray dst#) doff (MutableByteArray src#) soff sz = unsafePrimToPrim $ memmove_mba dst# (fromIntegral doff) src# (fromIntegral soff) (fromIntegral sz) -- | Fill a slice of a mutable byte array with a value. The offset and length -- are given in elements of type @a@ rather than in bytes. -- -- /Note:/ this function does not do bounds checking. setByteArray :: (Prim a, PrimMonad m) => MutableByteArray (PrimState m) -- ^ array to fill -> Int -- ^ offset into array -> Int -- ^ number of values to fill -> a -- ^ value to fill with -> m () {-# INLINE setByteArray #-} setByteArray (MutableByteArray dst#) (I# doff#) (I# sz#) x = primitive_ (setByteArray# dst# doff# sz# x) -- | Fill a slice of a mutable byte array with a byte. -- -- /Note:/ this function does not do bounds checking. fillByteArray :: PrimMonad m => MutableByteArray (PrimState m) -- ^ array to fill -> Int -- ^ offset into array -> Int -- ^ number of bytes to fill -> Word8 -- ^ byte to fill with -> m () {-# INLINE fillByteArray #-} fillByteArray = setByteArray foreign import ccall unsafe "primitive-memops.h hsprimitive_memmove" memmove_mba :: MutableByteArray# s -> CPtrdiff -> MutableByteArray# s -> CPtrdiff -> CSize -> IO () -- | Lexicographic comparison of equal-length slices into two byte arrays. -- This wraps the @compareByteArrays#@ primop, which wraps @memcmp@. compareByteArrays :: ByteArray -- ^ array A -> Int -- ^ offset A, given in bytes -> ByteArray -- ^ array B -> Int -- ^ offset B, given in bytes -> Int -- ^ length of the slice, given in bytes -> Ordering {-# INLINE compareByteArrays #-} #if __GLASGOW_HASKELL__ >= 804 compareByteArrays (ByteArray ba1#) (I# off1#) (ByteArray ba2#) (I# off2#) (I# n#) = compare (I# (compareByteArrays# ba1# off1# ba2# off2# n#)) 0 #else -- Emulate GHC 8.4's 'GHC.Prim.compareByteArrays#' compareByteArrays (ByteArray ba1#) (I# off1#) (ByteArray ba2#) (I# off2#) (I# n#) = compare (fromCInt (unsafeDupablePerformIO (memcmp_ba_offs ba1# off1# ba2# off2# n))) 0 where n = fromIntegral (I# n#) :: CSize fromCInt = fromIntegral :: CInt -> Int foreign import ccall unsafe "primitive-memops.h hsprimitive_memcmp_offset" memcmp_ba_offs :: ByteArray# -> Int# -> ByteArray# -> Int# -> CSize -> IO CInt #endif -- | The empty 'ByteArray'. emptyByteArray :: ByteArray {-# NOINLINE emptyByteArray #-} emptyByteArray = runST (newByteArray 0 >>= unsafeFreezeByteArray) die :: String -> String -> a die fun problem = error $ "Data.Primitive.ByteArray." ++ fun ++ ": " ++ problem -- | Return a newly allocated array with the specified subrange of the -- provided array. The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. cloneByteArray :: ByteArray -- ^ source array -> Int -- ^ offset into destination array -> Int -- ^ number of bytes to copy -> ByteArray {-# INLINE cloneByteArray #-} cloneByteArray src off n = runByteArray $ do dst <- newByteArray n copyByteArray dst 0 src off n return dst -- | Return a newly allocated mutable array with the specified subrange of -- the provided mutable array. The provided mutable array should contain the -- full subrange specified by the two Ints, but this is not checked. cloneMutableByteArray :: PrimMonad m => MutableByteArray (PrimState m) -- ^ source array -> Int -- ^ offset into destination array -> Int -- ^ number of bytes to copy -> m (MutableByteArray (PrimState m)) {-# INLINE cloneMutableByteArray #-} cloneMutableByteArray src off n = do dst <- newByteArray n copyMutableByteArray dst 0 src off n return dst -- | Execute the monadic action and freeze the resulting array. -- -- > runByteArray m = runST $ m >>= unsafeFreezeByteArray runByteArray :: (forall s. ST s (MutableByteArray s)) -> ByteArray #if MIN_VERSION_base(4,10,0) /* In new GHCs, runRW# is available. */ runByteArray m = ByteArray (runByteArray# m) runByteArray# :: (forall s. ST s (MutableByteArray s)) -> ByteArray# runByteArray# m = case runRW# $ \s -> case unST m s of { (# s', MutableByteArray mary# #) -> unsafeFreezeByteArray# mary# s'} of (# _, ary# #) -> ary# unST :: ST s a -> State# s -> (# State# s, a #) unST (GHCST.ST f) = f #else /* In older GHCs, runRW# is not available. */ runByteArray m = runST $ m >>= unsafeFreezeByteArray #endif {- $charElementAccess GHC provides two sets of element accessors for 'Char'. One set faithfully represents 'Char' as 32-bit words using UTF-32. The other set represents 'Char' as 8-bit words using Latin-1 (ISO-8859-1), and the write operation has undefined behavior for codepoints outside of the ASCII and Latin-1 blocks. The 'Prim' instance for 'Char' uses the UTF-32 set of operators. -} -- | Read an 8-bit element from the byte array, interpreting it as a -- Latin-1-encoded character. The offset is given in bytes. -- -- /Note:/ this function does not do bounds checking. readCharArray :: PrimMonad m => MutableByteArray (PrimState m) -> Int -> m Char {-# INLINE readCharArray #-} readCharArray (MutableByteArray arr#) (I# i#) = primitive (\s0 -> case readCharArray# arr# i# s0 of (# s1, c #) -> (# s1, C# c #) ) -- | Write a character to the byte array, encoding it with Latin-1 as -- a single byte. Behavior is undefined for codepoints outside of the -- ASCII and Latin-1 blocks. The offset is given in bytes. -- -- /Note:/ this function does not do bounds checking. writeCharArray :: PrimMonad m => MutableByteArray (PrimState m) -> Int -> Char -> m () {-# INLINE writeCharArray #-} writeCharArray (MutableByteArray arr#) (I# i#) (C# c) = primitive_ (writeCharArray# arr# i# c) -- | Read an 8-bit element from the byte array, interpreting it as a -- Latin-1-encoded character. The offset is given in bytes. -- -- /Note:/ this function does not do bounds checking. indexCharArray :: ByteArray -> Int -> Char {-# INLINE indexCharArray #-} indexCharArray (ByteArray arr#) (I# i#) = C# (indexCharArray# arr# i#) primitive-0.8.0.0/Data/Primitive/Internal/0000755000000000000000000000000007346545000016453 5ustar0000000000000000primitive-0.8.0.0/Data/Primitive/Internal/Operations.hs0000644000000000000000000001636307346545000021143 0ustar0000000000000000{-# LANGUAGE CPP, MagicHash, UnliftedFFITypes #-} -- | -- Module : Data.Primitive.Internal.Operations -- Copyright : (c) Roman Leshchinskiy 2011-2012 -- License : BSD-style -- -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- -- Internal operations. module Data.Primitive.Internal.Operations ( setWord8Array#, setWord16Array#, setWord32Array#, setWord64Array#, setWordArray#, setInt8Array#, setInt16Array#, setInt32Array#, setInt64Array#, setIntArray#, setAddrArray#, setStablePtrArray#, setFloatArray#, setDoubleArray#, setWideCharArray#, setWord8OffAddr#, setWord16OffAddr#, setWord32OffAddr#, setWord64OffAddr#, setWordOffAddr#, setInt8OffAddr#, setInt16OffAddr#, setInt32OffAddr#, setInt64OffAddr#, setIntOffAddr#, setAddrOffAddr#, setFloatOffAddr#, setDoubleOffAddr#, setWideCharOffAddr#, setStablePtrOffAddr# ) where import Data.Primitive.MachDeps (Word64_#, Int64_#) import Foreign.C.Types import GHC.Exts #if __GLASGOW_HASKELL__ >= 902 foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setWord8Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word8# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setWord16Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word16# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setWord32Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word32# -> IO () #else foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setWord8Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setWord16Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setWord32Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word# -> IO () #endif foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word64" setWord64Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word64_# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word" setWordArray# :: MutableByteArray# s -> CPtrdiff -> CSize -> Word# -> IO () #if __GLASGOW_HASKELL__ >= 902 foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setInt8Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int8# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setInt16Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int16# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setInt32Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int32# -> IO () #else foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setInt8Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setInt16Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setInt32Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int# -> IO () #endif foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word64" setInt64Array# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int64_# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word" setIntArray# :: MutableByteArray# s -> CPtrdiff -> CSize -> Int# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Ptr" setAddrArray# :: MutableByteArray# s -> CPtrdiff -> CSize -> Addr# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Ptr" setStablePtrArray# :: MutableByteArray# s -> CPtrdiff -> CSize -> StablePtr# a -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Float" setFloatArray# :: MutableByteArray# s -> CPtrdiff -> CSize -> Float# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Double" setDoubleArray# :: MutableByteArray# s -> CPtrdiff -> CSize -> Double# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Char" setWideCharArray# :: MutableByteArray# s -> CPtrdiff -> CSize -> Char# -> IO () #if __GLASGOW_HASKELL__ >= 902 foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setWord8OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word8# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setWord16OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word16# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setWord32OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word32# -> IO () #else foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setWord8OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setWord16OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setWord32OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word# -> IO () #endif foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word64" setWord64OffAddr# :: Addr# -> CPtrdiff -> CSize -> Word64_# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word" setWordOffAddr# :: Addr# -> CPtrdiff -> CSize -> Word# -> IO () #if __GLASGOW_HASKELL__ >= 902 foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setInt8OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int8# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setInt16OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int16# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setInt32OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int32# -> IO () #else foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word8" setInt8OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word16" setInt16OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word32" setInt32OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int# -> IO () #endif foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word64" setInt64OffAddr# :: Addr# -> CPtrdiff -> CSize -> Int64_# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Word" setIntOffAddr# :: Addr# -> CPtrdiff -> CSize -> Int# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Ptr" setAddrOffAddr# :: Addr# -> CPtrdiff -> CSize -> Addr# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Ptr" setStablePtrOffAddr# :: Addr# -> CPtrdiff -> CSize -> StablePtr# a -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Float" setFloatOffAddr# :: Addr# -> CPtrdiff -> CSize -> Float# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Double" setDoubleOffAddr# :: Addr# -> CPtrdiff -> CSize -> Double# -> IO () foreign import ccall unsafe "primitive-memops.h hsprimitive_memset_Char" setWideCharOffAddr# :: Addr# -> CPtrdiff -> CSize -> Char# -> IO () primitive-0.8.0.0/Data/Primitive/MVar.hs0000644000000000000000000001410107346545000016075 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} -- | -- Module : Data.Primitive.MVar -- License : BSD2 -- Portability : non-portable -- -- Primitive operations on 'MVar'. This module provides a similar interface -- to "Control.Concurrent.MVar". However, the functions are generalized to -- work in any 'PrimMonad' instead of only working in 'IO'. Note that all -- of the functions here are completely deterministic. Users of 'MVar' are -- responsible for designing abstractions that guarantee determinism in -- the presence of multi-threading. -- -- For a more detailed explanation, see "Control.Concurrent.MVar". -- -- @since 0.6.4.0 module Data.Primitive.MVar ( MVar(..) , newMVar , isEmptyMVar , newEmptyMVar , putMVar , readMVar , takeMVar , tryPutMVar , tryReadMVar , tryTakeMVar ) where import Control.Monad.Primitive import GHC.Exts ( MVar#, newMVar#, takeMVar#, sameMVar#, putMVar#, tryTakeMVar#, isEmptyMVar#, tryPutMVar#, (/=#) , readMVar#, tryReadMVar#, isTrue# ) -- | A synchronizing variable, used for communication between concurrent threads. -- It can be thought of as a box, which may be empty or full. data MVar s a = MVar (MVar# s a) instance Eq (MVar s a) where MVar mvar1# == MVar mvar2# = isTrue# (sameMVar# mvar1# mvar2#) -- | Create a new 'MVar' that is initially empty. newEmptyMVar :: PrimMonad m => m (MVar (PrimState m) a) newEmptyMVar = primitive $ \ s# -> case newMVar# s# of (# s2#, svar# #) -> (# s2#, MVar svar# #) -- | Create a new 'MVar' that holds the supplied argument. newMVar :: PrimMonad m => a -> m (MVar (PrimState m) a) newMVar value = do mvar <- newEmptyMVar putMVar mvar value return mvar -- | Return the contents of the 'MVar'. If the 'MVar' is currently -- empty, 'takeMVar' will wait until it is full. After a 'takeMVar', -- the 'MVar' is left empty. -- -- There are two further important properties of 'takeMVar': -- -- * 'takeMVar' is single-wakeup. That is, if there are multiple -- threads blocked in 'takeMVar', and the 'MVar' becomes full, -- only one thread will be woken up. The runtime guarantees that -- the woken thread completes its 'takeMVar' operation. -- * When multiple threads are blocked on an 'MVar', they are -- woken up in FIFO order. This is useful for providing -- fairness properties of abstractions built using 'MVar's. takeMVar :: PrimMonad m => MVar (PrimState m) a -> m a takeMVar (MVar mvar#) = primitive $ \ s# -> takeMVar# mvar# s# -- | Atomically read the contents of an 'MVar'. If the 'MVar' is -- currently empty, 'readMVar' will wait until it is full. -- 'readMVar' is guaranteed to receive the next 'putMVar'. -- -- /Multiple Wakeup:/ 'readMVar' is multiple-wakeup, so when multiple readers -- are blocked on an 'MVar', all of them are woken up at the same time. -- -- * It is single-wakeup instead of multiple-wakeup. -- * It might not receive the value from the next call to 'putMVar' if -- there is already a pending thread blocked on 'takeMVar'. -- * If another thread puts a value in the 'MVar' in between the -- calls to 'takeMVar' and 'putMVar', that value may be overridden. readMVar :: PrimMonad m => MVar (PrimState m) a -> m a readMVar (MVar mvar#) = primitive $ \ s# -> readMVar# mvar# s# -- | Put a value into an 'MVar'. If the 'MVar' is currently full, -- 'putMVar' will wait until it becomes empty. -- -- There are two further important properties of 'putMVar': -- -- * 'putMVar' is single-wakeup. That is, if there are multiple -- threads blocked in 'putMVar', and the 'MVar' becomes empty, -- only one thread will be woken up. The runtime guarantees that -- the woken thread completes its 'putMVar' operation. -- * When multiple threads are blocked on an 'MVar', they are -- woken up in FIFO order. This is useful for providing -- fairness properties of abstractions built using 'MVar's. putMVar :: PrimMonad m => MVar (PrimState m) a -> a -> m () putMVar (MVar mvar#) x = primitive_ (putMVar# mvar# x) -- | A non-blocking version of 'takeMVar'. The 'tryTakeMVar' function -- returns immediately, with 'Nothing' if the 'MVar' was empty, or -- @'Just' a@ if the 'MVar' was full with contents @a@. After 'tryTakeMVar', -- the 'MVar' is left empty. tryTakeMVar :: PrimMonad m => MVar (PrimState m) a -> m (Maybe a) tryTakeMVar (MVar m) = primitive $ \ s -> case tryTakeMVar# m s of (# s', 0#, _ #) -> (# s', Nothing #) -- MVar is empty (# s', _, a #) -> (# s', Just a #) -- MVar is full -- | A non-blocking version of 'putMVar'. The 'tryPutMVar' function -- attempts to put the value @a@ into the 'MVar', returning 'True' if -- it was successful, or 'False' otherwise. tryPutMVar :: PrimMonad m => MVar (PrimState m) a -> a -> m Bool tryPutMVar (MVar mvar#) x = primitive $ \ s# -> case tryPutMVar# mvar# x s# of (# s, 0# #) -> (# s, False #) (# s, _ #) -> (# s, True #) -- | A non-blocking version of 'readMVar'. The 'tryReadMVar' function -- returns immediately, with 'Nothing' if the 'MVar' was empty, or -- @'Just' a@ if the 'MVar' was full with contents @a@. -- -- * It is single-wakeup instead of multiple-wakeup. -- * In the presence of other threads calling 'putMVar', 'tryReadMVar' -- may block. -- * If another thread puts a value in the 'MVar' in between the -- calls to 'tryTakeMVar' and 'putMVar', that value may be overridden. tryReadMVar :: PrimMonad m => MVar (PrimState m) a -> m (Maybe a) tryReadMVar (MVar m) = primitive $ \ s -> case tryReadMVar# m s of (# s', 0#, _ #) -> (# s', Nothing #) -- MVar is empty (# s', _, a #) -> (# s', Just a #) -- MVar is full -- | Check whether a given 'MVar' is empty. -- -- Notice that the boolean value returned is just a snapshot of -- the state of the 'MVar'. By the time you get to react on its result, -- the 'MVar' may have been filled (or emptied) - so be extremely -- careful when using this operation. Use 'tryTakeMVar' instead if possible. isEmptyMVar :: PrimMonad m => MVar (PrimState m) a -> m Bool isEmptyMVar (MVar mv#) = primitive $ \ s# -> case isEmptyMVar# mv# s# of (# s2#, flg #) -> (# s2#, isTrue# (flg /=# 0#) #) primitive-0.8.0.0/Data/Primitive/MachDeps.hs0000644000000000000000000000411107346545000016714 0ustar0000000000000000{-# LANGUAGE CPP, MagicHash #-} -- | -- Module : Data.Primitive.MachDeps -- Copyright : (c) Roman Leshchinskiy 2009-2012 -- License : BSD-style -- -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- -- Machine-dependent constants. module Data.Primitive.MachDeps where #include "MachDeps.h" import GHC.Exts sIZEOF_CHAR, aLIGNMENT_CHAR, sIZEOF_INT, aLIGNMENT_INT, sIZEOF_WORD, aLIGNMENT_WORD, sIZEOF_DOUBLE, aLIGNMENT_DOUBLE, sIZEOF_FLOAT, aLIGNMENT_FLOAT, sIZEOF_PTR, aLIGNMENT_PTR, sIZEOF_FUNPTR, aLIGNMENT_FUNPTR, sIZEOF_STABLEPTR, aLIGNMENT_STABLEPTR, sIZEOF_INT8, aLIGNMENT_INT8, sIZEOF_WORD8, aLIGNMENT_WORD8, sIZEOF_INT16, aLIGNMENT_INT16, sIZEOF_WORD16, aLIGNMENT_WORD16, sIZEOF_INT32, aLIGNMENT_INT32, sIZEOF_WORD32, aLIGNMENT_WORD32, sIZEOF_INT64, aLIGNMENT_INT64, sIZEOF_WORD64, aLIGNMENT_WORD64 :: Int sIZEOF_CHAR = SIZEOF_HSCHAR aLIGNMENT_CHAR = ALIGNMENT_HSCHAR sIZEOF_INT = SIZEOF_HSINT aLIGNMENT_INT = ALIGNMENT_HSINT sIZEOF_WORD = SIZEOF_HSWORD aLIGNMENT_WORD = ALIGNMENT_HSWORD sIZEOF_DOUBLE = SIZEOF_HSDOUBLE aLIGNMENT_DOUBLE = ALIGNMENT_HSDOUBLE sIZEOF_FLOAT = SIZEOF_HSFLOAT aLIGNMENT_FLOAT = ALIGNMENT_HSFLOAT sIZEOF_PTR = SIZEOF_HSPTR aLIGNMENT_PTR = ALIGNMENT_HSPTR sIZEOF_FUNPTR = SIZEOF_HSFUNPTR aLIGNMENT_FUNPTR = ALIGNMENT_HSFUNPTR sIZEOF_STABLEPTR = SIZEOF_HSSTABLEPTR aLIGNMENT_STABLEPTR = ALIGNMENT_HSSTABLEPTR sIZEOF_INT8 = SIZEOF_INT8 aLIGNMENT_INT8 = ALIGNMENT_INT8 sIZEOF_WORD8 = SIZEOF_WORD8 aLIGNMENT_WORD8 = ALIGNMENT_WORD8 sIZEOF_INT16 = SIZEOF_INT16 aLIGNMENT_INT16 = ALIGNMENT_INT16 sIZEOF_WORD16 = SIZEOF_WORD16 aLIGNMENT_WORD16 = ALIGNMENT_WORD16 sIZEOF_INT32 = SIZEOF_INT32 aLIGNMENT_INT32 = ALIGNMENT_INT32 sIZEOF_WORD32 = SIZEOF_WORD32 aLIGNMENT_WORD32 = ALIGNMENT_WORD32 sIZEOF_INT64 = SIZEOF_INT64 aLIGNMENT_INT64 = ALIGNMENT_INT64 sIZEOF_WORD64 = SIZEOF_WORD64 aLIGNMENT_WORD64 = ALIGNMENT_WORD64 #if WORD_SIZE_IN_BITS == 32 || __GLASGOW_HASKELL__ >= 903 type Word64_# = Word64# type Int64_# = Int64# #else type Word64_# = Word# type Int64_# = Int# #endif primitive-0.8.0.0/Data/Primitive/MutVar.hs0000644000000000000000000000753407346545000016462 0ustar0000000000000000{-# LANGUAGE MagicHash, UnboxedTuples, DeriveDataTypeable, CPP #-} -- | -- Module : Data.Primitive.MutVar -- Copyright : (c) Justin Bonnar 2011, Roman Leshchinskiy 2011-2012 -- License : BSD-style -- -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- -- Primitive boxed mutable variables. This is a generalization of -- "Data.IORef", "Data.STRef" and "Data.STRef.Lazy" to work in -- any 'PrimMonad'. module Data.Primitive.MutVar ( MutVar(..), newMutVar, readMutVar, writeMutVar, atomicModifyMutVar, atomicModifyMutVar', modifyMutVar, modifyMutVar' ) where import Control.Monad.Primitive ( PrimMonad(..), primitive_ ) import GHC.Exts ( MutVar#, sameMutVar#, newMutVar# , readMutVar#, writeMutVar#, atomicModifyMutVar# , isTrue# ) import Data.Typeable ( Typeable ) -- | A 'MutVar' behaves like a single-element mutable array associated -- with a primitive state token. data MutVar s a = MutVar (MutVar# s a) deriving ( Typeable ) instance Eq (MutVar s a) where MutVar mva# == MutVar mvb# = isTrue# (sameMutVar# mva# mvb#) -- | Create a new 'MutVar' with the specified initial value. newMutVar :: PrimMonad m => a -> m (MutVar (PrimState m) a) {-# INLINE newMutVar #-} newMutVar initialValue = primitive $ \s# -> case newMutVar# initialValue s# of (# s'#, mv# #) -> (# s'#, MutVar mv# #) -- | Read the value of a 'MutVar'. readMutVar :: PrimMonad m => MutVar (PrimState m) a -> m a {-# INLINE readMutVar #-} readMutVar (MutVar mv#) = primitive (readMutVar# mv#) -- | Write a new value into a 'MutVar'. writeMutVar :: PrimMonad m => MutVar (PrimState m) a -> a -> m () {-# INLINE writeMutVar #-} writeMutVar (MutVar mv#) newValue = primitive_ (writeMutVar# mv# newValue) -- | Atomically mutate the contents of a 'MutVar'. -- -- This function is useful for using 'MutVar' in a safe way in a multithreaded program. -- If you only have one 'MutVar', then using 'atomicModifyMutVar' to access and modify -- it will prevent race conditions. -- -- Extending the atomicity to multiple 'MutVar's is problematic, -- so if you need to do anything more complicated, -- using 'Data.Primitive.MVar.MVar' instead is a good idea. -- -- 'atomicModifyMutVar' does not apply the function strictly. This means if a program -- calls 'atomicModifyMutVar' many times, but seldom uses the value, thunks will pile up -- in memory resulting in a space leak. -- To avoid this problem, use 'atomicModifyMutVar'' instead. atomicModifyMutVar :: PrimMonad m => MutVar (PrimState m) a -> (a -> (a, b)) -> m b {-# INLINE atomicModifyMutVar #-} atomicModifyMutVar (MutVar mv#) f = primitive $ atomicModifyMutVar# mv# f -- | Strict version of 'atomicModifyMutVar'. This forces both the value stored -- in the 'MutVar' as well as the value returned. atomicModifyMutVar' :: PrimMonad m => MutVar (PrimState m) a -> (a -> (a, b)) -> m b {-# INLINE atomicModifyMutVar' #-} atomicModifyMutVar' mv f = do b <- atomicModifyMutVar mv force b `seq` return b where force x = case f x of v@(x', _) -> x' `seq` v -- | Mutate the contents of a 'MutVar'. -- -- 'modifyMutVar' does not apply the function strictly. This means if a program -- calls 'modifyMutVar' many times, but seldom uses the value, thunks will pile up -- in memory resulting in a space leak. -- To avoid this problem, use 'modifyMutVar'' instead. modifyMutVar :: PrimMonad m => MutVar (PrimState m) a -> (a -> a) -> m () {-# INLINE modifyMutVar #-} modifyMutVar (MutVar mv#) g = primitive_ $ \s# -> case readMutVar# mv# s# of (# s'#, a #) -> writeMutVar# mv# (g a) s'# -- | Strict version of 'modifyMutVar'. modifyMutVar' :: PrimMonad m => MutVar (PrimState m) a -> (a -> a) -> m () {-# INLINE modifyMutVar' #-} modifyMutVar' (MutVar mv#) g = primitive_ $ \s# -> case readMutVar# mv# s# of (# s'#, a #) -> let a' = g a in a' `seq` writeMutVar# mv# a' s'# primitive-0.8.0.0/Data/Primitive/PrimArray.hs0000644000000000000000000011764507346545000017157 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE TemplateHaskellQuotes #-} {-# LANGUAGE RoleAnnotations #-} -- | -- Module : Data.Primitive.PrimArray -- Copyright : (c) Roman Leshchinskiy 2009-2012 -- License : BSD-style -- -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- -- Arrays of unboxed primitive types. The functions provided by this module -- match the behavior of those provided by "Data.Primitive.ByteArray", and -- the underlying types and primops that back them are the same. -- However, the type constructors 'PrimArray' and 'MutablePrimArray' take one additional -- argument compared to their respective counterparts 'ByteArray' and 'Data.Primitive.ByteArray.MutableByteArray'. -- This argument is used to designate the type of element in the array. -- Consequently, all functions in this module accept length and indices in -- terms of elements, not bytes. -- -- @since 0.6.4.0 module Data.Primitive.PrimArray ( -- * Types PrimArray(..) , MutablePrimArray(..) -- * Allocation , newPrimArray , newPinnedPrimArray , newAlignedPinnedPrimArray , resizeMutablePrimArray , shrinkMutablePrimArray -- * Element Access , readPrimArray , writePrimArray , indexPrimArray -- * Freezing and Thawing , freezePrimArray , thawPrimArray , runPrimArray , unsafeFreezePrimArray , unsafeThawPrimArray -- * Block Operations , copyPrimArray , copyMutablePrimArray , copyPrimArrayToPtr , copyMutablePrimArrayToPtr , copyPtrToMutablePrimArray , clonePrimArray , cloneMutablePrimArray , setPrimArray -- * Information , sameMutablePrimArray , getSizeofMutablePrimArray , sizeofMutablePrimArray , sizeofPrimArray , primArrayContents , mutablePrimArrayContents #if __GLASGOW_HASKELL__ >= 802 , isPrimArrayPinned , isMutablePrimArrayPinned #endif -- * List Conversion , primArrayToList , primArrayFromList , primArrayFromListN -- * Folding , foldrPrimArray , foldrPrimArray' , foldlPrimArray , foldlPrimArray' , foldlPrimArrayM' -- * Effectful Folding , traversePrimArray_ , itraversePrimArray_ -- * Map/Create , emptyPrimArray , mapPrimArray , imapPrimArray , generatePrimArray , replicatePrimArray , filterPrimArray , mapMaybePrimArray -- * Effectful Map/Create -- $effectfulMapCreate -- ** Lazy Applicative , traversePrimArray , itraversePrimArray , generatePrimArrayA , replicatePrimArrayA , filterPrimArrayA , mapMaybePrimArrayA -- ** Strict Primitive Monadic , traversePrimArrayP , itraversePrimArrayP , generatePrimArrayP , replicatePrimArrayP , filterPrimArrayP , mapMaybePrimArrayP ) where import GHC.Exts import Data.Primitive.Types import Data.Primitive.ByteArray (ByteArray(..)) #if !MIN_VERSION_base(4,11,0) import Data.Monoid ((<>)) #endif #if !MIN_VERSION_base(4,18,0) import Control.Applicative (liftA2) #endif import Control.DeepSeq import Control.Monad.Primitive import Control.Monad.ST import qualified Data.List as L import qualified Data.Primitive.ByteArray as PB import qualified Data.Primitive.Types as PT #if MIN_VERSION_base(4,10,0) import qualified GHC.ST as GHCST #endif import Language.Haskell.TH.Syntax (Lift (..)) #if !MIN_VERSION_base(4,11,0) import Data.Semigroup (Semigroup) #endif import qualified Data.Semigroup as SG #if __GLASGOW_HASKELL__ >= 802 import qualified GHC.Exts as Exts #endif -- | Arrays of unboxed elements. This accepts types like 'Double', 'Char', -- 'Int' and 'Word', as well as their fixed-length variants ('Word8', -- 'Word16', etc.). Since the elements are unboxed, a 'PrimArray' is strict -- in its elements. This differs from the behavior of 'Data.Primitive.Array.Array', -- which is lazy in its elements. data PrimArray a = PrimArray ByteArray# type role PrimArray nominal instance Lift (PrimArray a) where #if MIN_VERSION_template_haskell(2,16,0) liftTyped ary = [|| byteArrayToPrimArray ba ||] #else lift ary = [| byteArrayToPrimArray ba |] #endif where ba = primArrayToByteArray ary instance NFData (PrimArray a) where rnf (PrimArray _) = () -- | Mutable primitive arrays associated with a primitive state token. -- These can be written to and read from in a monadic context that supports -- sequencing, such as 'IO' or 'ST'. Typically, a mutable primitive array will -- be built and then converted to an immutable primitive array using -- 'unsafeFreezePrimArray'. However, it is also acceptable to simply discard -- a mutable primitive array since it lives in managed memory and will be -- garbage collected when no longer referenced. data MutablePrimArray s a = MutablePrimArray (MutableByteArray# s) instance Eq (MutablePrimArray s a) where (==) = sameMutablePrimArray instance NFData (MutablePrimArray s a) where rnf (MutablePrimArray _) = () sameByteArray :: ByteArray# -> ByteArray# -> Bool sameByteArray ba1 ba2 = case reallyUnsafePtrEquality# (unsafeCoerce# ba1 :: ()) (unsafeCoerce# ba2 :: ()) of r -> isTrue# r -- | @since 0.6.4.0 instance (Eq a, Prim a) => Eq (PrimArray a) where a1@(PrimArray ba1#) == a2@(PrimArray ba2#) | sameByteArray ba1# ba2# = True | sz1 /= sz2 = False | otherwise = loop (quot sz1 (sizeOf (undefined :: a)) - 1) where -- Here, we take the size in bytes, not in elements. We do this -- since it allows us to defer performing the division to -- calculate the size in elements. sz1 = PB.sizeofByteArray (ByteArray ba1#) sz2 = PB.sizeofByteArray (ByteArray ba2#) loop !i | i < 0 = True | otherwise = indexPrimArray a1 i == indexPrimArray a2 i && loop (i - 1) {-# INLINE (==) #-} -- | Lexicographic ordering. Subject to change between major versions. -- -- @since 0.6.4.0 instance (Ord a, Prim a) => Ord (PrimArray a) where compare a1@(PrimArray ba1#) a2@(PrimArray ba2#) | sameByteArray ba1# ba2# = EQ | otherwise = loop 0 where sz1 = PB.sizeofByteArray (ByteArray ba1#) sz2 = PB.sizeofByteArray (ByteArray ba2#) sz = quot (min sz1 sz2) (sizeOf (undefined :: a)) loop !i | i < sz = compare (indexPrimArray a1 i) (indexPrimArray a2 i) <> loop (i + 1) | otherwise = compare sz1 sz2 {-# INLINE compare #-} -- | @since 0.6.4.0 instance Prim a => IsList (PrimArray a) where type Item (PrimArray a) = a fromList = primArrayFromList fromListN = primArrayFromListN toList = primArrayToList -- | @since 0.6.4.0 instance (Show a, Prim a) => Show (PrimArray a) where showsPrec p a = showParen (p > 10) $ showString "fromListN " . shows (sizeofPrimArray a) . showString " " . shows (primArrayToList a) die :: String -> String -> a die fun problem = error $ "Data.Primitive.PrimArray." ++ fun ++ ": " ++ problem -- | Create a 'PrimArray' from a list. -- -- @primArrayFromList vs = `primArrayFromListN` (length vs) vs@ primArrayFromList :: Prim a => [a] -> PrimArray a primArrayFromList vs = primArrayFromListN (L.length vs) vs -- | Create a 'PrimArray' from a list of a known length. If the length -- of the list does not match the given length, this throws an exception. primArrayFromListN :: forall a. Prim a => Int -> [a] -> PrimArray a primArrayFromListN len vs = runST run where run :: forall s. ST s (PrimArray a) run = do arr <- newPrimArray len let go :: [a] -> Int -> ST s () go [] !ix = if ix == len then return () else die "fromListN" "list length less than specified size" go (a : as) !ix = if ix < len then do writePrimArray arr ix a go as (ix + 1) else die "fromListN" "list length greater than specified size" go vs 0 unsafeFreezePrimArray arr -- | Convert a 'PrimArray' to a list. {-# INLINE primArrayToList #-} primArrayToList :: forall a. Prim a => PrimArray a -> [a] primArrayToList xs = build (\c n -> foldrPrimArray c n xs) primArrayToByteArray :: PrimArray a -> PB.ByteArray primArrayToByteArray (PrimArray x) = PB.ByteArray x byteArrayToPrimArray :: ByteArray -> PrimArray a byteArrayToPrimArray (PB.ByteArray x) = PrimArray x -- | @since 0.6.4.0 instance Semigroup (PrimArray a) where x <> y = byteArrayToPrimArray (primArrayToByteArray x SG.<> primArrayToByteArray y) sconcat = byteArrayToPrimArray . SG.sconcat . fmap primArrayToByteArray stimes i arr = byteArrayToPrimArray (SG.stimes i (primArrayToByteArray arr)) -- | @since 0.6.4.0 instance Monoid (PrimArray a) where mempty = emptyPrimArray #if !(MIN_VERSION_base(4,11,0)) mappend x y = byteArrayToPrimArray (mappend (primArrayToByteArray x) (primArrayToByteArray y)) #endif mconcat = byteArrayToPrimArray . mconcat . map primArrayToByteArray -- | The empty 'PrimArray'. emptyPrimArray :: PrimArray a {-# NOINLINE emptyPrimArray #-} emptyPrimArray = runST $ primitive $ \s0# -> case newByteArray# 0# s0# of (# s1#, arr# #) -> case unsafeFreezeByteArray# arr# s1# of (# s2#, arr'# #) -> (# s2#, PrimArray arr'# #) -- | Create a new mutable primitive array of the given length. The -- underlying memory is left uninitialized. -- -- /Note:/ this function does not check if the input is non-negative. newPrimArray :: forall m a. (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) {-# INLINE newPrimArray #-} newPrimArray (I# n#) = primitive (\s# -> case newByteArray# (n# *# sizeOf# (undefined :: a)) s# of (# s'#, arr# #) -> (# s'#, MutablePrimArray arr# #) ) -- | Resize a mutable primitive array. The new size is given in elements. -- -- This will either resize the array in-place or, if not possible, allocate the -- contents into a new, unpinned array and copy the original array\'s contents. -- -- To avoid undefined behaviour, the original 'MutablePrimArray' shall not be -- accessed anymore after a 'resizeMutablePrimArray' has been performed. -- Moreover, no reference to the old one should be kept in order to allow -- garbage collection of the original 'MutablePrimArray' in case a new -- 'MutablePrimArray' had to be allocated. resizeMutablePrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -- ^ new size -> m (MutablePrimArray (PrimState m) a) {-# INLINE resizeMutablePrimArray #-} resizeMutablePrimArray (MutablePrimArray arr#) (I# n#) = primitive (\s# -> case resizeMutableByteArray# arr# (n# *# sizeOf# (undefined :: a)) s# of (# s'#, arr'# #) -> (# s'#, MutablePrimArray arr'# #)) -- | Shrink a mutable primitive array. The new size is given in elements. -- It must be smaller than the old size. The array will be resized in place. shrinkMutablePrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -> Int -- ^ new size -> m () {-# INLINE shrinkMutablePrimArray #-} shrinkMutablePrimArray (MutablePrimArray arr#) (I# n#) = primitive_ (shrinkMutableByteArray# arr# (n# *# sizeOf# (undefined :: a))) -- | Read a value from the array at the given index. -- -- /Note:/ this function does not do bounds checking. readPrimArray :: (Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -> Int -> m a {-# INLINE readPrimArray #-} readPrimArray (MutablePrimArray arr#) (I# i#) = primitive (readByteArray# arr# i#) -- | Write an element to the given index. -- -- /Note:/ this function does not do bounds checking. writePrimArray :: (Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -- ^ array -> Int -- ^ index -> a -- ^ element -> m () {-# INLINE writePrimArray #-} writePrimArray (MutablePrimArray arr#) (I# i#) x = primitive_ (writeByteArray# arr# i# x) -- | Copy part of a mutable array into another mutable array. -- In the case that the destination and -- source arrays are the same, the regions may overlap. -- -- /Note:/ this function does not do bounds or overlap checking. copyMutablePrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -- ^ destination array -> Int -- ^ offset into destination array -> MutablePrimArray (PrimState m) a -- ^ source array -> Int -- ^ offset into source array -> Int -- ^ number of elements to copy -> m () {-# INLINE copyMutablePrimArray #-} copyMutablePrimArray (MutablePrimArray dst#) (I# doff#) (MutablePrimArray src#) (I# soff#) (I# n#) = primitive_ (copyMutableByteArray# src# (soff# *# sizeOf# (undefined :: a)) dst# (doff# *# sizeOf# (undefined :: a)) (n# *# sizeOf# (undefined :: a)) ) -- | Copy part of an array into another mutable array. -- -- /Note:/ this function does not do bounds or overlap checking. copyPrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -- ^ destination array -> Int -- ^ offset into destination array -> PrimArray a -- ^ source array -> Int -- ^ offset into source array -> Int -- ^ number of elements to copy -> m () {-# INLINE copyPrimArray #-} copyPrimArray (MutablePrimArray dst#) (I# doff#) (PrimArray src#) (I# soff#) (I# n#) = primitive_ (copyByteArray# src# (soff# *# sizeOf# (undefined :: a)) dst# (doff# *# sizeOf# (undefined :: a)) (n# *# sizeOf# (undefined :: a)) ) -- | Copy a slice of an immutable primitive array to a pointer. -- The offset and length are given in elements of type @a@. -- This function assumes that the 'Prim' instance of @a@ -- agrees with the 'Storable' instance. -- -- /Note:/ this function does not do bounds or overlap checking. copyPrimArrayToPtr :: forall m a. (PrimMonad m, Prim a) => Ptr a -- ^ destination pointer -> PrimArray a -- ^ source array -> Int -- ^ offset into source array -> Int -- ^ number of elements to copy -> m () {-# INLINE copyPrimArrayToPtr #-} copyPrimArrayToPtr (Ptr addr#) (PrimArray ba#) (I# soff#) (I# n#) = primitive (\ s# -> let s'# = copyByteArrayToAddr# ba# (soff# *# siz#) addr# (n# *# siz#) s# in (# s'#, () #)) where siz# = sizeOf# (undefined :: a) -- | Copy a slice of a mutable primitive array to a pointer. -- The offset and length are given in elements of type @a@. -- This function assumes that the 'Prim' instance of @a@ -- agrees with the 'Storable' instance. -- -- /Note:/ this function does not do bounds or overlap checking. copyMutablePrimArrayToPtr :: forall m a. (PrimMonad m, Prim a) => Ptr a -- ^ destination pointer -> MutablePrimArray (PrimState m) a -- ^ source array -> Int -- ^ offset into source array -> Int -- ^ number of elements to copy -> m () {-# INLINE copyMutablePrimArrayToPtr #-} copyMutablePrimArrayToPtr (Ptr addr#) (MutablePrimArray mba#) (I# soff#) (I# n#) = primitive (\ s# -> let s'# = copyMutableByteArrayToAddr# mba# (soff# *# siz#) addr# (n# *# siz#) s# in (# s'#, () #)) where siz# = sizeOf# (undefined :: a) -- | Copy from a pointer to a mutable primitive array. -- The offset and length are given in elements of type @a@. -- This function assumes that the 'Prim' instance of @a@ -- agrees with the 'Storable' instance. -- -- /Note:/ this function does not do bounds or overlap checking. copyPtrToMutablePrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -- ^ destination array -> Int -- ^ destination offset -> Ptr a -- ^ source pointer -> Int -- ^ number of elements -> m () {-# INLINE copyPtrToMutablePrimArray #-} copyPtrToMutablePrimArray (MutablePrimArray ba#) (I# doff#) (Ptr addr#) (I# n#) = primitive_ (copyAddrToByteArray# addr# ba# (doff# *# siz#) (n# *# siz#)) where siz# = sizeOf# (undefined :: a) -- | Fill a slice of a mutable primitive array with a value. -- -- /Note:/ this function does not do bounds checking. setPrimArray :: (Prim a, PrimMonad m) => MutablePrimArray (PrimState m) a -- ^ array to fill -> Int -- ^ offset into array -> Int -- ^ number of values to fill -> a -- ^ value to fill with -> m () {-# INLINE setPrimArray #-} setPrimArray (MutablePrimArray dst#) (I# doff#) (I# sz#) x = primitive_ (PT.setByteArray# dst# doff# sz# x) -- | Get the size of a mutable primitive array in elements. Unlike 'sizeofMutablePrimArray', -- this function ensures sequencing in the presence of resizing. getSizeofMutablePrimArray :: forall m a. (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -- ^ array -> m Int {-# INLINE getSizeofMutablePrimArray #-} #if __GLASGOW_HASKELL__ >= 801 getSizeofMutablePrimArray (MutablePrimArray arr#) = primitive (\s# -> case getSizeofMutableByteArray# arr# s# of (# s'#, sz# #) -> (# s'#, I# (quotInt# sz# (sizeOf# (undefined :: a))) #) ) #else -- On older GHCs, it is not possible to resize a byte array, so -- this provides behavior consistent with the implementation for -- newer GHCs. getSizeofMutablePrimArray arr = return (sizeofMutablePrimArray arr) #endif -- | Size of the mutable primitive array in elements. This function shall not -- be used on primitive arrays that are an argument to or a result of -- 'resizeMutablePrimArray' or 'shrinkMutablePrimArray'. sizeofMutablePrimArray :: forall s a. Prim a => MutablePrimArray s a -> Int {-# INLINE sizeofMutablePrimArray #-} sizeofMutablePrimArray (MutablePrimArray arr#) = I# (quotInt# (sizeofMutableByteArray# arr#) (sizeOf# (undefined :: a))) -- | Check if the two arrays refer to the same memory block. sameMutablePrimArray :: MutablePrimArray s a -> MutablePrimArray s a -> Bool {-# INLINE sameMutablePrimArray #-} sameMutablePrimArray (MutablePrimArray arr#) (MutablePrimArray brr#) = isTrue# (sameMutableByteArray# arr# brr#) -- | Create an immutable copy of a slice of a primitive array. The offset and -- length are given in elements. -- -- This operation makes a copy of the specified section, so it is safe to -- continue using the mutable array afterward. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. freezePrimArray :: (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -- ^ source -> Int -- ^ offset in elements -> Int -- ^ length in elements -> m (PrimArray a) {-# INLINE freezePrimArray #-} freezePrimArray !src !off !len = do dst <- newPrimArray len copyMutablePrimArray dst 0 src off len unsafeFreezePrimArray dst -- | Create a mutable primitive array from a slice of an immutable primitive array. -- The offset and length are given in elements. -- -- This operation makes a copy of the specified slice, so it is safe to -- use the immutable array afterward. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. -- -- @since 0.7.2.0 thawPrimArray :: (PrimMonad m, Prim a) => PrimArray a -- ^ source -> Int -- ^ offset in elements -> Int -- ^ length in elements -> m (MutablePrimArray (PrimState m) a) {-# INLINE thawPrimArray #-} thawPrimArray !src !off !len = do dst <- newPrimArray len copyPrimArray dst 0 src off len return dst -- | Convert a mutable primitive array to an immutable one without copying. The -- array should not be modified after the conversion. unsafeFreezePrimArray :: PrimMonad m => MutablePrimArray (PrimState m) a -> m (PrimArray a) {-# INLINE unsafeFreezePrimArray #-} unsafeFreezePrimArray (MutablePrimArray arr#) = primitive (\s# -> case unsafeFreezeByteArray# arr# s# of (# s'#, arr'# #) -> (# s'#, PrimArray arr'# #)) -- | Convert an immutable array to a mutable one without copying. The -- original array should not be used after the conversion. unsafeThawPrimArray :: PrimMonad m => PrimArray a -> m (MutablePrimArray (PrimState m) a) {-# INLINE unsafeThawPrimArray #-} unsafeThawPrimArray (PrimArray arr#) = primitive (\s# -> (# s#, MutablePrimArray (unsafeCoerce# arr#) #)) -- | Read a primitive value from the primitive array. -- -- /Note:/ this function does not do bounds checking. indexPrimArray :: forall a. Prim a => PrimArray a -> Int -> a {-# INLINE indexPrimArray #-} indexPrimArray (PrimArray arr#) (I# i#) = indexByteArray# arr# i# -- | Get the size, in elements, of the primitive array. sizeofPrimArray :: forall a. Prim a => PrimArray a -> Int {-# INLINE sizeofPrimArray #-} sizeofPrimArray (PrimArray arr#) = I# (quotInt# (sizeofByteArray# arr#) (sizeOf# (undefined :: a))) #if __GLASGOW_HASKELL__ >= 802 -- | Check whether or not the primitive array is pinned. Pinned primitive arrays cannot -- be moved by the garbage collector. It is safe to use 'primArrayContents' -- on such arrays. This function is only available when compiling with -- GHC 8.2 or newer. -- -- @since 0.7.1.0 isPrimArrayPinned :: PrimArray a -> Bool {-# INLINE isPrimArrayPinned #-} isPrimArrayPinned (PrimArray arr#) = isTrue# (Exts.isByteArrayPinned# arr#) -- | Check whether or not the mutable primitive array is pinned. This function is -- only available when compiling with GHC 8.2 or newer. -- -- @since 0.7.1.0 isMutablePrimArrayPinned :: MutablePrimArray s a -> Bool {-# INLINE isMutablePrimArrayPinned #-} isMutablePrimArrayPinned (MutablePrimArray marr#) = isTrue# (Exts.isMutableByteArrayPinned# marr#) #endif -- | Lazy right-associated fold over the elements of a 'PrimArray'. {-# INLINE foldrPrimArray #-} foldrPrimArray :: forall a b. Prim a => (a -> b -> b) -> b -> PrimArray a -> b foldrPrimArray f z arr = go 0 where !sz = sizeofPrimArray arr go !i | i < sz = f (indexPrimArray arr i) (go (i + 1)) | otherwise = z -- | Strict right-associated fold over the elements of a 'PrimArray'. {-# INLINE foldrPrimArray' #-} foldrPrimArray' :: forall a b. Prim a => (a -> b -> b) -> b -> PrimArray a -> b foldrPrimArray' f z0 arr = go (sizeofPrimArray arr - 1) z0 where go !i !acc | i < 0 = acc | otherwise = go (i - 1) (f (indexPrimArray arr i) acc) -- | Lazy left-associated fold over the elements of a 'PrimArray'. {-# INLINE foldlPrimArray #-} foldlPrimArray :: forall a b. Prim a => (b -> a -> b) -> b -> PrimArray a -> b foldlPrimArray f z arr = go (sizeofPrimArray arr - 1) where go !i | i < 0 = z | otherwise = f (go (i - 1)) (indexPrimArray arr i) -- | Strict left-associated fold over the elements of a 'PrimArray'. {-# INLINE foldlPrimArray' #-} foldlPrimArray' :: forall a b. Prim a => (b -> a -> b) -> b -> PrimArray a -> b foldlPrimArray' f z0 arr = go 0 z0 where !sz = sizeofPrimArray arr go !i !acc | i < sz = go (i + 1) (f acc (indexPrimArray arr i)) | otherwise = acc -- | Strict left-associated fold over the elements of a 'PrimArray'. {-# INLINE foldlPrimArrayM' #-} foldlPrimArrayM' :: (Prim a, Monad m) => (b -> a -> m b) -> b -> PrimArray a -> m b foldlPrimArrayM' f z0 arr = go 0 z0 where !sz = sizeofPrimArray arr go !i !acc1 | i < sz = do acc2 <- f acc1 (indexPrimArray arr i) go (i + 1) acc2 | otherwise = return acc1 -- | Traverse a primitive array. The traversal forces the resulting values and -- writes them to the new primitive array as it performs the monadic effects. -- Consequently: -- -- >>> traversePrimArrayP (\x -> print x $> bool x undefined (x == 2)) (fromList [1, 2, 3 :: Int]) -- 1 -- 2 -- *** Exception: Prelude.undefined -- -- In many situations, 'traversePrimArrayP' can replace 'traversePrimArray', -- changing the strictness characteristics of the traversal but typically improving -- the performance. Consider the following short-circuiting traversal: -- -- > incrPositiveA :: PrimArray Int -> Maybe (PrimArray Int) -- > incrPositiveA xs = traversePrimArray (\x -> bool Nothing (Just (x + 1)) (x > 0)) xs -- -- This can be rewritten using 'traversePrimArrayP'. To do this, we must -- change the traversal context to @MaybeT (ST s)@, which has a 'PrimMonad' -- instance: -- -- > incrPositiveB :: PrimArray Int -> Maybe (PrimArray Int) -- > incrPositiveB xs = runST $ runMaybeT $ traversePrimArrayP -- > (\x -> bool (MaybeT (return Nothing)) (MaybeT (return (Just (x + 1)))) (x > 0)) -- > xs -- -- Benchmarks demonstrate that the second implementation runs 150 times -- faster than the first. It also results in fewer allocations. {-# INLINE traversePrimArrayP #-} traversePrimArrayP :: (PrimMonad m, Prim a, Prim b) => (a -> m b) -> PrimArray a -> m (PrimArray b) traversePrimArrayP f arr = do let !sz = sizeofPrimArray arr marr <- newPrimArray sz let go !ix = if ix < sz then do b <- f (indexPrimArray arr ix) writePrimArray marr ix b go (ix + 1) else return () go 0 unsafeFreezePrimArray marr -- | Filter the primitive array, keeping the elements for which the monadic -- predicate evaluates to true. {-# INLINE filterPrimArrayP #-} filterPrimArrayP :: (PrimMonad m, Prim a) => (a -> m Bool) -> PrimArray a -> m (PrimArray a) filterPrimArrayP f arr = do let !sz = sizeofPrimArray arr marr <- newPrimArray sz let go !ixSrc !ixDst = if ixSrc < sz then do let a = indexPrimArray arr ixSrc b <- f a if b then do writePrimArray marr ixDst a go (ixSrc + 1) (ixDst + 1) else go (ixSrc + 1) ixDst else return ixDst lenDst <- go 0 0 marr' <- resizeMutablePrimArray marr lenDst unsafeFreezePrimArray marr' -- | Map over the primitive array, keeping the elements for which the monadic -- predicate provides a 'Just'. {-# INLINE mapMaybePrimArrayP #-} mapMaybePrimArrayP :: (PrimMonad m, Prim a, Prim b) => (a -> m (Maybe b)) -> PrimArray a -> m (PrimArray b) mapMaybePrimArrayP f arr = do let !sz = sizeofPrimArray arr marr <- newPrimArray sz let go !ixSrc !ixDst = if ixSrc < sz then do let a = indexPrimArray arr ixSrc mb <- f a case mb of Just b -> do writePrimArray marr ixDst b go (ixSrc + 1) (ixDst + 1) Nothing -> go (ixSrc + 1) ixDst else return ixDst lenDst <- go 0 0 marr' <- resizeMutablePrimArray marr lenDst unsafeFreezePrimArray marr' -- | Generate a primitive array by evaluating the monadic generator function -- at each index. {-# INLINE generatePrimArrayP #-} generatePrimArrayP :: (PrimMonad m, Prim a) => Int -- ^ length -> (Int -> m a) -- ^ generator -> m (PrimArray a) generatePrimArrayP sz f = do marr <- newPrimArray sz let go !ix = if ix < sz then do b <- f ix writePrimArray marr ix b go (ix + 1) else return () go 0 unsafeFreezePrimArray marr -- | Execute the monadic action the given number of times and store the -- results in a primitive array. {-# INLINE replicatePrimArrayP #-} replicatePrimArrayP :: (PrimMonad m, Prim a) => Int -> m a -> m (PrimArray a) replicatePrimArrayP sz f = do marr <- newPrimArray sz let go !ix = if ix < sz then do b <- f writePrimArray marr ix b go (ix + 1) else return () go 0 unsafeFreezePrimArray marr -- | Map over the elements of a primitive array. {-# INLINE mapPrimArray #-} mapPrimArray :: (Prim a, Prim b) => (a -> b) -> PrimArray a -> PrimArray b mapPrimArray f arr = runST $ do let !sz = sizeofPrimArray arr marr <- newPrimArray sz let go !ix = if ix < sz then do let b = f (indexPrimArray arr ix) writePrimArray marr ix b go (ix + 1) else return () go 0 unsafeFreezePrimArray marr -- | Indexed map over the elements of a primitive array. {-# INLINE imapPrimArray #-} imapPrimArray :: (Prim a, Prim b) => (Int -> a -> b) -> PrimArray a -> PrimArray b imapPrimArray f arr = runST $ do let !sz = sizeofPrimArray arr marr <- newPrimArray sz let go !ix = if ix < sz then do let b = f ix (indexPrimArray arr ix) writePrimArray marr ix b go (ix + 1) else return () go 0 unsafeFreezePrimArray marr -- | Filter elements of a primitive array according to a predicate. {-# INLINE filterPrimArray #-} filterPrimArray :: Prim a => (a -> Bool) -> PrimArray a -> PrimArray a filterPrimArray p arr = runST $ do let !sz = sizeofPrimArray arr marr <- newPrimArray sz let go !ixSrc !ixDst = if ixSrc < sz then do let !a = indexPrimArray arr ixSrc if p a then do writePrimArray marr ixDst a go (ixSrc + 1) (ixDst + 1) else go (ixSrc + 1) ixDst else return ixDst dstLen <- go 0 0 marr' <- resizeMutablePrimArray marr dstLen unsafeFreezePrimArray marr' -- | Filter the primitive array, keeping the elements for which the monadic -- predicate evaluates true. filterPrimArrayA :: (Applicative f, Prim a) => (a -> f Bool) -- ^ mapping function -> PrimArray a -- ^ primitive array -> f (PrimArray a) filterPrimArrayA f = \ !ary -> let !len = sizeofPrimArray ary go !ixSrc | ixSrc == len = pure $ IxSTA $ \ixDst _ -> return ixDst | otherwise = let x = indexPrimArray ary ixSrc in liftA2 (\keep (IxSTA m) -> IxSTA $ \ixDst mary -> if keep then writePrimArray (MutablePrimArray mary) ixDst x >> m (ixDst + 1) mary else m ixDst mary ) (f x) (go (ixSrc + 1)) in if len == 0 then pure emptyPrimArray else runIxSTA len <$> go 0 -- | Map over the primitive array, keeping the elements for which the applicative -- predicate provides a 'Just'. mapMaybePrimArrayA :: (Applicative f, Prim a, Prim b) => (a -> f (Maybe b)) -- ^ mapping function -> PrimArray a -- ^ primitive array -> f (PrimArray b) mapMaybePrimArrayA f = \ !ary -> let !len = sizeofPrimArray ary go !ixSrc | ixSrc == len = pure $ IxSTA $ \ixDst _ -> return ixDst | otherwise = let x = indexPrimArray ary ixSrc in liftA2 (\mb (IxSTA m) -> IxSTA $ \ixDst mary -> case mb of Just b -> writePrimArray (MutablePrimArray mary) ixDst b >> m (ixDst + 1) mary Nothing -> m ixDst mary ) (f x) (go (ixSrc + 1)) in if len == 0 then pure emptyPrimArray else runIxSTA len <$> go 0 -- | Map over a primitive array, optionally discarding some elements. This -- has the same behavior as @Data.Maybe.mapMaybe@. {-# INLINE mapMaybePrimArray #-} mapMaybePrimArray :: (Prim a, Prim b) => (a -> Maybe b) -> PrimArray a -> PrimArray b mapMaybePrimArray p arr = runST $ do let !sz = sizeofPrimArray arr marr <- newPrimArray sz let go !ixSrc !ixDst = if ixSrc < sz then do let !a = indexPrimArray arr ixSrc case p a of Just b -> do writePrimArray marr ixDst b go (ixSrc + 1) (ixDst + 1) Nothing -> go (ixSrc + 1) ixDst else return ixDst dstLen <- go 0 0 marr' <- resizeMutablePrimArray marr dstLen unsafeFreezePrimArray marr' -- | Traverse a primitive array. The traversal performs all of the applicative -- effects /before/ forcing the resulting values and writing them to the new -- primitive array. Consequently: -- -- >>> traversePrimArray (\x -> print x $> bool x undefined (x == 2)) (fromList [1, 2, 3 :: Int]) -- 1 -- 2 -- 3 -- *** Exception: Prelude.undefined -- -- The function 'traversePrimArrayP' always outperforms this function, but it -- requires a 'PrimMonad' constraint, and it forces the values as -- it performs the effects. traversePrimArray :: (Applicative f, Prim a, Prim b) => (a -> f b) -- ^ mapping function -> PrimArray a -- ^ primitive array -> f (PrimArray b) traversePrimArray f = \ !ary -> let !len = sizeofPrimArray ary go !i | i == len = pure $ STA $ \mary -> unsafeFreezePrimArray (MutablePrimArray mary) | x <- indexPrimArray ary i = liftA2 (\b (STA m) -> STA $ \mary -> writePrimArray (MutablePrimArray mary) i b >> m mary) (f x) (go (i + 1)) in if len == 0 then pure emptyPrimArray else runSTA len <$> go 0 -- | Traverse a primitive array with the index of each element. itraversePrimArray :: (Applicative f, Prim a, Prim b) => (Int -> a -> f b) -> PrimArray a -> f (PrimArray b) itraversePrimArray f = \ !ary -> let !len = sizeofPrimArray ary go !i | i == len = pure $ STA $ \mary -> unsafeFreezePrimArray (MutablePrimArray mary) | x <- indexPrimArray ary i = liftA2 (\b (STA m) -> STA $ \mary -> writePrimArray (MutablePrimArray mary) i b >> m mary) (f i x) (go (i + 1)) in if len == 0 then pure emptyPrimArray else runSTA len <$> go 0 -- | Traverse a primitive array with the indices. The traversal forces the -- resulting values and writes them to the new primitive array as it performs -- the monadic effects. {-# INLINE itraversePrimArrayP #-} itraversePrimArrayP :: (Prim a, Prim b, PrimMonad m) => (Int -> a -> m b) -> PrimArray a -> m (PrimArray b) itraversePrimArrayP f arr = do let !sz = sizeofPrimArray arr marr <- newPrimArray sz let go !ix | ix < sz = do writePrimArray marr ix =<< f ix (indexPrimArray arr ix) go (ix + 1) | otherwise = return () go 0 unsafeFreezePrimArray marr -- | Generate a primitive array. {-# INLINE generatePrimArray #-} generatePrimArray :: Prim a => Int -- ^ length -> (Int -> a) -- ^ element from index -> PrimArray a generatePrimArray len f = runST $ do marr <- newPrimArray len let go !ix = if ix < len then do writePrimArray marr ix (f ix) go (ix + 1) else return () go 0 unsafeFreezePrimArray marr -- | Create a primitive array by copying the element the given -- number of times. {-# INLINE replicatePrimArray #-} replicatePrimArray :: Prim a => Int -- ^ length -> a -- ^ element -> PrimArray a replicatePrimArray len a = runST $ do marr <- newPrimArray len setPrimArray marr 0 len a unsafeFreezePrimArray marr -- | Generate a primitive array by evaluating the applicative generator -- function at each index. {-# INLINE generatePrimArrayA #-} generatePrimArrayA :: (Applicative f, Prim a) => Int -- ^ length -> (Int -> f a) -- ^ element from index -> f (PrimArray a) generatePrimArrayA len f = let go !i | i == len = pure $ STA $ \mary -> unsafeFreezePrimArray (MutablePrimArray mary) | otherwise = liftA2 (\b (STA m) -> STA $ \mary -> writePrimArray (MutablePrimArray mary) i b >> m mary) (f i) (go (i + 1)) in if len == 0 then pure emptyPrimArray else runSTA len <$> go 0 -- | Execute the applicative action the given number of times and store the -- results in a 'PrimArray'. {-# INLINE replicatePrimArrayA #-} replicatePrimArrayA :: (Applicative f, Prim a) => Int -- ^ length -> f a -- ^ applicative element producer -> f (PrimArray a) replicatePrimArrayA len f = let go !i | i == len = pure $ STA $ \mary -> unsafeFreezePrimArray (MutablePrimArray mary) | otherwise = liftA2 (\b (STA m) -> STA $ \mary -> writePrimArray (MutablePrimArray mary) i b >> m mary) f (go (i + 1)) in if len == 0 then pure emptyPrimArray else runSTA len <$> go 0 -- | Traverse the primitive array, discarding the results. There -- is no 'PrimMonad' variant of this function, since it would not provide -- any performance benefit. traversePrimArray_ :: (Applicative f, Prim a) => (a -> f b) -> PrimArray a -> f () traversePrimArray_ f a = go 0 where !sz = sizeofPrimArray a go !ix = if ix < sz then f (indexPrimArray a ix) *> go (ix + 1) else pure () -- | Traverse the primitive array with the indices, discarding the results. -- There is no 'PrimMonad' variant of this function, since it would not -- provide any performance benefit. itraversePrimArray_ :: (Applicative f, Prim a) => (Int -> a -> f b) -> PrimArray a -> f () itraversePrimArray_ f a = go 0 where !sz = sizeofPrimArray a go !ix = if ix < sz then f ix (indexPrimArray a ix) *> go (ix + 1) else pure () newtype IxSTA a = IxSTA {_runIxSTA :: forall s. Int -> MutableByteArray# s -> ST s Int} runIxSTA :: forall a. Prim a => Int -- maximum possible size -> IxSTA a -> PrimArray a runIxSTA !szUpper = \ (IxSTA m) -> runST $ do ar :: MutablePrimArray s a <- newPrimArray szUpper sz <- m 0 (unMutablePrimArray ar) ar' <- resizeMutablePrimArray ar sz unsafeFreezePrimArray ar' {-# INLINE runIxSTA #-} newtype STA a = STA {_runSTA :: forall s. MutableByteArray# s -> ST s (PrimArray a)} runSTA :: forall a. Prim a => Int -> STA a -> PrimArray a runSTA !sz = \ (STA m) -> runST $ newPrimArray sz >>= \ (ar :: MutablePrimArray s a) -> m (unMutablePrimArray ar) {-# INLINE runSTA #-} unMutablePrimArray :: MutablePrimArray s a -> MutableByteArray# s unMutablePrimArray (MutablePrimArray m) = m {- $effectfulMapCreate The naming conventions adopted in this section are explained in the documentation of the @Data.Primitive@ module. -} -- | Create a /pinned/ primitive array of the specified size (in elements). The garbage -- collector is guaranteed not to move it. -- -- @since 0.7.1.0 newPinnedPrimArray :: forall m a. (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) {-# INLINE newPinnedPrimArray #-} newPinnedPrimArray (I# n#) = primitive (\s# -> case newPinnedByteArray# (n# *# sizeOf# (undefined :: a)) s# of (# s'#, arr# #) -> (# s'#, MutablePrimArray arr# #)) -- | Create a /pinned/ primitive array of the specified size (in elements) and -- with the alignment given by its 'Prim' instance. The garbage collector is -- guaranteed not to move it. -- -- @since 0.7.0.0 newAlignedPinnedPrimArray :: forall m a. (PrimMonad m, Prim a) => Int -> m (MutablePrimArray (PrimState m) a) {-# INLINE newAlignedPinnedPrimArray #-} newAlignedPinnedPrimArray (I# n#) = primitive (\s# -> case newAlignedPinnedByteArray# (n# *# sizeOf# (undefined :: a)) (alignment# (undefined :: a)) s# of (# s'#, arr# #) -> (# s'#, MutablePrimArray arr# #)) -- | Yield a pointer to the array's data. This operation is only safe on -- /pinned/ prim arrays allocated by 'newPinnedByteArray' or -- 'newAlignedPinnedByteArray'. -- -- @since 0.7.1.0 primArrayContents :: PrimArray a -> Ptr a {-# INLINE primArrayContents #-} primArrayContents (PrimArray arr#) = Ptr (byteArrayContents# arr#) -- | Yield a pointer to the array's data. This operation is only safe on -- /pinned/ byte arrays allocated by 'newPinnedByteArray' or -- 'newAlignedPinnedByteArray'. -- -- @since 0.7.1.0 mutablePrimArrayContents :: MutablePrimArray s a -> Ptr a {-# INLINE mutablePrimArrayContents #-} mutablePrimArrayContents (MutablePrimArray arr#) = Ptr (byteArrayContents# (unsafeCoerce# arr#)) -- | Return a newly allocated array with the specified subrange of the -- provided array. The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. clonePrimArray :: Prim a => PrimArray a -- ^ source array -> Int -- ^ offset into destination array -> Int -- ^ number of elements to copy -> PrimArray a {-# INLINE clonePrimArray #-} clonePrimArray src off n = runPrimArray $ do dst <- newPrimArray n copyPrimArray dst 0 src off n return dst -- | Return a newly allocated mutable array with the specified subrange of -- the provided mutable array. The provided mutable array should contain the -- full subrange specified by the two Ints, but this is not checked. cloneMutablePrimArray :: (PrimMonad m, Prim a) => MutablePrimArray (PrimState m) a -- ^ source array -> Int -- ^ offset into destination array -> Int -- ^ number of elements to copy -> m (MutablePrimArray (PrimState m) a) {-# INLINE cloneMutablePrimArray #-} cloneMutablePrimArray src off n = do dst <- newPrimArray n copyMutablePrimArray dst 0 src off n return dst -- | Execute the monadic action and freeze the resulting array. -- -- > runPrimArray m = runST $ m >>= unsafeFreezePrimArray runPrimArray :: (forall s. ST s (MutablePrimArray s a)) -> PrimArray a #if MIN_VERSION_base(4,10,0) /* In new GHCs, runRW# is available. */ runPrimArray m = PrimArray (runPrimArray# m) runPrimArray# :: (forall s. ST s (MutablePrimArray s a)) -> ByteArray# runPrimArray# m = case runRW# $ \s -> case unST m s of { (# s', MutablePrimArray mary# #) -> unsafeFreezeByteArray# mary# s'} of (# _, ary# #) -> ary# unST :: ST s a -> State# s -> (# State# s, a #) unST (GHCST.ST f) = f #else /* In older GHCs, runRW# is not available. */ runPrimArray m = runST $ m >>= unsafeFreezePrimArray #endif primitive-0.8.0.0/Data/Primitive/PrimVar.hs0000644000000000000000000001562707346545000016626 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE RoleAnnotations #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE Unsafe #-} -- | Variant of @MutVar@ that has one less indirection for primitive types. -- The difference is illustrated by comparing @MutVar Int@ and @PrimVar Int@: -- -- * @MutVar Int@: @MutVar# --> I#@ -- * @PrimVar Int@: @MutableByteArray#@ -- -- This module is adapted from a module in Edward Kmett\'s @prim-ref@ library. module Data.Primitive.PrimVar ( -- * Primitive References PrimVar(..) , newPrimVar , newPinnedPrimVar , newAlignedPinnedPrimVar , readPrimVar , writePrimVar , modifyPrimVar , primVarContents , primVarToMutablePrimArray -- * Atomic Operations -- $atomic , casInt , fetchAddInt , fetchSubInt , fetchAndInt , fetchNandInt , fetchOrInt , fetchXorInt , atomicReadInt , atomicWriteInt ) where import Control.Monad.Primitive import Data.Primitive import GHC.Exts import GHC.Ptr (castPtr) -------------------------------------------------------------------------------- -- * Primitive References -------------------------------------------------------------------------------- -- | A 'PrimVar' behaves like a single-element mutable primitive array. newtype PrimVar s a = PrimVar (MutablePrimArray s a) type role PrimVar nominal nominal -- | Create a primitive reference. newPrimVar :: (PrimMonad m, Prim a) => a -> m (PrimVar (PrimState m) a) newPrimVar a = do m <- newPrimArray 1 writePrimArray m 0 a return (PrimVar m) {-# INLINE newPrimVar #-} -- | Create a pinned primitive reference. newPinnedPrimVar :: (PrimMonad m, Prim a) => a -> m (PrimVar (PrimState m) a) newPinnedPrimVar a = do m <- newPinnedPrimArray 1 writePrimArray m 0 a return (PrimVar m) {-# INLINE newPinnedPrimVar #-} -- | Create a pinned primitive reference with the appropriate alignment for its contents. newAlignedPinnedPrimVar :: (PrimMonad m, Prim a) => a -> m (PrimVar (PrimState m) a) newAlignedPinnedPrimVar a = do m <- newAlignedPinnedPrimArray 1 writePrimArray m 0 a return (PrimVar m) {-# INLINE newAlignedPinnedPrimVar #-} -- | Read a value from the 'PrimVar'. readPrimVar :: (PrimMonad m, Prim a) => PrimVar (PrimState m) a -> m a readPrimVar (PrimVar m) = readPrimArray m 0 {-# INLINE readPrimVar #-} -- | Write a value to the 'PrimVar'. writePrimVar :: (PrimMonad m, Prim a) => PrimVar (PrimState m) a -> a -> m () writePrimVar (PrimVar m) a = writePrimArray m 0 a {-# INLINE writePrimVar #-} -- | Mutate the contents of a 'PrimVar'. modifyPrimVar :: (PrimMonad m, Prim a) => PrimVar (PrimState m) a -> (a -> a) -> m () modifyPrimVar pv f = do x <- readPrimVar pv writePrimVar pv (f x) {-# INLINE modifyPrimVar #-} instance Eq (PrimVar s a) where PrimVar m == PrimVar n = sameMutablePrimArray m n {-# INLINE (==) #-} -- | Yield a pointer to the data of a 'PrimVar'. This operation is only safe on pinned byte arrays allocated by -- 'newPinnedPrimVar' or 'newAlignedPinnedPrimVar'. primVarContents :: PrimVar s a -> Ptr a primVarContents (PrimVar m) = castPtr $ mutablePrimArrayContents m {-# INLINE primVarContents #-} -- | Convert a 'PrimVar' to a one-elment 'MutablePrimArray'. primVarToMutablePrimArray :: PrimVar s a -> MutablePrimArray s a primVarToMutablePrimArray (PrimVar m) = m {-# INLINE primVarToMutablePrimArray #-} -------------------------------------------------------------------------------- -- * Atomic Operations -------------------------------------------------------------------------------- -- $atomic -- Atomic operations on `PrimVar s Int`. All atomic operations imply a full memory barrier. -- | Given a primitive reference, the expected old value, and the new value, perform an atomic compare and swap i.e. write the new value if the current value matches the provided old value. Returns the value of the element before the operation. casInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> Int -> m Int casInt (PrimVar (MutablePrimArray m)) (I# old) (I# new) = primitive $ \s -> case casIntArray# m 0# old new s of (# s', result #) -> (# s', I# result #) {-# INLINE casInt #-} -- | Given a reference, and a value to add, atomically add the value to the element. Returns the value of the element before the operation. fetchAddInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int fetchAddInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchAddIntArray# m 0# x s of (# s', result #) -> (# s', I# result #) {-# INLINE fetchAddInt #-} -- | Given a reference, and a value to subtract, atomically subtract the value from the element. Returns the value of the element before the operation. fetchSubInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int fetchSubInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchSubIntArray# m 0# x s of (# s', result #) -> (# s', I# result #) {-# INLINE fetchSubInt #-} -- | Given a reference, and a value to bitwise and, atomically and the value with the element. Returns the value of the element before the operation. fetchAndInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int fetchAndInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchAndIntArray# m 0# x s of (# s', result #) -> (# s', I# result #) {-# INLINE fetchAndInt #-} -- | Given a reference, and a value to bitwise nand, atomically nand the value with the element. Returns the value of the element before the operation. fetchNandInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int fetchNandInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchNandIntArray# m 0# x s of (# s', result #) -> (# s', I# result #) {-# INLINE fetchNandInt #-} -- | Given a reference, and a value to bitwise or, atomically or the value with the element. Returns the value of the element before the operation. fetchOrInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int fetchOrInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchOrIntArray# m 0# x s of (# s', result #) -> (# s', I# result #) {-# INLINE fetchOrInt #-} -- | Given a reference, and a value to bitwise xor, atomically xor the value with the element. Returns the value of the element before the operation. fetchXorInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m Int fetchXorInt (PrimVar (MutablePrimArray m)) (I# x) = primitive $ \s -> case fetchXorIntArray# m 0# x s of (# s', result #) -> (# s', I# result #) {-# INLINE fetchXorInt #-} -- | Given a reference, atomically read an element. atomicReadInt :: PrimMonad m => PrimVar (PrimState m) Int -> m Int atomicReadInt (PrimVar (MutablePrimArray m)) = primitive $ \s -> case atomicReadIntArray# m 0# s of (# s', result #) -> (# s', I# result #) {-# INLINE atomicReadInt #-} -- | Given a reference, atomically write an element. atomicWriteInt :: PrimMonad m => PrimVar (PrimState m) Int -> Int -> m () atomicWriteInt (PrimVar (MutablePrimArray m)) (I# x) = primitive_ $ \s -> atomicWriteIntArray# m 0# x s {-# INLINE atomicWriteInt #-} primitive-0.8.0.0/Data/Primitive/Ptr.hs0000644000000000000000000000665507346545000016014 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE ScopedTypeVariables #-} -- | -- Module : Data.Primitive.Ptr -- Copyright : (c) Roman Leshchinskiy 2009-2012 -- License : BSD-style -- -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- -- Primitive operations on machine addresses. -- -- @since 0.6.4.0 module Data.Primitive.Ptr ( -- * Types Ptr(..), -- * Address arithmetic nullPtr, advancePtr, subtractPtr, -- * Element access indexOffPtr, readOffPtr, writeOffPtr, -- * Block operations copyPtr, movePtr, setPtr , copyPtrToMutablePrimArray , copyPtrToMutableByteArray ) where import Control.Monad.Primitive import Data.Primitive.Types import Data.Primitive.PrimArray (copyPtrToMutablePrimArray) import Data.Primitive.ByteArray (copyPtrToMutableByteArray) import GHC.Exts import GHC.Ptr import Foreign.Marshal.Utils -- | Offset a pointer by the given number of elements. advancePtr :: forall a. Prim a => Ptr a -> Int -> Ptr a {-# INLINE advancePtr #-} advancePtr (Ptr a#) (I# i#) = Ptr (plusAddr# a# (i# *# sizeOf# (undefined :: a))) -- | Subtract a pointer from another pointer. The result represents -- the number of elements of type @a@ that fit in the contiguous -- memory range bounded by these two pointers. subtractPtr :: forall a. Prim a => Ptr a -> Ptr a -> Int {-# INLINE subtractPtr #-} subtractPtr (Ptr a#) (Ptr b#) = I# (quotInt# (minusAddr# a# b#) (sizeOf# (undefined :: a))) -- | Read a value from a memory position given by a pointer and an offset. -- The memory block the address refers to must be immutable. The offset is in -- elements of type @a@ rather than in bytes. indexOffPtr :: Prim a => Ptr a -> Int -> a {-# INLINE indexOffPtr #-} indexOffPtr (Ptr addr#) (I# i#) = indexOffAddr# addr# i# -- | Read a value from a memory position given by an address and an offset. -- The offset is in elements of type @a@ rather than in bytes. readOffPtr :: (Prim a, PrimMonad m) => Ptr a -> Int -> m a {-# INLINE readOffPtr #-} readOffPtr (Ptr addr#) (I# i#) = primitive (readOffAddr# addr# i#) -- | Write a value to a memory position given by an address and an offset. -- The offset is in elements of type @a@ rather than in bytes. writeOffPtr :: (Prim a, PrimMonad m) => Ptr a -> Int -> a -> m () {-# INLINE writeOffPtr #-} writeOffPtr (Ptr addr#) (I# i#) x = primitive_ (writeOffAddr# addr# i# x) -- | Copy the given number of elements from the second 'Ptr' to the first. The -- areas may not overlap. copyPtr :: forall m a. (PrimMonad m, Prim a) => Ptr a -- ^ destination pointer -> Ptr a -- ^ source pointer -> Int -- ^ number of elements -> m () {-# INLINE copyPtr #-} copyPtr (Ptr dst#) (Ptr src#) n = unsafePrimToPrim $ copyBytes (Ptr dst#) (Ptr src#) (n * sizeOf (undefined :: a)) -- | Copy the given number of elements from the second 'Ptr' to the first. The -- areas may overlap. movePtr :: forall m a. (PrimMonad m, Prim a) => Ptr a -- ^ destination pointer -> Ptr a -- ^ source pointer -> Int -- ^ number of elements -> m () {-# INLINE movePtr #-} movePtr (Ptr dst#) (Ptr src#) n = unsafePrimToPrim $ moveBytes (Ptr dst#) (Ptr src#) (n * sizeOf (undefined :: a)) -- | Fill a memory block with the given value. The length is in -- elements of type @a@ rather than in bytes. setPtr :: (Prim a, PrimMonad m) => Ptr a -> Int -> a -> m () {-# INLINE setPtr #-} setPtr (Ptr addr#) (I# n#) x = primitive_ (setOffAddr# addr# 0# n# x) primitive-0.8.0.0/Data/Primitive/SmallArray.hs0000644000000000000000000007430307346545000017311 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE DeriveTraversable #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE BangPatterns #-} {-# LANGUAGE TemplateHaskellQuotes #-} -- | -- Module : Data.Primitive.SmallArray -- Copyright: (c) 2015 Dan Doel -- License: BSD3 -- -- Maintainer: libraries@haskell.org -- Portability: non-portable -- -- Small arrays are boxed (im)mutable arrays. -- -- The underlying structure of the 'Data.Primitive.Array.Array' type contains a card table, allowing -- segments of the array to be marked as having been mutated. This allows the -- garbage collector to only re-traverse segments of the array that have been -- marked during certain phases, rather than having to traverse the entire -- array. -- -- 'SmallArray' lacks this table. This means that it takes up less memory and -- has slightly faster writes. It is also more efficient during garbage -- collection so long as the card table would have a single entry covering the -- entire array. These advantages make them suitable for use as arrays that are -- known to be small. -- -- The card size is 128, so for uses much larger than that, -- 'Data.Primitive.Array.Array' would likely be superior. module Data.Primitive.SmallArray ( SmallArray(..) , SmallMutableArray(..) , newSmallArray , readSmallArray , writeSmallArray , copySmallArray , copySmallMutableArray , indexSmallArray , indexSmallArrayM , indexSmallArray## , cloneSmallArray , cloneSmallMutableArray , freezeSmallArray , unsafeFreezeSmallArray , thawSmallArray , unsafeThawSmallArray , runSmallArray , createSmallArray , sizeofSmallArray , sizeofSmallMutableArray #if MIN_VERSION_base(4,14,0) , shrinkSmallMutableArray , resizeSmallMutableArray #endif , emptySmallArray , smallArrayFromList , smallArrayFromListN , mapSmallArray' , traverseSmallArrayP ) where import GHC.Exts hiding (toList) import qualified GHC.Exts import Control.Applicative import Control.DeepSeq import Control.Monad import qualified Control.Monad.Fail as Fail import Control.Monad.Fix import Control.Monad.Primitive import Control.Monad.ST import Control.Monad.Zip import Data.Data import Data.Foldable as Foldable import Data.Functor.Identity import qualified GHC.ST as GHCST import qualified Data.Semigroup as Sem import Text.ParserCombinators.ReadP #if !MIN_VERSION_base(4,10,0) import GHC.Base (runRW#) #endif import Data.Functor.Classes (Eq1(..), Ord1(..), Show1(..), Read1(..)) import Language.Haskell.TH.Syntax (Lift(..)) data SmallArray a = SmallArray (SmallArray# a) deriving Typeable #if MIN_VERSION_deepseq(1,4,3) instance NFData1 SmallArray where liftRnf r = foldl' (\_ -> r) () #endif instance NFData a => NFData (SmallArray a) where rnf = foldl' (\_ -> rnf) () data SmallMutableArray s a = SmallMutableArray (SmallMutableArray# s a) deriving Typeable instance Lift a => Lift (SmallArray a) where #if MIN_VERSION_template_haskell(2,16,0) liftTyped ary = case lst of [] -> [|| SmallArray (emptySmallArray# (##)) ||] [x] -> [|| pure $! x ||] x : xs -> [|| unsafeSmallArrayFromListN' len x xs ||] #else lift ary = case lst of [] -> [| SmallArray (emptySmallArray# (##)) |] [x] -> [| pure $! x |] x : xs -> [| unsafeSmallArrayFromListN' len x xs |] #endif where len = length ary lst = toList ary -- | Strictly create an array from a nonempty list (represented as -- a first element and a list of the rest) of a known length. If the length -- of the list does not match the given length, this makes demons fly -- out of your nose. We use it in the 'Lift' instance. If you edit the -- splice and break it, you get to keep both pieces. unsafeSmallArrayFromListN' :: Int -> a -> [a] -> SmallArray a unsafeSmallArrayFromListN' n y ys = createSmallArray n y $ \sma -> let go !_ix [] = return () go !ix (!x : xs) = do writeSmallArray sma ix x go (ix+1) xs in go 1 ys -- | Create a new small mutable array. -- -- /Note:/ this function does not check if the input is non-negative. newSmallArray :: PrimMonad m => Int -- ^ size -> a -- ^ initial contents -> m (SmallMutableArray (PrimState m) a) newSmallArray (I# i#) x = primitive $ \s -> case newSmallArray# i# x s of (# s', sma# #) -> (# s', SmallMutableArray sma# #) {-# INLINE newSmallArray #-} -- | Read the element at a given index in a mutable array. -- -- /Note:/ this function does not do bounds checking. readSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ array -> Int -- ^ index -> m a readSmallArray (SmallMutableArray sma#) (I# i#) = primitive $ readSmallArray# sma# i# {-# INLINE readSmallArray #-} -- | Write an element at the given idex in a mutable array. -- -- /Note:/ this function does not do bounds checking. writeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ array -> Int -- ^ index -> a -- ^ new element -> m () writeSmallArray (SmallMutableArray sma#) (I# i#) x = primitive_ $ writeSmallArray# sma# i# x {-# INLINE writeSmallArray #-} -- | Look up an element in an immutable array. -- -- The purpose of returning a result using a monad is to allow the caller to -- avoid retaining references to the array. Evaluating the return value will -- cause the array lookup to be performed, even though it may not require the -- element of the array to be evaluated (which could throw an exception). For -- instance: -- -- > data Box a = Box a -- > ... -- > -- > f sa = case indexSmallArrayM sa 0 of -- > Box x -> ... -- -- 'x' is not a closure that references 'sa' as it would be if we instead -- wrote: -- -- > let x = indexSmallArray sa 0 -- -- It also does not prevent 'sa' from being garbage collected. -- -- Note that 'Identity' is not adequate for this use, as it is a newtype, and -- cannot be evaluated without evaluating the element. -- -- /Note:/ this function does not do bounds checking. indexSmallArrayM :: Monad m => SmallArray a -- ^ array -> Int -- ^ index -> m a indexSmallArrayM (SmallArray sa#) (I# i#) = case indexSmallArray# sa# i# of (# x #) -> pure x {-# INLINE indexSmallArrayM #-} -- | Look up an element in an immutable array. -- -- /Note:/ this function does not do bounds checking. indexSmallArray :: SmallArray a -- ^ array -> Int -- ^ index -> a indexSmallArray sa i = runIdentity $ indexSmallArrayM sa i {-# INLINE indexSmallArray #-} -- | Read a value from the immutable array at the given index, returning -- the result in an unboxed unary tuple. This is currently used to implement -- folds. -- -- /Note:/ this function does not do bounds checking. indexSmallArray## :: SmallArray a -> Int -> (# a #) indexSmallArray## (SmallArray ary) (I# i) = indexSmallArray# ary i {-# INLINE indexSmallArray## #-} -- | Create a copy of a slice of an immutable array. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. cloneSmallArray :: SmallArray a -- ^ source -> Int -- ^ offset -> Int -- ^ length -> SmallArray a cloneSmallArray (SmallArray sa#) (I# i#) (I# j#) = SmallArray (cloneSmallArray# sa# i# j#) {-# INLINE cloneSmallArray #-} -- | Create a copy of a slice of a mutable array. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. cloneSmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ source -> Int -- ^ offset -> Int -- ^ length -> m (SmallMutableArray (PrimState m) a) cloneSmallMutableArray (SmallMutableArray sma#) (I# o#) (I# l#) = primitive $ \s -> case cloneSmallMutableArray# sma# o# l# s of (# s', smb# #) -> (# s', SmallMutableArray smb# #) {-# INLINE cloneSmallMutableArray #-} -- | Create an immutable array corresponding to a slice of a mutable array. -- -- This operation copies the portion of the array to be frozen. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. freezeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ source -> Int -- ^ offset -> Int -- ^ length -> m (SmallArray a) freezeSmallArray (SmallMutableArray sma#) (I# i#) (I# j#) = primitive $ \s -> case freezeSmallArray# sma# i# j# s of (# s', sa# #) -> (# s', SmallArray sa# #) {-# INLINE freezeSmallArray #-} -- | Render a mutable array immutable. -- -- This operation performs no copying, so care must be taken not to modify the -- input array after freezing. unsafeFreezeSmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> m (SmallArray a) unsafeFreezeSmallArray (SmallMutableArray sma#) = primitive $ \s -> case unsafeFreezeSmallArray# sma# s of (# s', sa# #) -> (# s', SmallArray sa# #) {-# INLINE unsafeFreezeSmallArray #-} -- | Create a mutable array corresponding to a slice of an immutable array. -- -- This operation copies the portion of the array to be thawed. -- -- /Note:/ The provided array should contain the full subrange -- specified by the two Ints, but this is not checked. thawSmallArray :: PrimMonad m => SmallArray a -- ^ source -> Int -- ^ offset -> Int -- ^ length -> m (SmallMutableArray (PrimState m) a) thawSmallArray (SmallArray sa#) (I# o#) (I# l#) = primitive $ \s -> case thawSmallArray# sa# o# l# s of (# s', sma# #) -> (# s', SmallMutableArray sma# #) {-# INLINE thawSmallArray #-} -- | Render an immutable array mutable. -- -- This operation performs no copying, so care must be taken with its use. unsafeThawSmallArray :: PrimMonad m => SmallArray a -> m (SmallMutableArray (PrimState m) a) unsafeThawSmallArray (SmallArray sa#) = primitive $ \s -> case unsafeThawSmallArray# sa# s of (# s', sma# #) -> (# s', SmallMutableArray sma# #) {-# INLINE unsafeThawSmallArray #-} -- | Copy a slice of an immutable array into a mutable array. -- -- /Note:/ this function does not do bounds or overlap checking. copySmallArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ destination -> Int -- ^ destination offset -> SmallArray a -- ^ source -> Int -- ^ source offset -> Int -- ^ length -> m () copySmallArray (SmallMutableArray dst#) (I# do#) (SmallArray src#) (I# so#) (I# l#) = primitive_ $ copySmallArray# src# so# dst# do# l# {-# INLINE copySmallArray #-} -- | Copy a slice of one mutable array into another. -- -- /Note:/ this function does not do bounds or overlap checking. copySmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -- ^ destination -> Int -- ^ destination offset -> SmallMutableArray (PrimState m) a -- ^ source -> Int -- ^ source offset -> Int -- ^ length -> m () copySmallMutableArray (SmallMutableArray dst#) (I# do#) (SmallMutableArray src#) (I# so#) (I# l#) = primitive_ $ copySmallMutableArray# src# so# dst# do# l# {-# INLINE copySmallMutableArray #-} -- | The number of elements in an immutable array. sizeofSmallArray :: SmallArray a -> Int sizeofSmallArray (SmallArray sa#) = I# (sizeofSmallArray# sa#) {-# INLINE sizeofSmallArray #-} -- | The number of elements in a mutable array. sizeofSmallMutableArray :: SmallMutableArray s a -> Int sizeofSmallMutableArray (SmallMutableArray sa#) = I# (sizeofSmallMutableArray# sa#) {-# INLINE sizeofSmallMutableArray #-} -- | This is the fastest, most straightforward way to traverse -- an array, but it only works correctly with a sufficiently -- "affine" 'PrimMonad' instance. In particular, it must only produce -- /one/ result array. 'Control.Monad.Trans.List.ListT'-transformed -- monads, for example, will not work right at all. traverseSmallArrayP :: PrimMonad m => (a -> m b) -> SmallArray a -> m (SmallArray b) traverseSmallArrayP f = \ !ary -> let !sz = sizeofSmallArray ary go !i !mary | i == sz = unsafeFreezeSmallArray mary | otherwise = do a <- indexSmallArrayM ary i b <- f a writeSmallArray mary i b go (i + 1) mary in do mary <- newSmallArray sz badTraverseValue go 0 mary {-# INLINE traverseSmallArrayP #-} -- | Strict map over the elements of the array. mapSmallArray' :: (a -> b) -> SmallArray a -> SmallArray b mapSmallArray' f sa = createSmallArray (length sa) (die "mapSmallArray'" "impossible") $ \smb -> fix ? 0 $ \go i -> when (i < length sa) $ do x <- indexSmallArrayM sa i let !y = f x writeSmallArray smb i y *> go (i + 1) {-# INLINE mapSmallArray' #-} -- | Execute the monadic action and freeze the resulting array. -- -- > runSmallArray m = runST $ m >>= unsafeFreezeSmallArray runSmallArray :: (forall s. ST s (SmallMutableArray s a)) -> SmallArray a -- This low-level business is designed to work with GHC's worker-wrapper -- transformation. A lot of the time, we don't actually need an Array -- constructor. By putting it on the outside, and being careful about -- how we special-case the empty array, we can make GHC smarter about this. -- The only downside is that separately created 0-length arrays won't share -- their Array constructors, although they'll share their underlying -- Array#s. runSmallArray m = SmallArray (runSmallArray# m) runSmallArray# :: (forall s. ST s (SmallMutableArray s a)) -> SmallArray# a runSmallArray# m = case runRW# $ \s -> case unST m s of { (# s', SmallMutableArray mary# #) -> unsafeFreezeSmallArray# mary# s'} of (# _, ary# #) -> ary# unST :: ST s a -> State# s -> (# State# s, a #) unST (GHCST.ST f) = f -- | Create an array of the given size with a default value, -- apply the monadic function and freeze the result. If the -- size is 0, return 'emptySmallArray' (rather than a new copy thereof). -- -- > createSmallArray 0 _ _ = emptySmallArray -- > createSmallArray n x f = runSmallArray $ do -- > mary <- newSmallArray n x -- > f mary -- > pure mary createSmallArray :: Int -> a -> (forall s. SmallMutableArray s a -> ST s ()) -> SmallArray a -- See the comment on runSmallArray for why we use emptySmallArray#. createSmallArray 0 _ _ = SmallArray (emptySmallArray# (# #)) createSmallArray n x f = runSmallArray $ do mary <- newSmallArray n x f mary pure mary emptySmallArray# :: (# #) -> SmallArray# a emptySmallArray# _ = case emptySmallArray of SmallArray ar -> ar {-# NOINLINE emptySmallArray# #-} die :: String -> String -> a die fun problem = error $ "Data.Primitive.SmallArray." ++ fun ++ ": " ++ problem -- | The empty 'SmallArray'. emptySmallArray :: SmallArray a emptySmallArray = runST $ newSmallArray 0 (die "emptySmallArray" "impossible") >>= unsafeFreezeSmallArray {-# NOINLINE emptySmallArray #-} infixl 1 ? (?) :: (a -> b -> c) -> (b -> a -> c) (?) = flip {-# INLINE (?) #-} noOp :: a -> ST s () noOp = const $ pure () smallArrayLiftEq :: (a -> b -> Bool) -> SmallArray a -> SmallArray b -> Bool smallArrayLiftEq p sa1 sa2 = length sa1 == length sa2 && loop (length sa1 - 1) where loop i | i < 0 = True | (# x #) <- indexSmallArray## sa1 i , (# y #) <- indexSmallArray## sa2 i = p x y && loop (i - 1) -- | @since 0.6.4.0 instance Eq1 SmallArray where liftEq = smallArrayLiftEq instance Eq a => Eq (SmallArray a) where sa1 == sa2 = smallArrayLiftEq (==) sa1 sa2 instance Eq (SmallMutableArray s a) where SmallMutableArray sma1# == SmallMutableArray sma2# = isTrue# (sameSmallMutableArray# sma1# sma2#) smallArrayLiftCompare :: (a -> b -> Ordering) -> SmallArray a -> SmallArray b -> Ordering smallArrayLiftCompare elemCompare a1 a2 = loop 0 where mn = length a1 `min` length a2 loop i | i < mn , (# x1 #) <- indexSmallArray## a1 i , (# x2 #) <- indexSmallArray## a2 i = elemCompare x1 x2 `mappend` loop (i + 1) | otherwise = compare (length a1) (length a2) -- | @since 0.6.4.0 instance Ord1 SmallArray where liftCompare = smallArrayLiftCompare -- | Lexicographic ordering. Subject to change between major versions. instance Ord a => Ord (SmallArray a) where compare sa1 sa2 = smallArrayLiftCompare compare sa1 sa2 instance Foldable SmallArray where -- Note: we perform the array lookups eagerly so we won't -- create thunks to perform lookups even if GHC can't see -- that the folding function is strict. foldr f = \z !ary -> let !sz = sizeofSmallArray ary go i | i == sz = z | (# x #) <- indexSmallArray## ary i = f x (go (i + 1)) in go 0 {-# INLINE foldr #-} foldl f = \z !ary -> let go i | i < 0 = z | (# x #) <- indexSmallArray## ary i = f (go (i - 1)) x in go (sizeofSmallArray ary - 1) {-# INLINE foldl #-} foldr1 f = \ !ary -> let !sz = sizeofSmallArray ary - 1 go i = case indexSmallArray## ary i of (# x #) | i == sz -> x | otherwise -> f x (go (i + 1)) in if sz < 0 then die "foldr1" "Empty SmallArray" else go 0 {-# INLINE foldr1 #-} foldl1 f = \ !ary -> let !sz = sizeofSmallArray ary - 1 go i = case indexSmallArray## ary i of (# x #) | i == 0 -> x | otherwise -> f (go (i - 1)) x in if sz < 0 then die "foldl1" "Empty SmallArray" else go sz {-# INLINE foldl1 #-} foldr' f = \z !ary -> let go i !acc | i == -1 = acc | (# x #) <- indexSmallArray## ary i = go (i - 1) (f x acc) in go (sizeofSmallArray ary - 1) z {-# INLINE foldr' #-} foldl' f = \z !ary -> let !sz = sizeofSmallArray ary go i !acc | i == sz = acc | (# x #) <- indexSmallArray## ary i = go (i + 1) (f acc x) in go 0 z {-# INLINE foldl' #-} null a = sizeofSmallArray a == 0 {-# INLINE null #-} length = sizeofSmallArray {-# INLINE length #-} maximum ary | sz == 0 = die "maximum" "Empty SmallArray" | (# frst #) <- indexSmallArray## ary 0 = go 1 frst where sz = sizeofSmallArray ary go i !e | i == sz = e | (# x #) <- indexSmallArray## ary i = go (i + 1) (max e x) {-# INLINE maximum #-} minimum ary | sz == 0 = die "minimum" "Empty SmallArray" | (# frst #) <- indexSmallArray## ary 0 = go 1 frst where sz = sizeofSmallArray ary go i !e | i == sz = e | (# x #) <- indexSmallArray## ary i = go (i + 1) (min e x) {-# INLINE minimum #-} sum = foldl' (+) 0 {-# INLINE sum #-} product = foldl' (*) 1 {-# INLINE product #-} newtype STA a = STA { _runSTA :: forall s. SmallMutableArray# s a -> ST s (SmallArray a) } runSTA :: Int -> STA a -> SmallArray a runSTA !sz = \ (STA m) -> runST $ newSmallArray_ sz >>= \ (SmallMutableArray ar#) -> m ar# {-# INLINE runSTA #-} newSmallArray_ :: Int -> ST s (SmallMutableArray s a) newSmallArray_ !n = newSmallArray n badTraverseValue badTraverseValue :: a badTraverseValue = die "traverse" "bad indexing" {-# NOINLINE badTraverseValue #-} instance Traversable SmallArray where traverse f = traverseSmallArray f {-# INLINE traverse #-} traverseSmallArray :: Applicative f => (a -> f b) -> SmallArray a -> f (SmallArray b) traverseSmallArray f = \ !ary -> let !len = sizeofSmallArray ary go !i | i == len = pure $ STA $ \mary -> unsafeFreezeSmallArray (SmallMutableArray mary) | (# x #) <- indexSmallArray## ary i = liftA2 (\b (STA m) -> STA $ \mary -> writeSmallArray (SmallMutableArray mary) i b >> m mary) (f x) (go (i + 1)) in if len == 0 then pure emptySmallArray else runSTA len <$> go 0 {-# INLINE [1] traverseSmallArray #-} {-# RULES "traverse/ST" forall (f :: a -> ST s b). traverseSmallArray f = traverseSmallArrayP f "traverse/IO" forall (f :: a -> IO b). traverseSmallArray f = traverseSmallArrayP f "traverse/Id" forall (f :: a -> Identity b). traverseSmallArray f = (coerce :: (SmallArray a -> SmallArray (Identity b)) -> SmallArray a -> Identity (SmallArray b)) (fmap f) #-} instance Functor SmallArray where fmap f sa = createSmallArray (length sa) (die "fmap" "impossible") $ \smb -> fix ? 0 $ \go i -> when (i < length sa) $ do x <- indexSmallArrayM sa i writeSmallArray smb i (f x) *> go (i + 1) {-# INLINE fmap #-} x <$ sa = createSmallArray (length sa) x noOp instance Applicative SmallArray where pure x = createSmallArray 1 x noOp sa *> sb = createSmallArray (la * lb) (die "*>" "impossible") $ \smb -> fix ? 0 $ \go i -> when (i < la) $ copySmallArray smb (i * lb) sb 0 lb *> go (i + 1) where la = length sa; lb = length sb a <* b = createSmallArray (sza * szb) (die "<*" "impossible") $ \ma -> let fill off i e = when (i < szb) $ writeSmallArray ma (off + i) e >> fill off (i + 1) e go i = when (i < sza) $ do x <- indexSmallArrayM a i fill (i * szb) 0 x go (i + 1) in go 0 where sza = sizeofSmallArray a; szb = sizeofSmallArray b ab <*> a = createSmallArray (szab * sza) (die "<*>" "impossible") $ \mb -> let go1 i = when (i < szab) $ do f <- indexSmallArrayM ab i go2 (i * sza) f 0 go1 (i + 1) go2 off f j = when (j < sza) $ do x <- indexSmallArrayM a j writeSmallArray mb (off + j) (f x) go2 off f (j + 1) in go1 0 where szab = sizeofSmallArray ab; sza = sizeofSmallArray a instance Alternative SmallArray where empty = emptySmallArray sl <|> sr = createSmallArray (length sl + length sr) (die "<|>" "impossible") $ \sma -> copySmallArray sma 0 sl 0 (length sl) *> copySmallArray sma (length sl) sr 0 (length sr) many sa | null sa = pure [] | otherwise = die "many" "infinite arrays are not well defined" some sa | null sa = emptySmallArray | otherwise = die "some" "infinite arrays are not well defined" data ArrayStack a = PushArray !(SmallArray a) !(ArrayStack a) | EmptyStack -- TODO: This isn't terribly efficient. It would be better to wrap -- ArrayStack with a type like -- -- data NES s a = NES !Int !(SmallMutableArray s a) !(ArrayStack a) -- -- We'd copy incoming arrays into the mutable array until we would -- overflow it. Then we'd freeze it, push it on the stack, and continue. -- Any sufficiently large incoming arrays would go straight on the stack. -- Such a scheme would make the stack much more compact in the case -- of many small arrays. instance Monad SmallArray where return = pure (>>) = (*>) sa >>= f = collect 0 EmptyStack (la - 1) where la = length sa collect sz stk i | i < 0 = createSmallArray sz (die ">>=" "impossible") $ fill 0 stk | (# x #) <- indexSmallArray## sa i , let sb = f x lsb = length sb -- If we don't perform this check, we could end up allocating -- a stack full of empty arrays if someone is filtering most -- things out. So we refrain from pushing empty arrays. = if lsb == 0 then collect sz stk (i - 1) else collect (sz + lsb) (PushArray sb stk) (i - 1) fill _ EmptyStack _ = return () fill off (PushArray sb sbs) smb = copySmallArray smb off sb 0 (length sb) *> fill (off + length sb) sbs smb #if !(MIN_VERSION_base(4,13,0)) fail = Fail.fail #endif instance Fail.MonadFail SmallArray where fail _ = emptySmallArray instance MonadPlus SmallArray where mzero = empty mplus = (<|>) zipW :: String -> (a -> b -> c) -> SmallArray a -> SmallArray b -> SmallArray c zipW nm = \f sa sb -> let mn = length sa `min` length sb in createSmallArray mn (die nm "impossible") $ \mc -> fix ? 0 $ \go i -> when (i < mn) $ do x <- indexSmallArrayM sa i y <- indexSmallArrayM sb i writeSmallArray mc i (f x y) go (i + 1) {-# INLINE zipW #-} instance MonadZip SmallArray where mzip = zipW "mzip" (,) mzipWith = zipW "mzipWith" {-# INLINE mzipWith #-} munzip sab = runST $ do let sz = length sab sma <- newSmallArray sz $ die "munzip" "impossible" smb <- newSmallArray sz $ die "munzip" "impossible" fix ? 0 $ \go i -> when (i < sz) $ case indexSmallArray sab i of (x, y) -> do writeSmallArray sma i x writeSmallArray smb i y go (i + 1) (,) <$> unsafeFreezeSmallArray sma <*> unsafeFreezeSmallArray smb instance MonadFix SmallArray where mfix f = createSmallArray (sizeofSmallArray (f err)) (die "mfix" "impossible") $ fix ? 0 $ \r !i !mary -> when (i < sz) $ do writeSmallArray mary i (fix (\xi -> f xi `indexSmallArray` i)) r (i + 1) mary where sz = sizeofSmallArray (f err) err = error "mfix for Data.Primitive.SmallArray applied to strict function." -- | @since 0.6.3.0 instance Sem.Semigroup (SmallArray a) where (<>) = (<|>) sconcat = mconcat . toList stimes n arr = case compare n 0 of LT -> die "stimes" "negative multiplier" EQ -> empty GT -> createSmallArray (n' * sizeofSmallArray arr) (die "stimes" "impossible") $ \sma -> let go i = if i < n' then do copySmallArray sma (i * sizeofSmallArray arr) arr 0 (sizeofSmallArray arr) go (i + 1) else return () in go 0 where n' = fromIntegral n :: Int instance Monoid (SmallArray a) where mempty = empty #if !(MIN_VERSION_base(4,11,0)) mappend = (Sem.<>) #endif mconcat l = createSmallArray n (die "mconcat" "impossible") $ \ma -> let go !_ [ ] = return () go off (a:as) = copySmallArray ma off a 0 (sizeofSmallArray a) >> go (off + sizeofSmallArray a) as in go 0 l where n = sum (fmap length l) instance IsList (SmallArray a) where type Item (SmallArray a) = a fromListN = smallArrayFromListN fromList = smallArrayFromList toList = Foldable.toList smallArrayLiftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> SmallArray a -> ShowS smallArrayLiftShowsPrec elemShowsPrec elemListShowsPrec p sa = showParen (p > 10) $ showString "fromListN " . shows (length sa) . showString " " . listLiftShowsPrec elemShowsPrec elemListShowsPrec 11 (toList sa) -- this need to be included for older ghcs listLiftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> [a] -> ShowS listLiftShowsPrec _ sl _ = sl instance Show a => Show (SmallArray a) where showsPrec p sa = smallArrayLiftShowsPrec showsPrec showList p sa -- | @since 0.6.4.0 instance Show1 SmallArray where liftShowsPrec = smallArrayLiftShowsPrec smallArrayLiftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (SmallArray a) smallArrayLiftReadsPrec _ listReadsPrec p = readParen (p > 10) . readP_to_S $ do () <$ string "fromListN" skipSpaces n <- readS_to_P reads skipSpaces l <- readS_to_P listReadsPrec return $ smallArrayFromListN n l instance Read a => Read (SmallArray a) where readsPrec = smallArrayLiftReadsPrec readsPrec readList -- | @since 0.6.4.0 instance Read1 SmallArray where liftReadsPrec = smallArrayLiftReadsPrec smallArrayDataType :: DataType smallArrayDataType = mkDataType "Data.Primitive.SmallArray.SmallArray" [fromListConstr] fromListConstr :: Constr fromListConstr = mkConstr smallArrayDataType "fromList" [] Prefix instance Data a => Data (SmallArray a) where toConstr _ = fromListConstr dataTypeOf _ = smallArrayDataType gunfold k z c = case constrIndex c of 1 -> k (z fromList) _ -> die "gunfold" "SmallArray" gfoldl f z m = z fromList `f` toList m instance (Typeable s, Typeable a) => Data (SmallMutableArray s a) where toConstr _ = die "toConstr" "SmallMutableArray" gunfold _ _ = die "gunfold" "SmallMutableArray" dataTypeOf _ = mkNoRepType "Data.Primitive.SmallArray.SmallMutableArray" -- | Create a 'SmallArray' from a list of a known length. If the length -- of the list does not match the given length, this throws an exception. smallArrayFromListN :: Int -> [a] -> SmallArray a smallArrayFromListN n l = createSmallArray n (die "smallArrayFromListN" "uninitialized element") $ \sma -> let go !ix [] = if ix == n then return () else die "smallArrayFromListN" "list length less than specified size" go !ix (x : xs) = if ix < n then do writeSmallArray sma ix x go (ix + 1) xs else die "smallArrayFromListN" "list length greater than specified size" in go 0 l -- | Create a 'SmallArray' from a list. smallArrayFromList :: [a] -> SmallArray a smallArrayFromList l = smallArrayFromListN (length l) l #if MIN_VERSION_base(4,14,0) -- | Shrink the mutable array in place. The size given must be equal to -- or less than the current size of the array. This is not checked. shrinkSmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -> m () {-# inline shrinkSmallMutableArray #-} shrinkSmallMutableArray (SmallMutableArray x) (I# n) = primitive (\s0 -> case GHC.Exts.shrinkSmallMutableArray# x n s0 of s1 -> (# s1, () #) ) -- | Resize a mutable array to new specified size. The returned -- 'SmallMutableArray' is either the original 'SmallMutableArray' -- resized in-place or, if not possible, a newly allocated -- 'SmallMutableArray' with the original content copied over. -- -- To avoid undefined behaviour, the original 'SmallMutableArray' -- shall not be accessed anymore after a 'resizeSmallMutableArray' has -- been performed. Moreover, no reference to the old one should be -- kept in order to allow garbage collection of the original -- 'SmallMutableArray' in case a new 'SmallMutableArray' had to be -- allocated. resizeSmallMutableArray :: PrimMonad m => SmallMutableArray (PrimState m) a -> Int -- ^ New size -> a -- ^ Newly created slots initialized to this element. Only used when array is grown. -> m (SmallMutableArray (PrimState m) a) resizeSmallMutableArray (SmallMutableArray arr) (I# n) x = primitive (\s0 -> case GHC.Exts.resizeSmallMutableArray# arr n x s0 of (# s1, arr' #) -> (# s1, SmallMutableArray arr' #) ) {-# INLINE resizeSmallMutableArray #-} #endif primitive-0.8.0.0/Data/Primitive/Types.hs0000644000000000000000000004556107346545000016352 0ustar0000000000000000{-# LANGUAGE CPP #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE DeriveDataTypeable #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE StandaloneDeriving #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE DeriveGeneric #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE PolyKinds #-} #if __GLASGOW_HASKELL__ < 906 {-# LANGUAGE TypeInType #-} #endif #include "HsBaseConfig.h" -- | -- Module : Data.Primitive.Types -- Copyright : (c) Roman Leshchinskiy 2009-2012 -- License : BSD-style -- -- Maintainer : Roman Leshchinskiy -- Portability : non-portable -- -- Basic types and classes for primitive array operations. module Data.Primitive.Types ( Prim(..) , sizeOf, alignment, defaultSetByteArray#, defaultSetOffAddr# , PrimStorable(..) , Ptr(..) ) where import Control.Monad.Primitive import Data.Primitive.MachDeps import Data.Primitive.Internal.Operations import Foreign.Ptr (IntPtr, intPtrToPtr, ptrToIntPtr, WordPtr, wordPtrToPtr, ptrToWordPtr) import Foreign.C.Types import System.Posix.Types import GHC.Word (Word8(..), Word16(..), Word32(..), Word64(..)) import GHC.Int (Int8(..), Int16(..), Int32(..), Int64(..)) import GHC.Stable (StablePtr(..)) import GHC.Exts hiding (setByteArray#) import Foreign.Storable (Storable) import qualified Foreign.Storable as FS import GHC.IO (IO(..)) import qualified GHC.Exts import Control.Applicative (Const(..)) import Data.Functor.Identity (Identity(..)) import qualified Data.Monoid as Monoid import qualified Data.Semigroup as Semigroup #if !MIN_VERSION_base(4,13,0) import Data.Ord (Down(..)) #endif -- | Class of types supporting primitive array operations. This includes -- interfacing with GC-managed memory (functions suffixed with @ByteArray#@) -- and interfacing with unmanaged memory (functions suffixed with @Addr#@). -- Endianness is platform-dependent. class Prim a where -- | Size of values of type @a@. The argument is not used. sizeOf# :: a -> Int# -- | Alignment of values of type @a@. The argument is not used. alignment# :: a -> Int# -- | Read a value from the array. The offset is in elements of type -- @a@ rather than in bytes. indexByteArray# :: ByteArray# -> Int# -> a -- | Read a value from the mutable array. The offset is in elements of type -- @a@ rather than in bytes. readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) -- | Write a value to the mutable array. The offset is in elements of type -- @a@ rather than in bytes. writeByteArray# :: MutableByteArray# s -> Int# -> a -> State# s -> State# s -- | Fill a slice of the mutable array with a value. The offset and length -- of the chunk are in elements of type @a@ rather than in bytes. setByteArray# :: MutableByteArray# s -> Int# -- ^ offset -> Int# -- ^ length -> a -> State# s -> State# s -- | Read a value from a memory position given by an address and an offset. -- The memory block the address refers to must be immutable. The offset is in -- elements of type @a@ rather than in bytes. indexOffAddr# :: Addr# -> Int# -> a -- | Read a value from a memory position given by an address and an offset. -- The offset is in elements of type @a@ rather than in bytes. readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, a #) -- | Write a value to a memory position given by an address and an offset. -- The offset is in elements of type @a@ rather than in bytes. writeOffAddr# :: Addr# -> Int# -> a -> State# s -> State# s -- | Fill a memory block given by an address, an offset and a length. -- The offset and length are in elements of type @a@ rather than in bytes. setOffAddr# :: Addr# -> Int# -- ^ offset -> Int# -- ^ length -> a -> State# s -> State# s -- | Size of values of type @a@. The argument is not used. -- -- This function has existed since 0.1, but was moved from 'Data.Primitive' -- to 'Data.Primitive.Types' in version 0.6.3.0. sizeOf :: Prim a => a -> Int sizeOf x = I# (sizeOf# x) -- | Alignment of values of type @a@. The argument is not used. -- -- This function has existed since 0.1, but was moved from 'Data.Primitive' -- to 'Data.Primitive.Types' in version 0.6.3.0. alignment :: Prim a => a -> Int alignment x = I# (alignment# x) -- | An implementation of 'setByteArray#' that calls 'writeByteArray#' -- to set each element. This is helpful when writing a 'Prim' instance -- for a multi-word data type for which there is no CPU-accelerated way -- to broadcast a value to contiguous memory. It is typically used -- alongside 'defaultSetOffAddr#'. For example: -- -- > data Trip = Trip Int Int Int -- > -- > instance Prim Trip -- > sizeOf# _ = 3# *# sizeOf# (undefined :: Int) -- > alignment# _ = alignment# (undefined :: Int) -- > indexByteArray# arr# i# = ... -- > readByteArray# arr# i# = ... -- > writeByteArray# arr# i# (Trip a b c) = -- > \s0 -> case writeByteArray# arr# (3# *# i#) a s0 of -- > s1 -> case writeByteArray# arr# ((3# *# i#) +# 1#) b s1 of -- > s2 -> case writeByteArray# arr# ((3# *# i#) +# 2# ) c s2 of -- > s3 -> s3 -- > setByteArray# = defaultSetByteArray# -- > indexOffAddr# addr# i# = ... -- > readOffAddr# addr# i# = ... -- > writeOffAddr# addr# i# (Trip a b c) = -- > \s0 -> case writeOffAddr# addr# (3# *# i#) a s0 of -- > s1 -> case writeOffAddr# addr# ((3# *# i#) +# 1#) b s1 of -- > s2 -> case writeOffAddr# addr# ((3# *# i#) +# 2# ) c s2 of -- > s3 -> s3 -- > setOffAddr# = defaultSetOffAddr# defaultSetByteArray# :: Prim a => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s defaultSetByteArray# arr# i# len# ident = go 0# where go ix# s0 = if isTrue# (ix# <# len#) then case writeByteArray# arr# (i# +# ix#) ident s0 of s1 -> go (ix# +# 1#) s1 else s0 -- | An implementation of 'setOffAddr#' that calls 'writeOffAddr#' -- to set each element. The documentation of 'defaultSetByteArray#' -- provides an example of how to use this. defaultSetOffAddr# :: Prim a => Addr# -> Int# -> Int# -> a -> State# s -> State# s defaultSetOffAddr# addr# i# len# ident = go 0# where go ix# s0 = if isTrue# (ix# <# len#) then case writeOffAddr# addr# (i# +# ix#) ident s0 of s1 -> go (ix# +# 1#) s1 else s0 -- | Newtype that uses a 'Prim' instance to give rise to a 'Storable' instance. -- This type is intended to be used with the @DerivingVia@ extension available -- in GHC 8.6 and up. For example, consider a user-defined 'Prim' instance for -- a multi-word data type. -- -- > data Uuid = Uuid Word64 Word64 -- > deriving Storable via (PrimStorable Uuid) -- > instance Prim Uuid where ... -- -- Writing the 'Prim' instance is tedious and unavoidable, but the 'Storable' -- instance comes for free once the 'Prim' instance is written. newtype PrimStorable a = PrimStorable { getPrimStorable :: a } instance Prim a => Storable (PrimStorable a) where sizeOf _ = sizeOf (undefined :: a) alignment _ = alignment (undefined :: a) peekElemOff (Ptr addr#) (I# i#) = primitive $ \s0# -> case readOffAddr# addr# i# s0# of (# s1, x #) -> (# s1, PrimStorable x #) pokeElemOff (Ptr addr#) (I# i#) (PrimStorable a) = primitive_ $ \s# -> writeOffAddr# addr# i# a s# #define derivePrim(ty, ctr, sz, align, idx_arr, rd_arr, wr_arr, set_arr, idx_addr, rd_addr, wr_addr, set_addr) \ instance Prim (ty) where { \ sizeOf# _ = unI# sz \ ; alignment# _ = unI# align \ ; indexByteArray# arr# i# = ctr (idx_arr arr# i#) \ ; readByteArray# arr# i# s# = case rd_arr arr# i# s# of \ { (# s1#, x# #) -> (# s1#, ctr x# #) } \ ; writeByteArray# arr# i# (ctr x#) s# = wr_arr arr# i# x# s# \ ; setByteArray# arr# i# n# (ctr x#) s# \ = let { i = fromIntegral (I# i#) \ ; n = fromIntegral (I# n#) \ } in \ case unsafeCoerce# (internal (set_arr arr# i n x#)) s# of \ { (# s1#, _ #) -> s1# } \ \ ; indexOffAddr# addr# i# = ctr (idx_addr addr# i#) \ ; readOffAddr# addr# i# s# = case rd_addr addr# i# s# of \ { (# s1#, x# #) -> (# s1#, ctr x# #) } \ ; writeOffAddr# addr# i# (ctr x#) s# = wr_addr addr# i# x# s# \ ; setOffAddr# addr# i# n# (ctr x#) s# \ = let { i = fromIntegral (I# i#) \ ; n = fromIntegral (I# n#) \ } in \ case unsafeCoerce# (internal (set_addr addr# i n x#)) s# of \ { (# s1#, _ #) -> s1# } \ ; {-# INLINE sizeOf# #-} \ ; {-# INLINE alignment# #-} \ ; {-# INLINE indexByteArray# #-} \ ; {-# INLINE readByteArray# #-} \ ; {-# INLINE writeByteArray# #-} \ ; {-# INLINE setByteArray# #-} \ ; {-# INLINE indexOffAddr# #-} \ ; {-# INLINE readOffAddr# #-} \ ; {-# INLINE writeOffAddr# #-} \ ; {-# INLINE setOffAddr# #-} \ } #if __GLASGOW_HASKELL__ >= 902 liberate# :: State# s -> State# r liberate# = unsafeCoerce# shimmedSetWord8Array# :: MutableByteArray# s -> Int -> Int -> Word8# -> IO () shimmedSetWord8Array# m (I# off) (I# len) w = IO (\s -> (# liberate# (GHC.Exts.setByteArray# m off len (GHC.Exts.word2Int# (GHC.Exts.word8ToWord# w)) (liberate# s)), () #)) shimmedSetInt8Array# :: MutableByteArray# s -> Int -> Int -> Int8# -> IO () shimmedSetInt8Array# m (I# off) (I# len) i = IO (\s -> (# liberate# (GHC.Exts.setByteArray# m off len (GHC.Exts.int8ToInt# i) (liberate# s)), () #)) #else liberate# :: State# s -> State# r liberate# = unsafeCoerce# shimmedSetWord8Array# :: MutableByteArray# s -> Int -> Int -> Word# -> IO () shimmedSetWord8Array# m (I# off) (I# len) w = IO (\s -> (# liberate# (GHC.Exts.setByteArray# m off len (GHC.Exts.word2Int# w) (liberate# s)), () #)) shimmedSetInt8Array# :: MutableByteArray# s -> Int -> Int -> Int# -> IO () shimmedSetInt8Array# m (I# off) (I# len) i = IO (\s -> (# liberate# (GHC.Exts.setByteArray# m off len i (liberate# s)), () #)) #endif unI# :: Int -> Int# unI# (I# n#) = n# derivePrim(Word, W#, sIZEOF_WORD, aLIGNMENT_WORD, indexWordArray#, readWordArray#, writeWordArray#, setWordArray#, indexWordOffAddr#, readWordOffAddr#, writeWordOffAddr#, setWordOffAddr#) derivePrim(Word8, W8#, sIZEOF_WORD8, aLIGNMENT_WORD8, indexWord8Array#, readWord8Array#, writeWord8Array#, shimmedSetWord8Array#, indexWord8OffAddr#, readWord8OffAddr#, writeWord8OffAddr#, setWord8OffAddr#) derivePrim(Word16, W16#, sIZEOF_WORD16, aLIGNMENT_WORD16, indexWord16Array#, readWord16Array#, writeWord16Array#, setWord16Array#, indexWord16OffAddr#, readWord16OffAddr#, writeWord16OffAddr#, setWord16OffAddr#) derivePrim(Word32, W32#, sIZEOF_WORD32, aLIGNMENT_WORD32, indexWord32Array#, readWord32Array#, writeWord32Array#, setWord32Array#, indexWord32OffAddr#, readWord32OffAddr#, writeWord32OffAddr#, setWord32OffAddr#) derivePrim(Word64, W64#, sIZEOF_WORD64, aLIGNMENT_WORD64, indexWord64Array#, readWord64Array#, writeWord64Array#, setWord64Array#, indexWord64OffAddr#, readWord64OffAddr#, writeWord64OffAddr#, setWord64OffAddr#) derivePrim(Int, I#, sIZEOF_INT, aLIGNMENT_INT, indexIntArray#, readIntArray#, writeIntArray#, setIntArray#, indexIntOffAddr#, readIntOffAddr#, writeIntOffAddr#, setIntOffAddr#) derivePrim(Int8, I8#, sIZEOF_INT8, aLIGNMENT_INT8, indexInt8Array#, readInt8Array#, writeInt8Array#, shimmedSetInt8Array#, indexInt8OffAddr#, readInt8OffAddr#, writeInt8OffAddr#, setInt8OffAddr#) derivePrim(Int16, I16#, sIZEOF_INT16, aLIGNMENT_INT16, indexInt16Array#, readInt16Array#, writeInt16Array#, setInt16Array#, indexInt16OffAddr#, readInt16OffAddr#, writeInt16OffAddr#, setInt16OffAddr#) derivePrim(Int32, I32#, sIZEOF_INT32, aLIGNMENT_INT32, indexInt32Array#, readInt32Array#, writeInt32Array#, setInt32Array#, indexInt32OffAddr#, readInt32OffAddr#, writeInt32OffAddr#, setInt32OffAddr#) derivePrim(Int64, I64#, sIZEOF_INT64, aLIGNMENT_INT64, indexInt64Array#, readInt64Array#, writeInt64Array#, setInt64Array#, indexInt64OffAddr#, readInt64OffAddr#, writeInt64OffAddr#, setInt64OffAddr#) derivePrim(Float, F#, sIZEOF_FLOAT, aLIGNMENT_FLOAT, indexFloatArray#, readFloatArray#, writeFloatArray#, setFloatArray#, indexFloatOffAddr#, readFloatOffAddr#, writeFloatOffAddr#, setFloatOffAddr#) derivePrim(Double, D#, sIZEOF_DOUBLE, aLIGNMENT_DOUBLE, indexDoubleArray#, readDoubleArray#, writeDoubleArray#, setDoubleArray#, indexDoubleOffAddr#, readDoubleOffAddr#, writeDoubleOffAddr#, setDoubleOffAddr#) derivePrim(Char, C#, sIZEOF_CHAR, aLIGNMENT_CHAR, indexWideCharArray#, readWideCharArray#, writeWideCharArray#, setWideCharArray#, indexWideCharOffAddr#, readWideCharOffAddr#, writeWideCharOffAddr#, setWideCharOffAddr#) derivePrim(Ptr a, Ptr, sIZEOF_PTR, aLIGNMENT_PTR, indexAddrArray#, readAddrArray#, writeAddrArray#, setAddrArray#, indexAddrOffAddr#, readAddrOffAddr#, writeAddrOffAddr#, setAddrOffAddr#) derivePrim(StablePtr a, StablePtr, sIZEOF_PTR, aLIGNMENT_PTR, indexStablePtrArray#, readStablePtrArray#, writeStablePtrArray#, setStablePtrArray#, indexStablePtrOffAddr#, readStablePtrOffAddr#, writeStablePtrOffAddr#, setStablePtrOffAddr#) derivePrim(FunPtr a, FunPtr, sIZEOF_PTR, aLIGNMENT_PTR, indexAddrArray#, readAddrArray#, writeAddrArray#, setAddrArray#, indexAddrOffAddr#, readAddrOffAddr#, writeAddrOffAddr#, setAddrOffAddr#) -- Prim instances for newtypes in Foreign.C.Types deriving instance Prim CChar deriving instance Prim CSChar deriving instance Prim CUChar deriving instance Prim CShort deriving instance Prim CUShort deriving instance Prim CInt deriving instance Prim CUInt deriving instance Prim CLong deriving instance Prim CULong deriving instance Prim CPtrdiff deriving instance Prim CSize deriving instance Prim CWchar deriving instance Prim CSigAtomic deriving instance Prim CLLong deriving instance Prim CULLong #if MIN_VERSION_base(4,10,0) deriving instance Prim CBool #endif deriving instance Prim CIntPtr deriving instance Prim CUIntPtr deriving instance Prim CIntMax deriving instance Prim CUIntMax deriving instance Prim CClock deriving instance Prim CTime deriving instance Prim CUSeconds deriving instance Prim CSUSeconds deriving instance Prim CFloat deriving instance Prim CDouble -- Prim instances for newtypes in System.Posix.Types #if defined(HTYPE_DEV_T) deriving instance Prim CDev #endif #if defined(HTYPE_INO_T) deriving instance Prim CIno #endif #if defined(HTYPE_MODE_T) deriving instance Prim CMode #endif #if defined(HTYPE_OFF_T) deriving instance Prim COff #endif #if defined(HTYPE_PID_T) deriving instance Prim CPid #endif #if defined(HTYPE_SSIZE_T) deriving instance Prim CSsize #endif #if defined(HTYPE_GID_T) deriving instance Prim CGid #endif #if defined(HTYPE_NLINK_T) deriving instance Prim CNlink #endif #if defined(HTYPE_UID_T) deriving instance Prim CUid #endif #if defined(HTYPE_CC_T) deriving instance Prim CCc #endif #if defined(HTYPE_SPEED_T) deriving instance Prim CSpeed #endif #if defined(HTYPE_TCFLAG_T) deriving instance Prim CTcflag #endif #if defined(HTYPE_RLIM_T) deriving instance Prim CRLim #endif #if defined(HTYPE_BLKSIZE_T) deriving instance Prim CBlkSize #endif #if defined(HTYPE_BLKCNT_T) deriving instance Prim CBlkCnt #endif #if defined(HTYPE_CLOCKID_T) deriving instance Prim CClockId #endif #if defined(HTYPE_FSBLKCNT_T) deriving instance Prim CFsBlkCnt #endif #if defined(HTYPE_FSFILCNT_T) deriving instance Prim CFsFilCnt #endif #if defined(HTYPE_ID_T) deriving instance Prim CId #endif #if defined(HTYPE_KEY_T) deriving instance Prim CKey #endif #if defined(HTYPE_TIMER_T) deriving instance Prim CTimer #endif deriving instance Prim Fd -- Andrew Martin: The instances for WordPtr and IntPtr are written out by -- hand in a tedious way. We cannot use GND because the data constructors for -- these types were not available before GHC 8.2. The CPP for generating code -- for the Int and Word types does not work here. There is a way to clean this -- up a little with CPP, and if anyone wants to do that, go for it. In the -- meantime, I am going to ship this with the instances written out by hand. -- | @since 0.7.1.0 instance Prim WordPtr where sizeOf# _ = sizeOf# (undefined :: Ptr ()) alignment# _ = alignment# (undefined :: Ptr ()) indexByteArray# a i = ptrToWordPtr (indexByteArray# a i) readByteArray# a i s0 = case readByteArray# a i s0 of (# s1, p #) -> (# s1, ptrToWordPtr p #) writeByteArray# a i wp = writeByteArray# a i (wordPtrToPtr wp) setByteArray# a i n wp = setByteArray# a i n (wordPtrToPtr wp) indexOffAddr# a i = ptrToWordPtr (indexOffAddr# a i) readOffAddr# a i s0 = case readOffAddr# a i s0 of (# s1, p #) -> (# s1, ptrToWordPtr p #) writeOffAddr# a i wp = writeOffAddr# a i (wordPtrToPtr wp) setOffAddr# a i n wp = setOffAddr# a i n (wordPtrToPtr wp) -- | @since 0.7.1.0 instance Prim IntPtr where sizeOf# _ = sizeOf# (undefined :: Ptr ()) alignment# _ = alignment# (undefined :: Ptr ()) indexByteArray# a i = ptrToIntPtr (indexByteArray# a i) readByteArray# a i s0 = case readByteArray# a i s0 of (# s1, p #) -> (# s1, ptrToIntPtr p #) writeByteArray# a i wp = writeByteArray# a i (intPtrToPtr wp) setByteArray# a i n wp = setByteArray# a i n (intPtrToPtr wp) indexOffAddr# a i = ptrToIntPtr (indexOffAddr# a i) readOffAddr# a i s0 = case readOffAddr# a i s0 of (# s1, p #) -> (# s1, ptrToIntPtr p #) writeOffAddr# a i wp = writeOffAddr# a i (intPtrToPtr wp) setOffAddr# a i n wp = setOffAddr# a i n (intPtrToPtr wp) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Const a b) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Down a) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Identity a) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Monoid.Dual a) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Monoid.Sum a) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Monoid.Product a) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Semigroup.First a) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Semigroup.Last a) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Semigroup.Min a) -- | @since 0.6.5.0 deriving instance Prim a => Prim (Semigroup.Max a) primitive-0.8.0.0/LICENSE0000644000000000000000000000301607346545000013063 0ustar0000000000000000Copyright (c) 2008-2009, Roman Leshchinskiy All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: - Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. - Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. - Neither name of the University nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE UNIVERSITY COURT OF THE UNIVERSITY OF GLASGOW AND THE CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE UNIVERSITY COURT OF THE UNIVERSITY OF GLASGOW OR THE CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. primitive-0.8.0.0/bench/Array/Traverse/0000755000000000000000000000000007346545000016006 5ustar0000000000000000primitive-0.8.0.0/bench/Array/Traverse/Closure.hs0000644000000000000000000000244507346545000017763 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE RankNTypes #-} {-# LANGUAGE MagicHash #-} module Array.Traverse.Closure ( traversePoly ) where import Control.Applicative import Control.Monad.ST import Data.Primitive.Array import GHC.Exts (Int(..),MutableArray#) {-# INLINE traversePoly #-} traversePoly :: Applicative f => (a -> f b) -> Array a -> f (Array b) traversePoly f = \ !ary -> let !len = sizeofArray ary go !i | i == len = pure $ STA $ \mary -> unsafeFreezeArray (MutableArray mary) | (# x #) <- indexArray## ary i = liftA2 (\b (STA m) -> STA $ \mary -> writeArray (MutableArray mary) i b >> m mary) (f x) (go (i + 1)) in if len == 0 then pure mempty else runSTA len <$> go 0 badTraverseValue :: a badTraverseValue = die "traversePoly" "bad indexing" {-# NOINLINE badTraverseValue #-} die :: String -> String -> a die fun problem = error $ "Array.Traverse.Closure" ++ fun ++ ": " ++ problem newtype STA a = STA {_runSTA :: forall s. MutableArray# s a -> ST s (Array a)} runSTA :: Int -> STA a -> Array a runSTA !sz = \ (STA m) -> runST $ newArray_ sz >>= \ ar -> m (marray# ar) {-# INLINE runSTA #-} newArray_ :: Int -> ST s (MutableArray s a) newArray_ !n = newArray n badTraverseValue primitive-0.8.0.0/bench/Array/Traverse/Unsafe.hs0000644000000000000000000000212107346545000017557 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} module Array.Traverse.Unsafe ( traversePoly , traverseMono ) where import Control.Monad.ST import Control.Monad.Trans.State.Strict import Control.Monad.Primitive import Data.Primitive.Array {-# INLINE traversePoly #-} traversePoly :: PrimMonad m => (a -> m b) -> Array a -> m (Array b) traversePoly f = \ !ary -> let !sz = sizeofArray ary go !i !mary | i == sz = unsafeFreezeArray mary | otherwise = do a <- indexArrayM ary i b <- f a writeArray mary i b go (i + 1) mary in do mary <- newArray sz badTraverseValue go 0 mary badTraverseValue :: a badTraverseValue = die "traversePoly" "bad indexing" {-# NOINLINE badTraverseValue #-} die :: String -> String -> a die fun problem = error $ "Array.Traverse.Unsafe" ++ fun ++ ": " ++ problem -- Included to make it easy to inspect GHC Core that results -- from inlining traversePoly. traverseMono :: (Int -> StateT Word (ST s) Int) -> Array Int -> StateT Word (ST s) (Array Int) traverseMono f x = traversePoly f x primitive-0.8.0.0/bench/ByteArray/0000755000000000000000000000000007346545000015037 5ustar0000000000000000primitive-0.8.0.0/bench/ByteArray/Compare.hs0000644000000000000000000000552207346545000016765 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE ScopedTypeVariables #-} module ByteArray.Compare ( benchmark , argumentSmall , argumentMedium , argumentLarge ) where import Data.Primitive import Data.Word import Control.Monad import Control.Monad.ST (runST) import GHC.Exts (fromList) -- This takes the cross product of the argument with itself -- and compares each pair of combined ByteArrays. In other words, -- it compare every ByteArray to every other ByteArray (including -- itself). This is does efficiently and should not allocate -- any memory. benchmark :: Array ByteArray -> Int benchmark !uarr = outer 0 where sz = sizeofArray uarr outer :: Int -> Int outer !v0 = let go !v !ix = if ix < sz then go (inner v (indexArray uarr ix)) (ix + 1) else v in go v0 0 inner :: Int -> ByteArray -> Int inner !v0 !barr = let go !v !ix = if ix < sz then let !y = case compare barr (indexArray uarr ix) of LT -> (-1) EQ -> 0 GT -> 1 in go (v + y) (ix + 1) else v in go v0 0 -- This is an array of all byte arrays consistent of the bytes 0 and 1 -- bewteen length 0 and 7 inclusive: -- -- [] -- [0] -- [1] -- [0,0] -- [0,1] -- ... -- [1,1,1,1,1,1,0] -- [1,1,1,1,1,1,1] -- -- These are very small byte arrays. All of them are smaller than a -- cache line. A comparison function that uses the FFI may perform -- worse on such inputs than one that does not. argumentSmall :: Array ByteArray argumentSmall = runST $ do let (ys :: [[Word8]]) = foldMap (\n -> replicateM n [0,1]) (enumFromTo 0 7) marr <- newArray (length ys) undefined let go !_ [] = return () go !ix (x : xs) = do writeArray marr ix (fromList x) go (ix + 1) xs go 0 ys unsafeFreezeArray marr -- This is an array of all byte arrays consistent of the bytes 0 and 1 -- bewteen length 0 and 7 inclusive. However, they are all padded on the -- left by the same 256 bytes. Comparing any two of them will require -- walking and comparing the first 256 bytes. argumentMedium :: Array ByteArray argumentMedium = runST $ do let (ys :: [[Word8]]) = foldMap (\n -> map (enumFromTo 0 255 ++) (replicateM n [0,1])) (enumFromTo 0 7) marr <- newArray (length ys) undefined let go !_ [] = return () go !ix (x : xs) = do writeArray marr ix (fromList x) go (ix + 1) xs go 0 ys unsafeFreezeArray marr -- Same thing but with left padding of 1024 bytes. argumentLarge :: Array ByteArray argumentLarge = runST $ do let (ys :: [[Word8]]) = foldMap (\n -> map (concat (replicate 4 (enumFromTo 0 255)) ++) (replicateM n [0,1])) (enumFromTo 0 7) marr <- newArray (length ys) undefined let go !_ [] = return () go !ix (x : xs) = do writeArray marr ix (fromList x) go (ix + 1) xs go 0 ys unsafeFreezeArray marr primitive-0.8.0.0/bench/PrimArray/0000755000000000000000000000000007346545000015043 5ustar0000000000000000primitive-0.8.0.0/bench/PrimArray/Compare.hs0000644000000000000000000000256607346545000016776 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE ScopedTypeVariables #-} module PrimArray.Compare ( benchmarkLt , benchmarkLtDef , benchmarkLte , benchmarkLteDef , argumentA , argumentB ) where import Data.Primitive import Data.Word import Control.Monad import Control.Monad.ST (runST) import GHC.Exts (fromList) benchmarkLtDef :: PrimArray Int -> PrimArray Int -> Bool benchmarkLtDef a b = case compare a b of LT -> True _ -> False benchmarkLteDef :: PrimArray Int -> PrimArray Int -> Bool benchmarkLteDef a b = case compare a b of GT -> False _ -> True benchmarkLt :: PrimArray Int -> PrimArray Int -> Bool benchmarkLt a b = let !sz1 = sizeofPrimArray a !sz2 = sizeofPrimArray b !sz = min sz1 sz2 loop !i | i < sz = if indexPrimArray a i < indexPrimArray b i then True else loop (i + 1) | otherwise = sz1 < sz2 in loop 0 benchmarkLte :: PrimArray Int -> PrimArray Int -> Bool benchmarkLte a b = let !sz1 = sizeofPrimArray a !sz2 = sizeofPrimArray b !sz = min sz1 sz2 loop !i | i < sz = if indexPrimArray a i <= indexPrimArray b i then loop (i + 1) else False | otherwise = sz1 < sz2 in loop 0 argumentA :: PrimArray Int argumentA = fromList (enumFromTo 0 8000 ++ [55]) argumentB :: PrimArray Int argumentB = fromList (enumFromTo 0 8000 ++ [56]) primitive-0.8.0.0/bench/PrimArray/Traverse.hs0000644000000000000000000000126707346545000017200 0ustar0000000000000000module PrimArray.Traverse ( benchmarkApplicative , benchmarkPrimMonad , argument ) where import Control.Monad.ST (runST) import Control.Monad.Trans.Maybe (MaybeT(..)) import Data.Bool (bool) import Data.Primitive.PrimArray import GHC.Exts (fromList) benchmarkApplicative :: PrimArray Int -> Maybe (PrimArray Int) benchmarkApplicative xs = traversePrimArray (\x -> bool Nothing (Just (x + 1)) (x > 0)) xs benchmarkPrimMonad :: PrimArray Int -> Maybe (PrimArray Int) benchmarkPrimMonad xs = runST $ runMaybeT $ traversePrimArrayP (\x -> bool (MaybeT (return Nothing)) (MaybeT (return (Just (x + 1)))) (x > 0)) xs argument :: PrimArray Int argument = fromList (enumFromTo 1 10000) primitive-0.8.0.0/bench/0000755000000000000000000000000007346545000013135 5ustar0000000000000000primitive-0.8.0.0/bench/main.hs0000644000000000000000000000527707346545000014430 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} {-# OPTIONS_GHC -fno-warn-orphans #-} import Test.Tasty.Bench import Control.Monad.ST import Data.Primitive import Control.Monad.Trans.State.Strict -- These are fixed implementations of certain operations. In the event -- that primitive changes its implementation of a function, these -- implementations stay the same. They are helpful for ensuring that -- something that is a performance win in one version of GHC doesn't -- become a regression later. They are also helpful for evaluating -- how well different implementation hold up in different scenarios. import qualified Array.Traverse.Unsafe import qualified Array.Traverse.Closure -- These are particular scenarios that are tested against the -- implementations actually used by primitive. import qualified ByteArray.Compare import qualified PrimArray.Compare import qualified PrimArray.Traverse main :: IO () main = defaultMain [ bgroup "Array" [ bgroup "implementations" [ bgroup "traverse" [ bench "closure" (nf (\x -> runST (runStateT (Array.Traverse.Closure.traversePoly cheap x) 0)) numbers) , bench "unsafe" (nf (\x -> runST (runStateT (Array.Traverse.Unsafe.traversePoly cheap x) 0)) numbers) ] ] ] , bgroup "ByteArray" [ bgroup "compare" [ bench "small" (whnf ByteArray.Compare.benchmark ByteArray.Compare.argumentSmall) , bench "medium" (whnf ByteArray.Compare.benchmark ByteArray.Compare.argumentMedium) , bench "large" (whnf ByteArray.Compare.benchmark ByteArray.Compare.argumentLarge) ] ] , bgroup "PrimArray" [ bgroup "traverse" [ bgroup "Maybe" [ bench "Applicative" (whnf PrimArray.Traverse.benchmarkApplicative PrimArray.Traverse.argument) , bench "PrimMonad" (whnf PrimArray.Traverse.benchmarkPrimMonad PrimArray.Traverse.argument) ] ] , bgroup "implementations" [ bgroup "less-than" [ bench "default" (whnf (PrimArray.Compare.benchmarkLtDef PrimArray.Compare.argumentA) PrimArray.Compare.argumentB) , bench "override" (whnf (PrimArray.Compare.benchmarkLt PrimArray.Compare.argumentA) PrimArray.Compare.argumentB) ] , bgroup "less-than-equal" [ bench "default" (whnf (PrimArray.Compare.benchmarkLteDef PrimArray.Compare.argumentA) PrimArray.Compare.argumentB) , bench "override" (whnf (PrimArray.Compare.benchmarkLte PrimArray.Compare.argumentA) PrimArray.Compare.argumentB) ] ] ] ] cheap :: Int -> StateT Int (ST s) Int cheap i = modify (\x -> x + i) >> return (i * i) numbers :: Array Int numbers = fromList (enumFromTo 0 10000) primitive-0.8.0.0/cbits/0000755000000000000000000000000007346545000013162 5ustar0000000000000000primitive-0.8.0.0/cbits/primitive-memops.c0000644000000000000000000000516607346545000016644 0ustar0000000000000000#include #include "primitive-memops.h" void hsprimitive_memcpy( void *dst, ptrdiff_t doff, void *src, ptrdiff_t soff, size_t len ) { memcpy( (char *)dst + doff, (char *)src + soff, len ); } void hsprimitive_memmove( void *dst, ptrdiff_t doff, void *src, ptrdiff_t soff, size_t len ) { memmove( (char *)dst + doff, (char *)src + soff, len ); } #define MEMSET(TYPE, ATYPE) \ void hsprimitive_memset_ ## TYPE (Hs ## TYPE *p, ptrdiff_t off, size_t n, ATYPE x) \ { \ p += off; \ if (x == 0) \ memset(p, 0, n * sizeof(Hs ## TYPE)); \ else if (sizeof(Hs ## TYPE) == sizeof(int)*2) { \ int *q = (int *)p; \ const int *r = (const int *)(void *)&x; \ while (n>0) { \ q[0] = r[0]; \ q[1] = r[1]; \ q += 2; \ --n; \ } \ } \ else { \ while (n>0) { \ *p++ = x; \ --n; \ } \ } \ } int hsprimitive_memcmp( HsWord8 *s1, HsWord8 *s2, size_t n ) { return memcmp( s1, s2, n ); } int hsprimitive_memcmp_offset( HsWord8 *s1, HsInt off1, HsWord8 *s2, HsInt off2, size_t n ) { return memcmp( s1 + off1, s2 + off2, n ); } void hsprimitive_memset_Word8 (HsWord8 *p, ptrdiff_t off, size_t n, HsWord8 x) { memset( (char *)(p+off), x, n ); } /* MEMSET(HsWord8, HsWord) */ MEMSET(Word16, HsWord16) MEMSET(Word32, HsWord32) MEMSET(Word64, HsWord64) MEMSET(Word, HsWord) MEMSET(Ptr, HsPtr) MEMSET(Float, HsFloat) MEMSET(Double, HsDouble) MEMSET(Char, HsChar) primitive-0.8.0.0/cbits/primitive-memops.h0000644000000000000000000000223507346545000016643 0ustar0000000000000000#ifndef haskell_primitive_memops_h #define haskell_primitive_memops_h // N.B. GHC RTS headers want to come first, lest things break on Windows. #include #include #include void hsprimitive_memcpy(void *dst, ptrdiff_t doff, void *src, ptrdiff_t soff, size_t len); void hsprimitive_memmove(void *dst, ptrdiff_t doff, void *src, ptrdiff_t soff, size_t len); int hsprimitive_memcmp(HsWord8 *s1, HsWord8 *s2, size_t n); int hsprimitive_memcmp_offset(HsWord8 *s1, HsInt off1, HsWord8 *s2, HsInt off2, size_t n); void hsprimitive_memset_Word8(HsWord8 *, ptrdiff_t, size_t, HsWord8); void hsprimitive_memset_Word16(HsWord16 *, ptrdiff_t, size_t, HsWord16); void hsprimitive_memset_Word32(HsWord32 *, ptrdiff_t, size_t, HsWord32); void hsprimitive_memset_Word64(HsWord64 *, ptrdiff_t, size_t, HsWord64); void hsprimitive_memset_Word(HsWord *, ptrdiff_t, size_t, HsWord); void hsprimitive_memset_Ptr(HsPtr *, ptrdiff_t, size_t, HsPtr); void hsprimitive_memset_Float(HsFloat *, ptrdiff_t, size_t, HsFloat); void hsprimitive_memset_Double(HsDouble *, ptrdiff_t, size_t, HsDouble); void hsprimitive_memset_Char(HsChar *, ptrdiff_t, size_t, HsChar); #endif primitive-0.8.0.0/changelog.md0000644000000000000000000002261407346545000014334 0ustar0000000000000000## Changes in version 0.8.0.0 * Add `resizeSmallMutableArray` that wraps `resizeSmallMutableArray#` from `GHC.Exts`. * New module `Data.Primitive.PrimVar`. This is essentially `PrimArray` with element length 1. For types with `Prim` instances, this is a drop-in replacement for `MutVar` with fewer indirections. * `PrimArray`'s type argument has been given a nominal role instead of a phantom role. This is a breaking change. * Add `readCharArray`, `writeCharArray`, `indexCharArray` for operating on 8-bit characters in a byte array. * When building with `base-4.17` and newer, re-export the `ByteArray` and `MutableByteArray` types from `base` instead of defining them in this library. This does not change the user-facing interface of `Data.Primitive.ByteArray`. * Add `keepAlive` that wraps `keepAlive#` for GHC 9.2 and newer. It falls back to using `touch` for older GHCs. ## Changes in version 0.7.4.0 * Add Lift instances (#332) * Expose `copyPtrToMutablePrimArray` * Improve definitions for stimes (#326) * Support GHC 9.4. Note: GHC 9.4 is not released at the time of primitive-0.7.4.0's release, so this support might be reverted by a hackage metadata revision if things change. * Drop support for GHC 7.10 ## Changes in version 0.7.3.0 * Correct implementations of `*>` for `Array` and `SmallArray`. * Drop support for GHC < 7.10 * Export `runByteArray` and `runPrimArray`. * Export `createArray` and `createSmallArray`. * Export `emptyByteArray`, `emptyPrimArray`, `emptyArray` and `emptySmallArray`. ## Changes in version 0.7.2.0 * Add `thawByteArray` and `thawPrimArray`. * Changed the `Show` instance of `ByteArray`, so that all 8-bit words are rendered as two digits. For example, display `0x0D` instead of `0xD`. ## Changes in version 0.7.1.0 * Introduce convenience class `MonadPrim` and `MonadPrimBase`. * Add `PrimMonad` and `PrimBase` instances for `Lazy.ST` (GHC >= 8.2). thanks to Avi Dessauer (@Avi-D-coder) for this first contribution * Add `freezeByteArray` and `freezePrimArray`. * Add `compareByteArrays`. * Add `shrinkMutableByteArray`. * Add `Eq` instances for `MutableByteArray` and `MutablePrimArray`. by Andrew Martin * Add functions for manipulating pinned Prim Arrays by Andrew Martin * Add `copyPtrToMutableByteArray`. * Add `NFData` instances for `ByteArray`, `MutableByteArray`, `PrimArray` and `MutablePrimArray`. by Callan McGill * Add `shrinkSmallMutableArray`. * Add `clonePrimArray` and `cloneMutablePrimArray`. * Add `cloneMutableByteArray` and `cloneByteArray`. * Add `Prim` instances for `WordPtr` and `IntPtr`. * Add `NFData` instances for `Array` and `SmallArray`. by Callan McGill * Add `copyByteArrayToPtr` and `copyMutableByteArrayToPtr`. * Export `arrayFromList` and `arrayFromListN`. ## Changes in version 0.7.0.1 * Allow building with GHC 8.12. Thanks Ryan GL Scott for this and every compat patch over time. ## Changes in version 0.7.0.0 * Remove `Addr` data type, lifted code should use `Ptr a` now * Define `MonadFail` instances for `Array` and `SmallArray`. * Define `unsafeInterleave`. * Add a `Prim` instance for `StablePtr` * Remove `UnliftedArray` and related type classes * Add a lot more tests for `PrimArray`. * Added PrimMonad instance for CPS Writer and RWS monads from Transformers * Remove useless accidental laziness in `atomicModifyMutVar`, making it match `atomicModifyIORef`. The semantics should be the same. * lots of little documentation twiddles. ## Changes in version 0.6.4.1 * Add instances for the following newtypes from `base`: `Const`, `Identity`, `Down`, `Dual`, `Sum`, `Product`, `First`, `Last`, `Min`, `Max` * Add `base-orphans` dependency to test suite to accomodate older versions of GHC not having instances of `Show` and `Eq` for some of the above newtypes. ## Changes in version 0.6.4.0 * Introduce `Data.Primitive.PrimArray`, which offers types and function for dealing with a `ByteArray` tagged with a phantom type variable for tracking the element type. * Implement `isByteArrayPinned` and `isMutableByteArrayPinned`. * Add `Eq1`, `Ord1`, `Show1`, and `Read1` instances for `Array` and `SmallArray`. * Improve the test suite. This includes having property tests for typeclasses from `base` such as `Eq`, `Ord`, `Functor`, `Applicative`, `Monad`, `IsList`, `Monoid`, `Foldable`, and `Traversable`. * Fix the broken `IsList` instance for `ByteArray`. The old definition would allocate a byte array of the correct size and then leave the memory unitialized instead of writing the list elements to it. * Fix the broken `Functor` instance for `Array`. The old definition would allocate an array of the correct size with thunks for erroring installed at every index. It failed to replace these thunks with the result of the function applied to the elements of the argument array. * Fix the broken `Applicative` instances of `Array` and `SmallArray`. The old implementation of `<*>` for `Array` failed to initialize some elements but correctly initialized others in the resulting `Array`. It is unclear what the old behavior of `<*>` was for `SmallArray`, but it was incorrect. * Fix the broken `Monad` instances for `Array` and `SmallArray`. * Fix the implementation of `foldl1` in the `Foldable` instances for `Array` and `SmallArray`. In both cases, the old implementation simply returned the first element of the array and made no use of the other elements in the array. * Fix the implementation of `mconcat` in the `Monoid` instance for `SmallArray`. * Implement `Data.Primitive.Ptr`, implementations of `Ptr` functions that require a `Prim` constraint instead of a `Storable` constraint. * Add `PrimUnlifted` instances for `TVar` and `MVar`. * Use `compareByteArrays#` for the `Eq` and `Ord` instances of `ByteArray` when building with GHC 8.4 and newer. * Add `Prim` instances for lots of types in `Foreign.C.Types` and `System.Posix.Types`. * Reexport `Data.Primitive.SmallArray` and `Data.Primitive.UnliftedArray` from `Data.Primitive`. * Add fold functions and map function to `Data.Primitive.UnliftedArray`. Add typeclass instances for `IsList`, `Ord`, and `Show`. * Add `defaultSetByteArray#` and `defaultSetOffAddr#` to `Data.Primitive.Types`. * Add `Data.Primitive.MVar`, a replacement for `Control.Concurrent.MVar` that can run in any `PrimMonad` instead of just `IO`. It is not a full replacement. Notably, it's missing masking functions and support for adding finalizers. ## Changes in version 0.6.3.0 * Add `PrimMonad` instances for `ContT`, `AccumT`, and `SelectT` from `transformers` * Add `Eq`, `Ord`, `Show`, and `IsList` instances for `ByteArray` * Add `Semigroup` instances for `Array` and `SmallArray`. This allows `primitive` to build on GHC 8.4 and later. ## Changes in version 0.6.2.0 * Drop support for GHCs before 7.4 * `SmallArray` support * `ArrayArray#` based support for more efficient arrays of unlifted pointer types * Make `Array` and the like instances of various classes for convenient use * Add `Prim` instances for Ptr and FunPtr * Add `ioToPrim`, `stToPrim` and unsafe counterparts for situations that would otherwise require type ascriptions on `primToPrim` * Add `evalPrim` * Add `PrimBase` instance for `IdentityT` ## Changes in version 0.6.1.0 * Use more appropriate types in internal memset functions, which prevents overflows/segfaults on 64-bit systems. * Fixed a warning on GHC 7.10 * Worked around a -dcore-lint bug in GHC 7.6/7.7 ## Changes in version 0.6 * Split PrimMonad into two classes to allow automatic lifting of primitive operations into monad transformers. The `internal` operation has moved to the `PrimBase` class. * Fixed the test suite on older GHCs ## Changes in version 0.5.4.0 * Changed primitive_ to work around an oddity with GHC's code generation on certain versions that led to side effects not happening when used in conjunction with certain very unsafe IO performers. * Allow primitive to build on GHC 7.9 ## Changes in version 0.5.3.0 * Implement `cloneArray` and `cloneMutableArray` primitives (with fall-back implementations for GHCs prior to version 7.2.1) ## Changes in version 0.5.2.1 * Add strict variants of `MutVar` modification functions `atomicModifyMutVar'` and `modifyMutVar'` * Fix compilation on Solaris 10 with GNU C 3.4.3 ## Changes in version 0.5.1.0 * Add support for GHC 7.7's new primitive `Bool` representation ## Changes in version 0.5.0.1 * Disable array copying primitives for GHC 7.6.* and earlier ## Changes in version 0.5 * New in `Data.Primitive.MutVar`: `atomicModifyMutVar` * Efficient block fill operations: `setByteArray`, `setAddr` ## Changes in version 0.4.1 * New module `Data.Primitive.MutVar` ## Changes in version 0.4.0.1 * Critical bug fix in `fillByteArray` ## Changes in version 0.4 * Support for GHC 7.2 array copying primitives * New in `Data.Primitive.ByteArray`: `copyByteArray`, `copyMutableByteArray`, `moveByteArray`, `fillByteArray` * Deprecated in `Data.Primitive.ByteArray`: `memcpyByteArray`, `memcpyByteArray'`, `memmoveByteArray`, `memsetByteArray` * New in `Data.Primitive.Array`: `copyArray`, `copyMutableByteArray` * New in `Data.Primitive.Addr`: `copyAddr`, `moveAddr` * Deprecated in `Data.Primitive.Addr`: `memcpyAddr` primitive-0.8.0.0/primitive.cabal0000644000000000000000000000604007346545000015052 0ustar0000000000000000Cabal-Version: 2.0 Name: primitive Version: 0.8.0.0 License: BSD3 License-File: LICENSE Author: Roman Leshchinskiy Maintainer: libraries@haskell.org Copyright: (c) Roman Leshchinskiy 2009-2012 Homepage: https://github.com/haskell/primitive Bug-Reports: https://github.com/haskell/primitive/issues Category: Data Synopsis: Primitive memory-related operations Build-Type: Simple Description: This package provides various primitive memory-related operations. Extra-Source-Files: changelog.md test/*.hs test/LICENSE Tested-With: GHC == 8.0.2 GHC == 8.2.2 GHC == 8.4.4 GHC == 8.6.5 GHC == 8.8.4 GHC == 8.10.7 GHC == 9.0.2 GHC == 9.2.5 GHC == 9.4.4 Library Default-Language: Haskell2010 Default-Extensions: TypeOperators Other-Extensions: BangPatterns, CPP, DeriveDataTypeable, MagicHash, TypeFamilies, UnboxedTuples, UnliftedFFITypes Exposed-Modules: Control.Monad.Primitive Data.Primitive Data.Primitive.MachDeps Data.Primitive.Types Data.Primitive.Array Data.Primitive.ByteArray Data.Primitive.PrimArray Data.Primitive.SmallArray Data.Primitive.Ptr Data.Primitive.MutVar Data.Primitive.MVar Data.Primitive.PrimVar Other-Modules: Data.Primitive.Internal.Operations Build-Depends: base >= 4.9 && < 4.19 , deepseq >= 1.1 && < 1.5 , transformers >= 0.5 && < 0.7 , template-haskell >= 2.11 if impl(ghc >= 9.2) cpp-options: -DHAVE_KEEPALIVE if impl(ghc < 9.4) build-depends: data-array-byte >= 0.1 && < 0.1.1 Ghc-Options: -O2 Include-Dirs: cbits Install-Includes: primitive-memops.h includes: primitive-memops.h c-sources: cbits/primitive-memops.c if !os(solaris) cc-options: -ftree-vectorize if arch(i386) || arch(x86_64) cc-options: -msse2 test-suite test-qc Default-Language: Haskell2010 hs-source-dirs: test test/src main-is: main.hs Other-Modules: PrimLaws type: exitcode-stdio-1.0 build-depends: base , base-orphans , ghc-prim , primitive , quickcheck-classes-base >= 0.6 && <0.7 , QuickCheck >= 2.13 && < 2.15 , tasty ^>= 1.2 || ^>= 1.3 || ^>= 1.4 , tasty-quickcheck , tagged , transformers >= 0.5 , transformers-compat cpp-options: -DHAVE_UNARY_LAWS ghc-options: -O2 benchmark bench Default-Language: Haskell2010 hs-source-dirs: bench main-is: main.hs type: exitcode-stdio-1.0 ghc-options: -O2 other-modules: Array.Traverse.Closure Array.Traverse.Unsafe ByteArray.Compare PrimArray.Compare PrimArray.Traverse build-depends: base , primitive , deepseq , tasty-bench , transformers >= 0.5 source-repository head type: git location: https://github.com/haskell/primitive primitive-0.8.0.0/test/0000755000000000000000000000000007346545000013035 5ustar0000000000000000primitive-0.8.0.0/test/LICENSE0000644000000000000000000000301607346545000014042 0ustar0000000000000000Copyright (c) 2008-2009, Roman Leshchinskiy All rights reserved. Redistribution and use in source and binary forms, with or without modification, are permitted provided that the following conditions are met: - Redistributions of source code must retain the above copyright notice, this list of conditions and the following disclaimer. - Redistributions in binary form must reproduce the above copyright notice, this list of conditions and the following disclaimer in the documentation and/or other materials provided with the distribution. - Neither name of the University nor the names of its contributors may be used to endorse or promote products derived from this software without specific prior written permission. THIS SOFTWARE IS PROVIDED BY THE UNIVERSITY COURT OF THE UNIVERSITY OF GLASGOW AND THE CONTRIBUTORS "AS IS" AND ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED. IN NO EVENT SHALL THE UNIVERSITY COURT OF THE UNIVERSITY OF GLASGOW OR THE CONTRIBUTORS BE LIABLE FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. primitive-0.8.0.0/test/main.hs0000644000000000000000000004646107346545000014330 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE StandaloneDeriving #-} {-# OPTIONS_GHC -fno-warn-orphans #-} #if __GLASGOW_HASKELL__ >= 805 {-# LANGUAGE GeneralizedNewtypeDeriving #-} {-# LANGUAGE DerivingStrategies #-} {-# LANGUAGE DerivingVia #-} {-# LANGUAGE TypeInType #-} #endif import Control.Monad import Control.Monad.ST import Data.Primitive import Data.Word import Data.Proxy (Proxy(..)) import GHC.Int import GHC.IO import GHC.Exts import Data.Function (on) import Control.Applicative (Const(..)) import PrimLaws (primLaws) import Data.Functor.Identity (Identity(..)) import qualified Data.Monoid as Monoid import Data.Ord (Down(..)) import Data.Semigroup (stimes, stimesMonoid) import qualified Data.Semigroup as Semigroup #if !(MIN_VERSION_base(4,11,0)) import Data.Monoid ((<>)) #endif #if __GLASGOW_HASKELL__ >= 805 import Foreign.Storable (Storable) #endif import Data.Orphans () import Test.Tasty (defaultMain,testGroup,TestTree) import Test.QuickCheck (Arbitrary,Arbitrary1,Gen,CoArbitrary,Function,(===),(==>)) import qualified Test.Tasty.QuickCheck as TQC import qualified Test.QuickCheck as QC import qualified Test.QuickCheck.Classes.Base as QCC import qualified Test.QuickCheck.Classes.Base.IsList as QCCL import qualified Data.List as L main :: IO () main = do testArray testByteArray defaultMain $ testGroup "properties" [ testGroup "Array" [ lawsToTest (QCC.eqLaws (Proxy :: Proxy (Array Int))) , lawsToTest (QCC.ordLaws (Proxy :: Proxy (Array Int))) , lawsToTest (QCC.monoidLaws (Proxy :: Proxy (Array Int))) , lawsToTest (QCC.showReadLaws (Proxy :: Proxy (Array Int))) , lawsToTest (QCC.functorLaws (Proxy1 :: Proxy1 Array)) , lawsToTest (QCC.applicativeLaws (Proxy1 :: Proxy1 Array)) , lawsToTest (QCC.monadLaws (Proxy1 :: Proxy1 Array)) , lawsToTest (QCC.foldableLaws (Proxy1 :: Proxy1 Array)) , lawsToTest (QCC.traversableLaws (Proxy1 :: Proxy1 Array)) , lawsToTest (QCC.isListLaws (Proxy :: Proxy (Array Int))) , TQC.testProperty "mapArray'" (QCCL.mapProp int16 int32 mapArray') , TQC.testProperty "*>" $ \(xs :: Array Int) (ys :: Array Int) -> toList (xs *> ys) === (toList xs *> toList ys) , TQC.testProperty "<*" $ \(xs :: Array Int) (ys :: Array Int) -> toList (xs <* ys) === (toList xs <* toList ys) , lawsToTest (QCC.semigroupLaws (Proxy :: Proxy (Array Int))) , TQC.testProperty "stimes" $ \(QC.NonNegative (n :: Int)) (xs :: Array Int) -> stimes n xs == stimesMonoid n xs ] , testGroup "SmallArray" [ lawsToTest (QCC.eqLaws (Proxy :: Proxy (SmallArray Int))) , lawsToTest (QCC.ordLaws (Proxy :: Proxy (SmallArray Int))) , lawsToTest (QCC.monoidLaws (Proxy :: Proxy (SmallArray Int))) , lawsToTest (QCC.showReadLaws (Proxy :: Proxy (Array Int))) , lawsToTest (QCC.functorLaws (Proxy1 :: Proxy1 SmallArray)) , lawsToTest (QCC.applicativeLaws (Proxy1 :: Proxy1 SmallArray)) , lawsToTest (QCC.monadLaws (Proxy1 :: Proxy1 SmallArray)) , lawsToTest (QCC.foldableLaws (Proxy1 :: Proxy1 SmallArray)) , lawsToTest (QCC.traversableLaws (Proxy1 :: Proxy1 SmallArray)) , lawsToTest (QCC.isListLaws (Proxy :: Proxy (SmallArray Int))) , TQC.testProperty "mapSmallArray'" (QCCL.mapProp int16 int32 mapSmallArray') , TQC.testProperty "*>" $ \(xs :: SmallArray Int) (ys :: SmallArray Int) -> toList (xs *> ys) === (toList xs *> toList ys) , TQC.testProperty "<*" $ \(xs :: SmallArray Int) (ys :: SmallArray Int) -> toList (xs <* ys) === (toList xs <* toList ys) , lawsToTest (QCC.semigroupLaws (Proxy :: Proxy (SmallArray Int))) , TQC.testProperty "stimes" $ \(QC.NonNegative (n :: Int)) (xs :: SmallArray Int) -> stimes n xs == stimesMonoid n xs ] , testGroup "ByteArray" [ testGroup "Ordering" [ TQC.testProperty "equality" byteArrayEqProp , TQC.testProperty "compare" byteArrayCompareProp , testGroup "Filling" [ TQC.testProperty "Int8" (setByteArrayProp (Proxy :: Proxy Int8)) , TQC.testProperty "Int16" (setByteArrayProp (Proxy :: Proxy Int16)) , TQC.testProperty "Int32" (setByteArrayProp (Proxy :: Proxy Int32)) , TQC.testProperty "Int64" (setByteArrayProp (Proxy :: Proxy Int64)) , TQC.testProperty "Int" (setByteArrayProp (Proxy :: Proxy Int)) , TQC.testProperty "Word8" (setByteArrayProp (Proxy :: Proxy Word8)) , TQC.testProperty "Word16" (setByteArrayProp (Proxy :: Proxy Word16)) , TQC.testProperty "Word32" (setByteArrayProp (Proxy :: Proxy Word32)) , TQC.testProperty "Word64" (setByteArrayProp (Proxy :: Proxy Word64)) , TQC.testProperty "Word" (setByteArrayProp (Proxy :: Proxy Word)) ] ] , testGroup "Resize" [ TQC.testProperty "shrink" byteArrayShrinkProp , TQC.testProperty "grow" byteArrayGrowProp ] , lawsToTest (QCC.eqLaws (Proxy :: Proxy ByteArray)) , lawsToTest (QCC.ordLaws (Proxy :: Proxy ByteArray)) , lawsToTest (QCC.monoidLaws (Proxy :: Proxy ByteArray)) , lawsToTest (QCC.showReadLaws (Proxy :: Proxy (Array Int))) , lawsToTest (QCC.isListLaws (Proxy :: Proxy ByteArray)) , TQC.testProperty "foldrByteArray" (QCCL.foldrProp word8 foldrByteArray) , lawsToTest (QCC.semigroupLaws (Proxy :: Proxy ByteArray)) , TQC.testProperty "stimes" $ \(QC.NonNegative (n :: Int)) (xs :: ByteArray) -> stimes n xs == stimesMonoid n xs ] , testGroup "PrimArray" [ lawsToTest (QCC.eqLaws (Proxy :: Proxy (PrimArray Word16))) , lawsToTest (QCC.ordLaws (Proxy :: Proxy (PrimArray Word16))) , lawsToTest (QCC.monoidLaws (Proxy :: Proxy (PrimArray Word16))) , lawsToTest (QCC.isListLaws (Proxy :: Proxy (PrimArray Word16))) , TQC.testProperty "foldrPrimArray" (QCCL.foldrProp int16 foldrPrimArray) , TQC.testProperty "foldrPrimArray'" (QCCL.foldrProp int16 foldrPrimArray') , TQC.testProperty "foldlPrimArray" (QCCL.foldlProp int16 foldlPrimArray) , TQC.testProperty "foldlPrimArray'" (QCCL.foldlProp int16 foldlPrimArray') , TQC.testProperty "foldlPrimArrayM'" (QCCL.foldlMProp int16 foldlPrimArrayM') , TQC.testProperty "mapPrimArray" (QCCL.mapProp int16 int32 mapPrimArray) , TQC.testProperty "traversePrimArray" (QCCL.traverseProp int16 int32 traversePrimArray) , TQC.testProperty "traversePrimArrayP" (QCCL.traverseProp int16 int32 traversePrimArrayP) , TQC.testProperty "imapPrimArray" (QCCL.imapProp int16 int32 imapPrimArray) , TQC.testProperty "itraversePrimArray" (QCCL.imapMProp int16 int32 itraversePrimArray) , TQC.testProperty "itraversePrimArrayP" (QCCL.imapMProp int16 int32 itraversePrimArrayP) , TQC.testProperty "generatePrimArray" (QCCL.generateProp int16 generatePrimArray) , TQC.testProperty "generatePrimArrayA" (QCCL.generateMProp int16 generatePrimArrayA) , TQC.testProperty "generatePrimArrayP" (QCCL.generateMProp int16 generatePrimArrayP) , TQC.testProperty "replicatePrimArray" (QCCL.replicateProp int16 replicatePrimArray) , TQC.testProperty "replicatePrimArrayA" (QCCL.replicateMProp int16 replicatePrimArrayA) , TQC.testProperty "replicatePrimArrayP" (QCCL.replicateMProp int16 replicatePrimArrayP) , TQC.testProperty "filterPrimArray" (QCCL.filterProp int16 filterPrimArray) , TQC.testProperty "filterPrimArrayA" (QCCL.filterMProp int16 filterPrimArrayA) , TQC.testProperty "filterPrimArrayP" (QCCL.filterMProp int16 filterPrimArrayP) , TQC.testProperty "mapMaybePrimArray" (QCCL.mapMaybeProp int16 int32 mapMaybePrimArray) , TQC.testProperty "mapMaybePrimArrayA" (QCCL.mapMaybeMProp int16 int32 mapMaybePrimArrayA) , TQC.testProperty "mapMaybePrimArrayP" (QCCL.mapMaybeMProp int16 int32 mapMaybePrimArrayP) , lawsToTest (QCC.semigroupLaws (Proxy :: Proxy (PrimArray Word16))) , TQC.testProperty "stimes" $ \(QC.NonNegative (n :: Int)) (xs :: PrimArray Word16) -> stimes n xs == stimesMonoid n xs ] , testGroup "DefaultSetMethod" [ lawsToTest (primLaws (Proxy :: Proxy DefaultSetMethod)) ] #if __GLASGOW_HASKELL__ >= 805 , testGroup "PrimStorable" [ lawsToTest (QCC.storableLaws (Proxy :: Proxy Derived)) ] #endif , testGroup "Prim" [ renameLawsToTest "Word" (primLaws (Proxy :: Proxy Word)) , renameLawsToTest "Word8" (primLaws (Proxy :: Proxy Word8)) , renameLawsToTest "Word16" (primLaws (Proxy :: Proxy Word16)) , renameLawsToTest "Word32" (primLaws (Proxy :: Proxy Word32)) , renameLawsToTest "Word64" (primLaws (Proxy :: Proxy Word64)) , renameLawsToTest "Int" (primLaws (Proxy :: Proxy Int)) , renameLawsToTest "Int8" (primLaws (Proxy :: Proxy Int8)) , renameLawsToTest "Int16" (primLaws (Proxy :: Proxy Int16)) , renameLawsToTest "Int32" (primLaws (Proxy :: Proxy Int32)) , renameLawsToTest "Int64" (primLaws (Proxy :: Proxy Int64)) , renameLawsToTest "Const" (primLaws (Proxy :: Proxy (Const Int16 Int16))) , renameLawsToTest "Down" (primLaws (Proxy :: Proxy (Down Int16))) , renameLawsToTest "Identity" (primLaws (Proxy :: Proxy (Identity Int16))) , renameLawsToTest "Dual" (primLaws (Proxy :: Proxy (Monoid.Dual Int16))) , renameLawsToTest "Sum" (primLaws (Proxy :: Proxy (Monoid.Sum Int16))) , renameLawsToTest "Product" (primLaws (Proxy :: Proxy (Monoid.Product Int16))) , renameLawsToTest "First" (primLaws (Proxy :: Proxy (Semigroup.First Int16))) , renameLawsToTest "Last" (primLaws (Proxy :: Proxy (Semigroup.Last Int16))) , renameLawsToTest "Min" (primLaws (Proxy :: Proxy (Semigroup.Min Int16))) , renameLawsToTest "Max" (primLaws (Proxy :: Proxy (Semigroup.Max Int16))) ] ] deriving instance Arbitrary a => Arbitrary (Down a) -- Const, Dual, Sum, Product: all have Arbitrary instances defined -- in QuickCheck itself deriving instance Arbitrary a => Arbitrary (Semigroup.First a) deriving instance Arbitrary a => Arbitrary (Semigroup.Last a) deriving instance Arbitrary a => Arbitrary (Semigroup.Min a) deriving instance Arbitrary a => Arbitrary (Semigroup.Max a) word8 :: Proxy Word8 word8 = Proxy int16 :: Proxy Int16 int16 = Proxy int32 :: Proxy Int32 int32 = Proxy setByteArrayProp :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> QC.Property setByteArrayProp _ = QC.property $ \(QC.NonNegative (n :: Int)) (QC.NonNegative (off :: Int)) (QC.NonNegative (len :: Int)) (x :: a) (y :: a) -> (off < n && off + len <= n) ==> -- We use PrimArray in this test because it makes it easier to -- get the element-vs-byte distinction right. let actual = runST $ do m <- newPrimArray n forM_ (enumFromTo 0 (n - 1)) $ \ix -> writePrimArray m ix x setPrimArray m off len y unsafeFreezePrimArray m expected = runST $ do m <- newPrimArray n forM_ (enumFromTo 0 (n - 1)) $ \ix -> writePrimArray m ix x forM_ (enumFromTo off (off + len - 1)) $ \ix -> writePrimArray m ix y unsafeFreezePrimArray m in expected === actual -- Tests that using resizeByteArray to shrink a byte array produces -- the same results as calling Data.List.take on the list that the -- byte array corresponds to. byteArrayShrinkProp :: QC.Property byteArrayShrinkProp = QC.property $ \(QC.NonNegative (n :: Int)) (QC.NonNegative (m :: Int)) -> let large = max n m small = min n m xs = intsLessThan large ys = byteArrayFromList xs largeBytes = large * sizeOf (undefined :: Int) smallBytes = small * sizeOf (undefined :: Int) expected = byteArrayFromList (L.take small xs) actual = runST $ do mzs0 <- newByteArray largeBytes copyByteArray mzs0 0 ys 0 largeBytes mzs1 <- resizeMutableByteArray mzs0 smallBytes unsafeFreezeByteArray mzs1 in expected === actual -- Tests that using resizeByteArray with copyByteArray (to fill in the -- new empty space) to grow a byte array produces the same results as -- calling Data.List.++ on the lists corresponding to the original -- byte array and the appended byte array. byteArrayGrowProp :: QC.Property byteArrayGrowProp = QC.property $ \(QC.NonNegative (n :: Int)) (QC.NonNegative (m :: Int)) -> let large = max n m small = min n m xs1 = intsLessThan small xs2 = intsLessThan (large - small) ys1 = byteArrayFromList xs1 ys2 = byteArrayFromList xs2 largeBytes = large * sizeOf (undefined :: Int) smallBytes = small * sizeOf (undefined :: Int) expected = byteArrayFromList (xs1 ++ xs2) actual = runST $ do mzs0 <- newByteArray smallBytes copyByteArray mzs0 0 ys1 0 smallBytes mzs1 <- resizeMutableByteArray mzs0 largeBytes copyByteArray mzs1 smallBytes ys2 0 ((large - small) * sizeOf (undefined :: Int)) unsafeFreezeByteArray mzs1 in expected === actual -- Tests that writing stable ptrs to a PrimArray, reading them back -- out, and then dereferencing them gives correct results. --stablePtrPrimProp :: QC.Property --stablePtrPrimProp = QC.property $ \(xs :: [Integer]) -> unsafePerformIO $ do -- ptrs <- mapM newStablePtr xs -- let ptrs' = primArrayToList (primArrayFromList ptrs) -- ys <- mapM deRefStablePtr ptrs' -- mapM_ freeStablePtr ptrs' -- return (xs === ys) --stablePtrPrimBlockProp :: QC.Property --stablePtrPrimBlockProp = QC.property $ \(x :: Word) (QC.NonNegative (len :: Int)) -> unsafePerformIO $ do -- ptr <- newStablePtr x -- let ptrs' = replicatePrimArray len ptr -- let go ix = if ix < len -- then do -- n <- deRefStablePtr (indexPrimArray ptrs' ix) -- ns <- go (ix + 1) -- return (n : ns) -- else return [] -- ys <- go 0 -- freeStablePtr ptr -- return (L.replicate len x === ys) -- Provide the non-negative integers up to the bound. For example: -- -- >>> intsLessThan 5 -- [0,1,2,3,4] intsLessThan :: Int -> [Int] intsLessThan i = if i < 1 then [] else (i - 1) : intsLessThan (i - 1) byteArrayCompareProp :: QC.Property byteArrayCompareProp = QC.property $ \(xs :: [Word8]) (ys :: [Word8]) -> compareLengthFirst xs ys === compare (byteArrayFromList xs) (byteArrayFromList ys) byteArrayEqProp :: QC.Property byteArrayEqProp = QC.property $ \(xs :: [Word8]) (ys :: [Word8]) -> (compareLengthFirst xs ys == EQ) === (byteArrayFromList xs == byteArrayFromList ys) compareLengthFirst :: [Word8] -> [Word8] -> Ordering compareLengthFirst xs ys = (compare `on` length) xs ys <> compare xs ys -- on GHC 7.4, Proxy is not polykinded, so we need this instead. data Proxy1 (f :: * -> *) = Proxy1 lawsToTest :: QCC.Laws -> TestTree lawsToTest (QCC.Laws name pairs) = testGroup name (map (uncurry TQC.testProperty) pairs) renameLawsToTest :: String -> QCC.Laws -> TestTree renameLawsToTest name (QCC.Laws _ pairs) = testGroup name (map (uncurry TQC.testProperty) pairs) testArray :: IO () testArray = do arr <- newArray 1 'A' let unit = case writeArray arr 0 'B' of IO f -> case f realWorld# of (# _, _ #) -> () c1 <- readArray arr 0 return $! unit c2 <- readArray arr 0 if c1 == 'A' && c2 == 'B' then return () else error $ "Expected AB, got: " ++ show (c1, c2) testByteArray :: IO () testByteArray = do let arr1 = mkByteArray ([0xde, 0xad, 0xbe, 0xef] :: [Word8]) arr2 = mkByteArray ([0xde, 0xad, 0xbe, 0xef] :: [Word8]) arr3 = mkByteArray ([0xde, 0xad, 0xbe, 0xee] :: [Word8]) arr4 = mkByteArray ([0xde, 0xad, 0xbe, 0xdd] :: [Word8]) arr5 = mkByteArray ([0xde, 0xad, 0xbe, 0xef, 0xde, 0xad, 0xbe, 0xdd] :: [Word8]) arr6 = mkByteArray ([0xde, 0xad, 0x00, 0x01, 0xb0] :: [Word8]) when (show arr1 /= "[0xde, 0xad, 0xbe, 0xef]") $ fail $ "ByteArray Show incorrect: "++show arr1 when (show arr6 /= "[0xde, 0xad, 0x00, 0x01, 0xb0]") $ fail $ "ByteArray Show incorrect: "++ show arr6 when (compareByteArrays arr3 1 arr4 1 3 /= GT) $ fail $ "arr3[1,3] should be greater than arr4[1,3]" when (compareByteArrays arr3 0 arr4 1 3 /= GT) $ fail $ "arr3[0,3] should be greater than arr4[1,3]" when (compareByteArrays arr5 1 arr2 1 3 /= EQ) $ fail $ "arr3[1,3] should be equal to than arr4[1,3]" unless (arr1 > arr3) $ fail $ "ByteArray Ord incorrect" unless (arr1 == arr2) $ fail $ "ByteArray Eq incorrect" unless (mappend arr1 arr4 == arr5) $ fail $ "ByteArray Monoid mappend incorrect" unless (mappend arr1 (mappend arr3 arr4) == mappend (mappend arr1 arr3) arr4) $ fail $ "ByteArray Monoid mappend not associative" unless (mconcat [arr1,arr2,arr3,arr4,arr5] == (arr1 <> arr2 <> arr3 <> arr4 <> arr5)) $ fail $ "ByteArray Monoid mconcat incorrect" unless (stimes (3 :: Int) arr4 == (arr4 <> arr4 <> arr4)) $ fail $ "ByteArray Semigroup stimes incorrect" mkByteArray :: Prim a => [a] -> ByteArray mkByteArray xs = runST $ do marr <- newByteArray (length xs * sizeOf (head xs)) sequence_ $ zipWith (writeByteArray marr) [0..] xs unsafeFreezeByteArray marr instance Arbitrary1 Array where liftArbitrary elemGen = fmap fromList (QC.liftArbitrary elemGen) instance Arbitrary a => Arbitrary (Array a) where arbitrary = fmap fromList QC.arbitrary instance Arbitrary1 SmallArray where liftArbitrary elemGen = fmap smallArrayFromList (QC.liftArbitrary elemGen) instance Arbitrary a => Arbitrary (SmallArray a) where arbitrary = fmap smallArrayFromList QC.arbitrary instance Arbitrary ByteArray where arbitrary = do xs <- QC.arbitrary :: Gen [Word8] return $ runST $ do a <- newByteArray (L.length xs) iforM_ xs $ \ix x -> do writeByteArray a ix x unsafeFreezeByteArray a instance (Arbitrary a, Prim a) => Arbitrary (PrimArray a) where arbitrary = do xs <- QC.arbitrary :: Gen [a] return $ runST $ do a <- newPrimArray (L.length xs) iforM_ xs $ \ix x -> do writePrimArray a ix x unsafeFreezePrimArray a instance (Prim a, CoArbitrary a) => CoArbitrary (PrimArray a) where coarbitrary x = QC.coarbitrary (primArrayToList x) instance (Prim a, Function a) => Function (PrimArray a) where function = QC.functionMap primArrayToList primArrayFromList iforM_ :: Monad m => [a] -> (Int -> a -> m b) -> m () iforM_ xs0 f = go 0 xs0 where go !_ [] = return () go !ix (x : xs) = f ix x >> go (ix + 1) xs newtype DefaultSetMethod = DefaultSetMethod Int16 deriving (Eq,Show,Arbitrary) instance Prim DefaultSetMethod where sizeOf# _ = sizeOf# (undefined :: Int16) alignment# _ = alignment# (undefined :: Int16) indexByteArray# arr ix = DefaultSetMethod (indexByteArray# arr ix) readByteArray# arr ix s0 = case readByteArray# arr ix s0 of (# s1, n #) -> (# s1, DefaultSetMethod n #) writeByteArray# arr ix (DefaultSetMethod n) s0 = writeByteArray# arr ix n s0 setByteArray# = defaultSetByteArray# indexOffAddr# addr off = DefaultSetMethod (indexOffAddr# addr off) readOffAddr# addr off s0 = case readOffAddr# addr off s0 of (# s1, n #) -> (# s1, DefaultSetMethod n #) writeOffAddr# addr off (DefaultSetMethod n) s0 = writeOffAddr# addr off n s0 setOffAddr# = defaultSetOffAddr# #if __GLASGOW_HASKELL__ >= 805 newtype Derived = Derived Int16 deriving stock (Eq, Show) deriving newtype (Arbitrary, Prim) deriving Storable via (PrimStorable Derived) #endif primitive-0.8.0.0/test/src/0000755000000000000000000000000007346545000013624 5ustar0000000000000000primitive-0.8.0.0/test/src/PrimLaws.hs0000644000000000000000000001307007346545000015717 0ustar0000000000000000{-# LANGUAGE BangPatterns #-} {-# LANGUAGE CPP #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UnboxedTuples #-} {-# OPTIONS_GHC -Wall #-} -- This module is almost an exact copy of the unexported module -- Test.QuickCheck.Classes.Prim from quickcheck-classes. We cannot depend -- on quickcheck-classes in the test suite since that would imply a circular -- dependency between primitive and quickcheck-classes. Instead, we copy -- this one module and then depend on quickcheck-classes-base to get -- everything else we need. module PrimLaws ( primLaws ) where import Control.Applicative import Control.Monad.Primitive (primitive_) import Control.Monad.ST import Data.Proxy (Proxy) import Data.Primitive.PrimArray import Data.Primitive.ByteArray import Data.Primitive.Types import Data.Primitive.Ptr import Foreign.Marshal.Alloc import GHC.Exts (State#,Int#,Int(I#),(+#),(<#)) import GHC.Exts (IsList(fromList,toList)) import System.IO.Unsafe import Test.QuickCheck hiding ((.&.)) import qualified Data.List as L import qualified Data.Primitive as P import Test.QuickCheck.Classes.Base (Laws(..)) import Test.QuickCheck.Classes.Internal (isTrue#) -- | Test that a 'Prim' instance obey the several laws. primLaws :: (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Laws primLaws p = Laws "Prim" [ ("ByteArray Put-Get (you get back what you put in)", primPutGetByteArray p) , ("ByteArray Get-Put (putting back what you got out has no effect)", primGetPutByteArray p) , ("ByteArray Put-Put (putting twice is same as putting once)", primPutPutByteArray p) , ("ByteArray Set Range", primSetByteArray p) , ("ByteArray List Conversion Roundtrips", primListByteArray p) , ("Ptr Put-Get (you get back what you put in)", primPutGetAddr p) , ("Ptr List Conversion Roundtrips", primListAddr p) ] primListAddr :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property primListAddr _ = property $ \(as :: [a]) -> unsafePerformIO $ do let len = L.length as ptr :: Ptr a <- mallocBytes (len * P.sizeOf (undefined :: a)) let go :: Int -> [a] -> IO () go !ix xs = case xs of [] -> return () (x : xsNext) -> do writeOffPtr ptr ix x go (ix + 1) xsNext go 0 as let rebuild :: Int -> IO [a] rebuild !ix = if ix < len then (:) <$> readOffPtr ptr ix <*> rebuild (ix + 1) else return [] asNew <- rebuild 0 free ptr return (as == asNew) primPutGetByteArray :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property primPutGetByteArray _ = property $ \(a :: a) len -> (len > 0) ==> do ix <- choose (0,len - 1) return $ runST $ do arr <- newPrimArray len writePrimArray arr ix a a' <- readPrimArray arr ix return (a == a') primGetPutByteArray :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property primGetPutByteArray _ = property $ \(as :: [a]) -> (not (L.null as)) ==> do let arr1 = primArrayFromList as :: PrimArray a len = L.length as ix <- choose (0,len - 1) arr2 <- return $ runST $ do marr <- newPrimArray len copyPrimArray marr 0 arr1 0 len a <- readPrimArray marr ix writePrimArray marr ix a unsafeFreezePrimArray marr return (arr1 == arr2) primPutPutByteArray :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property primPutPutByteArray _ = property $ \(a :: a) (as :: [a]) -> (not (L.null as)) ==> do let arr1 = primArrayFromList as :: PrimArray a len = L.length as ix <- choose (0,len - 1) (arr2,arr3) <- return $ runST $ do marr2 <- newPrimArray len copyPrimArray marr2 0 arr1 0 len writePrimArray marr2 ix a marr3 <- newPrimArray len copyMutablePrimArray marr3 0 marr2 0 len arr2 <- unsafeFreezePrimArray marr2 writePrimArray marr3 ix a arr3 <- unsafeFreezePrimArray marr3 return (arr2,arr3) return (arr2 == arr3) primPutGetAddr :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property primPutGetAddr _ = property $ \(a :: a) len -> (len > 0) ==> do ix <- choose (0,len - 1) return $ unsafePerformIO $ do ptr :: Ptr a <- mallocBytes (len * P.sizeOf (undefined :: a)) writeOffPtr ptr ix a a' <- readOffPtr ptr ix free ptr return (a == a') primSetByteArray :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property primSetByteArray _ = property $ \(as :: [a]) (z :: a) -> do let arr1 = primArrayFromList as :: PrimArray a len = L.length as x <- choose (0,len) y <- choose (0,len) let lo = min x y hi = max x y return $ runST $ do marr2 <- newPrimArray len copyPrimArray marr2 0 arr1 0 len marr3 <- newPrimArray len copyPrimArray marr3 0 arr1 0 len setPrimArray marr2 lo (hi - lo) z internalDefaultSetPrimArray marr3 lo (hi - lo) z arr2 <- unsafeFreezePrimArray marr2 arr3 <- unsafeFreezePrimArray marr3 return (arr2 == arr3) primListByteArray :: forall a. (Prim a, Eq a, Arbitrary a, Show a) => Proxy a -> Property primListByteArray _ = property $ \(as :: [a]) -> as == toList (fromList as :: PrimArray a) internalDefaultSetPrimArray :: Prim a => MutablePrimArray s a -> Int -> Int -> a -> ST s () internalDefaultSetPrimArray (MutablePrimArray arr) (I# i) (I# len) ident = primitive_ (internalDefaultSetByteArray# arr i len ident) internalDefaultSetByteArray# :: Prim a => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s internalDefaultSetByteArray# arr# i# len# ident = go 0# where go ix# s0 = if isTrue# (ix# <# len#) then case writeByteArray# arr# (i# +# ix#) ident s0 of s1 -> go (ix# +# 1#) s1 else s0