primitive-0.7.1.0: Primitive memory-related operations

Copyright(c) Roman Leshchinskiy 2009-2012
LicenseBSD-style
MaintainerRoman Leshchinskiy <rl@cse.unsw.edu.au>
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Primitive.Types

Description

Basic types and classes for primitive array operations

Synopsis

Documentation

class Prim a where Source #

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.

Methods

sizeOf# :: a -> Int# Source #

Size of values of type a. The argument is not used.

alignment# :: a -> Int# Source #

Alignment of values of type a. The argument is not used.

indexByteArray# :: ByteArray# -> Int# -> a Source #

Read a value from the array. The offset is in elements of type a rather than in bytes.

readByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, a#) Source #

Read a value from the mutable array. The offset is in elements of type a rather than in bytes.

writeByteArray# :: MutableByteArray# s -> Int# -> a -> State# s -> State# s Source #

Write a value to the mutable array. The offset is in elements of type a rather than in bytes.

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s Source #

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.

indexOffAddr# :: Addr# -> Int# -> a Source #

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.

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, a#) Source #

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.

writeOffAddr# :: Addr# -> Int# -> a -> State# s -> State# s Source #

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.

setOffAddr# :: Addr# -> Int# -> Int# -> a -> State# s -> State# s Source #

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.

Instances
Prim Char Source # 
Instance details

Defined in Data.Primitive.Types

Prim Double Source # 
Instance details

Defined in Data.Primitive.Types

Prim Float Source # 
Instance details

Defined in Data.Primitive.Types

Prim Int Source # 
Instance details

Defined in Data.Primitive.Types

Prim Int8 Source # 
Instance details

Defined in Data.Primitive.Types

Prim Int16 Source # 
Instance details

Defined in Data.Primitive.Types

Prim Int32 Source # 
Instance details

Defined in Data.Primitive.Types

Prim Int64 Source # 
Instance details

Defined in Data.Primitive.Types

Prim Word Source # 
Instance details

Defined in Data.Primitive.Types

Prim Word8 Source # 
Instance details

Defined in Data.Primitive.Types

Prim Word16 Source # 
Instance details

Defined in Data.Primitive.Types

Prim Word32 Source # 
Instance details

Defined in Data.Primitive.Types

Prim Word64 Source # 
Instance details

Defined in Data.Primitive.Types

Prim CDev Source # 
Instance details

Defined in Data.Primitive.Types

Prim CIno Source # 
Instance details

Defined in Data.Primitive.Types

Prim CMode Source # 
Instance details

Defined in Data.Primitive.Types

Prim COff Source # 
Instance details

Defined in Data.Primitive.Types

Prim CPid Source # 
Instance details

Defined in Data.Primitive.Types

Prim CSsize Source # 
Instance details

Defined in Data.Primitive.Types

Prim CGid Source # 
Instance details

Defined in Data.Primitive.Types

Prim CNlink Source # 
Instance details

Defined in Data.Primitive.Types

Prim CUid Source # 
Instance details

Defined in Data.Primitive.Types

Prim CCc Source # 
Instance details

Defined in Data.Primitive.Types

Prim CSpeed Source # 
Instance details

Defined in Data.Primitive.Types

Prim CTcflag Source # 
Instance details

Defined in Data.Primitive.Types

Prim CRLim Source # 
Instance details

Defined in Data.Primitive.Types

Prim CBlkSize Source # 
Instance details

Defined in Data.Primitive.Types

Prim CBlkCnt Source # 
Instance details

Defined in Data.Primitive.Types

Prim CClockId Source # 
Instance details

Defined in Data.Primitive.Types

Prim CFsBlkCnt Source # 
Instance details

Defined in Data.Primitive.Types

Prim CFsFilCnt Source # 
Instance details

Defined in Data.Primitive.Types

Prim CId Source # 
Instance details

Defined in Data.Primitive.Types

Prim CKey Source # 
Instance details

Defined in Data.Primitive.Types

Prim CTimer Source # 
Instance details

Defined in Data.Primitive.Types

Prim Fd Source # 
Instance details

Defined in Data.Primitive.Types

Prim CChar Source # 
Instance details

Defined in Data.Primitive.Types

Prim CSChar Source # 
Instance details

Defined in Data.Primitive.Types

Prim CUChar Source # 
Instance details

Defined in Data.Primitive.Types

Prim CShort Source # 
Instance details

Defined in Data.Primitive.Types

Prim CUShort Source # 
Instance details

Defined in Data.Primitive.Types

Prim CInt Source # 
Instance details

Defined in Data.Primitive.Types

Prim CUInt Source # 
Instance details

Defined in Data.Primitive.Types

Prim CLong Source # 
Instance details

Defined in Data.Primitive.Types

Prim CULong Source # 
Instance details

Defined in Data.Primitive.Types

Prim CLLong Source # 
Instance details

Defined in Data.Primitive.Types

Prim CULLong Source # 
Instance details

Defined in Data.Primitive.Types

Prim CBool Source # 
Instance details

Defined in Data.Primitive.Types

Prim CFloat Source # 
Instance details

Defined in Data.Primitive.Types

Prim CDouble Source # 
Instance details

Defined in Data.Primitive.Types

Prim CPtrdiff Source # 
Instance details

Defined in Data.Primitive.Types

Prim CSize Source # 
Instance details

Defined in Data.Primitive.Types

Prim CWchar Source # 
Instance details

Defined in Data.Primitive.Types

Prim CSigAtomic Source # 
Instance details

Defined in Data.Primitive.Types

Prim CClock Source # 
Instance details

Defined in Data.Primitive.Types

Prim CTime Source # 
Instance details

Defined in Data.Primitive.Types

Prim CUSeconds Source # 
Instance details

Defined in Data.Primitive.Types

Prim CSUSeconds Source # 
Instance details

Defined in Data.Primitive.Types

Prim CIntPtr Source # 
Instance details

Defined in Data.Primitive.Types

Prim CUIntPtr Source # 
Instance details

Defined in Data.Primitive.Types

Prim CIntMax Source # 
Instance details

Defined in Data.Primitive.Types

Prim CUIntMax Source # 
Instance details

Defined in Data.Primitive.Types

Prim WordPtr Source #

Since: 0.7.1.0

Instance details

Defined in Data.Primitive.Types

Prim IntPtr Source #

Since: 0.7.1.0

Instance details

Defined in Data.Primitive.Types

Prim (StablePtr a) Source # 
Instance details

Defined in Data.Primitive.Types

Prim (Ptr a) Source # 
Instance details

Defined in Data.Primitive.Types

Prim (FunPtr a) Source # 
Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Min a) Source #

Since: 0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Max a) Source #

Since: 0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (First a) Source #

Since: 0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Last a) Source #

Since: 0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Identity a) Source #

Since: 0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Dual a) Source #

Since: 0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Sum a) Source #

Since: 0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Product a) Source #

Since: 0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Down a) Source #

Since: 0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Const a b) Source #

Since: 0.6.5.0

Instance details

Defined in Data.Primitive.Types

sizeOf :: Prim a => a -> Int Source #

Size of values of type a. The argument is not used.

This function has existed since 0.1, but was moved from Primitive to Types in version 0.6.3.0

alignment :: Prim a => a -> Int Source #

Alignment of values of type a. The argument is not used.

This function has existed since 0.1, but was moved from Primitive to Types in version 0.6.3.0

defaultSetByteArray# :: Prim a => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s Source #

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#

defaultSetOffAddr# :: Prim a => Addr# -> Int# -> Int# -> a -> State# s -> State# s Source #

An implementation of setOffAddr# that calls writeOffAddr# to set each element. The documentation of defaultSetByteArray# provides an example of how to use this.

newtype PrimStorable a Source #

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.

Constructors

PrimStorable 

Fields

Instances
Prim a => Storable (PrimStorable a) Source # 
Instance details

Defined in Data.Primitive.Types

data Ptr a #

A value of type Ptr a represents a pointer to an object, or an array of objects, which may be marshalled to or from Haskell values of type a.

The type a will often be an instance of class Storable which provides the marshalling operations. However this is not essential, and you can provide your own operations to access the pointer. For example you might write small foreign functions to get or set the fields of a C struct.

Constructors

Ptr Addr# 
Instances
NFData1 Ptr

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

liftRnf :: (a -> ()) -> Ptr a -> () #

Generic1 (URec (Ptr ()) :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 (URec (Ptr ())) :: k -> Type #

Methods

from1 :: URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a #

to1 :: Rep1 (URec (Ptr ())) a -> URec (Ptr ()) a #

Eq (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

(==) :: Ptr a -> Ptr a -> Bool #

(/=) :: Ptr a -> Ptr a -> Bool #

Data a => Data (Ptr a)

Since: base-4.8.0.0

Instance details

Defined in Data.Data

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Ptr a -> c (Ptr a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Ptr a) #

toConstr :: Ptr a -> Constr #

dataTypeOf :: Ptr a -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Ptr a)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Ptr a)) #

gmapT :: (forall b. Data b => b -> b) -> Ptr a -> Ptr a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Ptr a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Ptr a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Ptr a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Ptr a -> m (Ptr a) #

Ord (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

compare :: Ptr a -> Ptr a -> Ordering #

(<) :: Ptr a -> Ptr a -> Bool #

(<=) :: Ptr a -> Ptr a -> Bool #

(>) :: Ptr a -> Ptr a -> Bool #

(>=) :: Ptr a -> Ptr a -> Bool #

max :: Ptr a -> Ptr a -> Ptr a #

min :: Ptr a -> Ptr a -> Ptr a #

Show (Ptr a)

Since: base-2.1

Instance details

Defined in GHC.Ptr

Methods

showsPrec :: Int -> Ptr a -> ShowS #

show :: Ptr a -> String #

showList :: [Ptr a] -> ShowS #

Storable (Ptr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ptr a -> Int #

alignment :: Ptr a -> Int #

peekElemOff :: Ptr (Ptr a) -> Int -> IO (Ptr a) #

pokeElemOff :: Ptr (Ptr a) -> Int -> Ptr a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Ptr a) #

pokeByteOff :: Ptr b -> Int -> Ptr a -> IO () #

peek :: Ptr (Ptr a) -> IO (Ptr a) #

poke :: Ptr (Ptr a) -> Ptr a -> IO () #

NFData (Ptr a)

Since: deepseq-1.4.2.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Ptr a -> () #

Prim (Ptr a) Source # 
Instance details

Defined in Data.Primitive.Types

Functor (URec (Ptr ()) :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

fmap :: (a -> b) -> URec (Ptr ()) a -> URec (Ptr ()) b #

(<$) :: a -> URec (Ptr ()) b -> URec (Ptr ()) a #

Foldable (URec (Ptr ()) :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => URec (Ptr ()) m -> m #

foldMap :: Monoid m => (a -> m) -> URec (Ptr ()) a -> m #

foldr :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b #

foldr' :: (a -> b -> b) -> b -> URec (Ptr ()) a -> b #

foldl :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b #

foldl' :: (b -> a -> b) -> b -> URec (Ptr ()) a -> b #

foldr1 :: (a -> a -> a) -> URec (Ptr ()) a -> a #

foldl1 :: (a -> a -> a) -> URec (Ptr ()) a -> a #

toList :: URec (Ptr ()) a -> [a] #

null :: URec (Ptr ()) a -> Bool #

length :: URec (Ptr ()) a -> Int #

elem :: Eq a => a -> URec (Ptr ()) a -> Bool #

maximum :: Ord a => URec (Ptr ()) a -> a #

minimum :: Ord a => URec (Ptr ()) a -> a #

sum :: Num a => URec (Ptr ()) a -> a #

product :: Num a => URec (Ptr ()) a -> a #

Traversable (URec (Ptr ()) :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> URec (Ptr ()) a -> f (URec (Ptr ()) b) #

sequenceA :: Applicative f => URec (Ptr ()) (f a) -> f (URec (Ptr ()) a) #

mapM :: Monad m => (a -> m b) -> URec (Ptr ()) a -> m (URec (Ptr ()) b) #

sequence :: Monad m => URec (Ptr ()) (m a) -> m (URec (Ptr ()) a) #

Eq (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

(==) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(/=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

Ord (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

compare :: URec (Ptr ()) p -> URec (Ptr ()) p -> Ordering #

(<) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(<=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

(>=) :: URec (Ptr ()) p -> URec (Ptr ()) p -> Bool #

max :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

min :: URec (Ptr ()) p -> URec (Ptr ()) p -> URec (Ptr ()) p #

Generic (URec (Ptr ()) p) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (URec (Ptr ()) p) :: Type -> Type #

Methods

from :: URec (Ptr ()) p -> Rep (URec (Ptr ()) p) x #

to :: Rep (URec (Ptr ()) p) x -> URec (Ptr ()) p #

data URec (Ptr ()) (p :: k)

Used for marking occurrences of Addr#

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

data URec (Ptr ()) (p :: k) = UAddr {}
type Rep1 (URec (Ptr ()) :: k -> Type)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep1 (URec (Ptr ()) :: k -> Type) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UAddr" PrefixI True) (S1 (MetaSel (Just "uAddr#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UAddr :: k -> Type)))
type Rep (URec (Ptr ()) p)

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

type Rep (URec (Ptr ()) p) = D1 (MetaData "URec" "GHC.Generics" "base" False) (C1 (MetaCons "UAddr" PrefixI True) (S1 (MetaSel (Just "uAddr#") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (UAddr :: Type -> Type)))