pvar-0.1.1.0: Mutable variable with primitive values

Copyright(c) Alexey Kuleshevich 2020
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Primitive.PVar

Contents

Description

 
Synopsis

Documentation

PVar has significantly better performance characterisitcs over IORef, STRef and MutVar. This is because value is mutated directly in memory instead of following an extra pointer. Besides better performance there is another consequence of direct mutation, namely that values are always evaluated to normal form when being written into a PVar

Primitive variable

data PVar m a Source #

Mutable variable with primitive value.

Since: 0.1.0

Instances
Prim a => Storable (PVar IO a) Source #

poke+peek will result in a new copy of a PVar

Instance details

Defined in Data.Primitive.PVar.Internal

Methods

sizeOf :: PVar IO a -> Int #

alignment :: PVar IO a -> Int #

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

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

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

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

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

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

NFData (PVar m a) Source #

Values are already written into PVar in NF, this instance is trivial.

Instance details

Defined in Data.Primitive.PVar.Internal

Methods

rnf :: PVar m a -> () #

newPVar :: (PrimMonad m, Prim a) => a -> m (PVar m a) Source #

Create a mutable variable in unpinned memory (i.e. GC can move it) with an initial value. This is a prefered way to create a mutable variable, since it will not contribute to memory fragmentation. For pinned memory versions see newPinnedPVar and newAlignedPinnedPVar

Since: 0.1.0

withPVarST Source #

Arguments

:: Prim p 
=> p

Initial value assigned to the mutable variable

-> (forall s. PVar (ST s) p -> ST s a)

Action to run

-> a

Result produced by the ST action

Run an ST action on a mutable variable.

Since: 0.1.0

Generic Operations

readPVar :: (PrimMonad m, Prim a) => PVar m a -> m a Source #

Read a value from a mutable variable

Since: 0.1.0

writePVar :: (PrimMonad m, Prim a) => PVar m a -> a -> m () Source #

Write a value into a mutable variable

Since: 0.1.0

modifyPVar_ :: (PrimMonad m, Prim a) => PVar m a -> (a -> a) -> m () Source #

Apply a pure function to the contents of a mutable variable.

Since: 0.1.0

modifyPVar :: (PrimMonad m, Prim a) => PVar m a -> (a -> a) -> m a Source #

Apply a pure function to the contents of a mutable variable. Returns the old value.

Since: 0.1.0

modifyPVarM_ :: (PrimMonad m, Prim a) => PVar m a -> (a -> m a) -> m () Source #

Apply a monadic action to the contents of a mutable variable.

Since: 0.1.0

modifyPVarM :: (PrimMonad m, Prim a) => PVar m a -> (a -> m a) -> m a Source #

Apply a monadic action to the contents of a mutable variable. Returns the old value.

Since: 0.1.0

swapPVars_ :: (PrimMonad m, Prim a) => PVar m a -> PVar m a -> m () Source #

Swap contents of two mutable variables.

Since: 0.1.0

swapPVars :: (PrimMonad m, Prim a) => PVar m a -> PVar m a -> m (a, a) Source #

Swap contents of two mutable variables. Returns their old values.

Since: 0.1.0

copyPVar Source #

Arguments

:: (PrimMonad m, Prim a) 
=> PVar m a

Source variable

-> PVar m a

Destination variable

-> m () 

Copy contents of one mutable variable PVar into another

Since: 0.1.0

sizeOfPVar :: Prim a => PVar m a -> Int Source #

Size in bytes of a value stored inside the mutable variable. PVar itself is neither accessed nor evaluated.

Since: 0.1.0

alignmentPVar :: Prim a => PVar m a -> Int Source #

Alignment in bytes of the value stored inside of the mutable variable. PVar itself is neither accessed nor evaluated.

Since: 0.1.0

Pinned memory

In theory it is unsafe to mix Storable and Prim operations on the same chunk of memory, because some instances can have differnet memory layouts for the same type. This is highly uncommon in practice and if you are intermixing the two concepts together you probably already know what you are doing.

newPinnedPVar :: (PrimMonad m, Prim a) => a -> m (PVar m a) Source #

Create a mutable variable in pinned memory with an initial value.

Since: 0.1.0

newAlignedPinnedPVar :: (PrimMonad m, Prim a) => a -> m (PVar m a) Source #

Create a mutable variable in pinned memory with an initial value and aligned according to its alignment

Since: 0.1.0

withPtrPVar :: (PrimMonad m, Prim a) => PVar n a -> (Ptr a -> m b) -> m (Maybe b) Source #

Apply an action to the Ptr that references the mutable variable, but only if it is backed by pinned memory, cause otherwise it would be unsafe.

Since: 0.1.0

withStorablePVar Source #

Arguments

:: (PrimMonad m, Storable a) 
=> a

Initial value

-> (PVar m a -> Ptr a -> m b)

Action to run

-> m b 

Apply an action to the newly allocated PVar and to the Ptr that references it. Memory allocated with number of bytes specified by sizeOf a is allocated and pinned, therefore it is safe to operate directly with the pointer as well as over FFI. Returning the pointer from the supplied action would be very unsafe, therefore return the PVar if you still need it afterwards, garbage colelctor will cleanup the memory when it is no longer needed.

Since: 0.1.0

withAlignedStorablePVar Source #

Arguments

:: (PrimMonad m, Storable a) 
=> a

Initial value

-> (PVar m a -> Ptr a -> m b)

Action to run

-> m b 

Same withStorablePVar, except memory is aligned according to alignment.

Since: 0.1.0

copyPVarToPtr :: (PrimMonad m, Prim a) => PVar m a -> Ptr a -> m () Source #

Copy contents of a mutable variable PVar into a pointer Ptr

Since: 0.1.0

toForeignPtrPVar :: PVar IO a -> Maybe (ForeignPtr a) Source #

Convert PVar into a ForeignPtr, but only if it is backed by pinned memory.

Since: 0.1.0

isPinnedPVar :: PVar m a -> Bool Source #

Check if PVar is backed by pinned memory or not

Since: 0.1.0

peekPrim :: (Storable a, PrimMonad m) => Ptr a -> m a Source #

Use Storable reading functionality inside the PrimMonad.

Since: 0.1.0

pokePrim :: (Storable a, PrimMonad m) => Ptr a -> a -> m () Source #

Use Storable wrting functionality inside the PrimMonad.

Since: 0.1.0

Atomic operations

atomicModifyIntPVar :: PrimMonad m => PVar m Int -> (Int -> (Int, a)) -> m a Source #

Apply a function to an integer element of a PVar atomically. Implies a full memory barrier.

Since: 0.1.0

atomicModifyIntPVar_ :: PrimMonad m => PVar m Int -> (Int -> Int) -> m () Source #

Apply a function to an integer element of a PVar atomically. Returns the old value. Implies a full memory barrier.

Since: 0.1.0

atomicReadIntPVar :: PrimMonad m => PVar m Int -> m Int Source #

Create a new PVar in pinned memory with an initial value in it aligned on the size of an Int. Implies a full memory barrier.

Since: 0.1.0

atomicWriteIntPVar :: PrimMonad m => PVar m Int -> Int -> m () Source #

Write a value into an PVar atomically. Implies a full memory barrier.

Since: 0.1.0

casIntPVar Source #

Arguments

:: PrimMonad m 
=> PVar m Int

Variable to mutate

-> Int

Old expected value

-> Int

New value

-> m Int

Old actual value

Compare and swap. This is a function that is used to implement modifyIntPVar. Implies a full memory barrier.

Since: 0.1.0

atomicAddIntPVar :: PrimMonad m => PVar m Int -> Int -> m Int Source #

Add two numbers, corresponds to + done atomically. Returns the previous value of the mutable variable. Implies a full memory barrier.

Since: 0.1.0

atomicSubIntPVar :: PrimMonad m => PVar m Int -> Int -> m Int Source #

Subtract two numbers, corresponds to subtract done atomically. Returns the previous value of the mutable variable. Implies a full memory barrier.

Since: 0.1.0

atomicAndIntPVar :: PrimMonad m => PVar m Int -> Int -> m Int Source #

Binary conjuction (AND), corresponds to and done atomically. Returns the previous value of the mutable variable. Implies a full memory barrier.

Since: 0.1.0

atomicNandIntPVar :: PrimMonad m => PVar m Int -> Int -> m Int Source #

Binary negation of conjuction (Not AND), corresponds to \x y -> complement (x and y) done atomically. Returns the previous value of the mutable variable. Implies a full memory barrier.

Since: 0.1.0

atomicOrIntPVar :: PrimMonad m => PVar m Int -> Int -> m Int Source #

Binary disjunction (OR), corresponds to or done atomically. Returns the previous value of the mutable variable. Implies a full memory barrier.

Since: 0.1.0

atomicXorIntPVar :: PrimMonad m => PVar m Int -> Int -> m Int Source #

Binary exclusive disjunction (XOR), corresponds to xor done atomically. Returns the previous value of the mutable variable. Implies a full memory barrier.

Since: 0.1.0

atomicNotIntPVar :: PrimMonad m => PVar m Int -> m Int Source #

Binary negation (NOT), corresponds to ones' complement done atomically. Returns the previous value of the mutable variable. Implies a full memory barrier.

Since: 0.1.0

Re-exports

class Prim a #

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.

Instances
Prim Char 
Instance details

Defined in Data.Primitive.Types

Prim Double 
Instance details

Defined in Data.Primitive.Types

Prim Float 
Instance details

Defined in Data.Primitive.Types

Prim Int 
Instance details

Defined in Data.Primitive.Types

Prim Int8 
Instance details

Defined in Data.Primitive.Types

Prim Int16 
Instance details

Defined in Data.Primitive.Types

Prim Int32 
Instance details

Defined in Data.Primitive.Types

Prim Int64 
Instance details

Defined in Data.Primitive.Types

Prim Word 
Instance details

Defined in Data.Primitive.Types

Prim Word8 
Instance details

Defined in Data.Primitive.Types

Prim Word16 
Instance details

Defined in Data.Primitive.Types

Prim Word32 
Instance details

Defined in Data.Primitive.Types

Prim Word64 
Instance details

Defined in Data.Primitive.Types

Prim CDev 
Instance details

Defined in Data.Primitive.Types

Prim CIno 
Instance details

Defined in Data.Primitive.Types

Prim CMode 
Instance details

Defined in Data.Primitive.Types

Prim COff 
Instance details

Defined in Data.Primitive.Types

Prim CPid 
Instance details

Defined in Data.Primitive.Types

Prim CSsize 
Instance details

Defined in Data.Primitive.Types

Prim CGid 
Instance details

Defined in Data.Primitive.Types

Prim CNlink 
Instance details

Defined in Data.Primitive.Types

Prim CUid 
Instance details

Defined in Data.Primitive.Types

Prim CCc 
Instance details

Defined in Data.Primitive.Types

Prim CSpeed 
Instance details

Defined in Data.Primitive.Types

Prim CTcflag 
Instance details

Defined in Data.Primitive.Types

Prim CRLim 
Instance details

Defined in Data.Primitive.Types

Prim CBlkSize 
Instance details

Defined in Data.Primitive.Types

Prim CBlkCnt 
Instance details

Defined in Data.Primitive.Types

Prim CClockId 
Instance details

Defined in Data.Primitive.Types

Prim CFsBlkCnt 
Instance details

Defined in Data.Primitive.Types

Prim CFsFilCnt 
Instance details

Defined in Data.Primitive.Types

Prim CId 
Instance details

Defined in Data.Primitive.Types

Prim CKey 
Instance details

Defined in Data.Primitive.Types

Prim CTimer 
Instance details

Defined in Data.Primitive.Types

Prim Fd 
Instance details

Defined in Data.Primitive.Types

Prim CChar 
Instance details

Defined in Data.Primitive.Types

Prim CSChar 
Instance details

Defined in Data.Primitive.Types

Prim CUChar 
Instance details

Defined in Data.Primitive.Types

Prim CShort 
Instance details

Defined in Data.Primitive.Types

Prim CUShort 
Instance details

Defined in Data.Primitive.Types

Prim CInt 
Instance details

Defined in Data.Primitive.Types

Prim CUInt 
Instance details

Defined in Data.Primitive.Types

Prim CLong 
Instance details

Defined in Data.Primitive.Types

Prim CULong 
Instance details

Defined in Data.Primitive.Types

Prim CLLong 
Instance details

Defined in Data.Primitive.Types

Prim CULLong 
Instance details

Defined in Data.Primitive.Types

Prim CBool 
Instance details

Defined in Data.Primitive.Types

Prim CFloat 
Instance details

Defined in Data.Primitive.Types

Prim CDouble 
Instance details

Defined in Data.Primitive.Types

Prim CPtrdiff 
Instance details

Defined in Data.Primitive.Types

Prim CSize 
Instance details

Defined in Data.Primitive.Types

Prim CWchar 
Instance details

Defined in Data.Primitive.Types

Prim CSigAtomic 
Instance details

Defined in Data.Primitive.Types

Prim CClock 
Instance details

Defined in Data.Primitive.Types

Prim CTime 
Instance details

Defined in Data.Primitive.Types

Prim CUSeconds 
Instance details

Defined in Data.Primitive.Types

Prim CSUSeconds 
Instance details

Defined in Data.Primitive.Types

Prim CIntPtr 
Instance details

Defined in Data.Primitive.Types

Prim CUIntPtr 
Instance details

Defined in Data.Primitive.Types

Prim CIntMax 
Instance details

Defined in Data.Primitive.Types

Prim CUIntMax 
Instance details

Defined in Data.Primitive.Types

Prim (StablePtr a) 
Instance details

Defined in Data.Primitive.Types

Prim (Ptr a) 
Instance details

Defined in Data.Primitive.Types

Prim (FunPtr a) 
Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Min a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Max a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (First a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Last a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Identity a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Dual a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Sum a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Product a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Down a)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Prim a => Prim (Const a b)

Since: primitive-0.6.5.0

Instance details

Defined in Data.Primitive.Types

Methods

sizeOf# :: Const a b -> Int# #

alignment# :: Const a b -> Int# #

indexByteArray# :: ByteArray# -> Int# -> Const a b #

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

writeByteArray# :: MutableByteArray# s -> Int# -> Const a b -> State# s -> State# s #

setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Const a b -> State# s -> State# s #

indexOffAddr# :: Addr# -> Int# -> Const a b #

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

writeOffAddr# :: Addr# -> Int# -> Const a b -> State# s -> State# s #

setOffAddr# :: Addr# -> Int# -> Int# -> Const a b -> State# s -> State# s #

class Monad m => PrimMonad (m :: Type -> Type) #

Class of monads which can perform primitive state-transformer actions

Minimal complete definition

primitive

Associated Types

type PrimState (m :: Type -> Type) :: Type #

State token type

Instances
PrimMonad IO 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState IO :: Type #

Methods

primitive :: (State# (PrimState IO) -> (#State# (PrimState IO), a#)) -> IO a #

PrimMonad (ST s) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ST s) :: Type #

Methods

primitive :: (State# (PrimState (ST s)) -> (#State# (PrimState (ST s)), a#)) -> ST s a #

PrimMonad m => PrimMonad (MaybeT m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (MaybeT m) :: Type #

Methods

primitive :: (State# (PrimState (MaybeT m)) -> (#State# (PrimState (MaybeT m)), a#)) -> MaybeT m a #

PrimMonad m => PrimMonad (ListT m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ListT m) :: Type #

Methods

primitive :: (State# (PrimState (ListT m)) -> (#State# (PrimState (ListT m)), a#)) -> ListT m a #

(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (WriterT w m) :: Type #

Methods

primitive :: (State# (PrimState (WriterT w m)) -> (#State# (PrimState (WriterT w m)), a#)) -> WriterT w m a #

(Monoid w, PrimMonad m) => PrimMonad (AccumT w m)

Since: primitive-0.6.3.0

Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (AccumT w m) :: Type #

Methods

primitive :: (State# (PrimState (AccumT w m)) -> (#State# (PrimState (AccumT w m)), a#)) -> AccumT w m a #

(Monoid w, PrimMonad m) => PrimMonad (WriterT w m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (WriterT w m) :: Type #

Methods

primitive :: (State# (PrimState (WriterT w m)) -> (#State# (PrimState (WriterT w m)), a#)) -> WriterT w m a #

PrimMonad m => PrimMonad (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (StateT s m) :: Type #

Methods

primitive :: (State# (PrimState (StateT s m)) -> (#State# (PrimState (StateT s m)), a#)) -> StateT s m a #

PrimMonad m => PrimMonad (StateT s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (StateT s m) :: Type #

Methods

primitive :: (State# (PrimState (StateT s m)) -> (#State# (PrimState (StateT s m)), a#)) -> StateT s m a #

PrimMonad m => PrimMonad (SelectT r m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (SelectT r m) :: Type #

Methods

primitive :: (State# (PrimState (SelectT r m)) -> (#State# (PrimState (SelectT r m)), a#)) -> SelectT r m a #

PrimMonad m => PrimMonad (IdentityT m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (IdentityT m) :: Type #

Methods

primitive :: (State# (PrimState (IdentityT m)) -> (#State# (PrimState (IdentityT m)), a#)) -> IdentityT m a #

PrimMonad m => PrimMonad (ExceptT e m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ExceptT e m) :: Type #

Methods

primitive :: (State# (PrimState (ExceptT e m)) -> (#State# (PrimState (ExceptT e m)), a#)) -> ExceptT e m a #

(Error e, PrimMonad m) => PrimMonad (ErrorT e m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ErrorT e m) :: Type #

Methods

primitive :: (State# (PrimState (ErrorT e m)) -> (#State# (PrimState (ErrorT e m)), a#)) -> ErrorT e m a #

PrimMonad m => PrimMonad (ReaderT r m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ReaderT r m) :: Type #

Methods

primitive :: (State# (PrimState (ReaderT r m)) -> (#State# (PrimState (ReaderT r m)), a#)) -> ReaderT r m a #

PrimMonad m => PrimMonad (ContT r m)

Since: primitive-0.6.3.0

Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ContT r m) :: Type #

Methods

primitive :: (State# (PrimState (ContT r m)) -> (#State# (PrimState (ContT r m)), a#)) -> ContT r m a #

(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (RWST r w s m) :: Type #

Methods

primitive :: (State# (PrimState (RWST r w s m)) -> (#State# (PrimState (RWST r w s m)), a#)) -> RWST r w s m a #

(Monoid w, PrimMonad m) => PrimMonad (RWST r w s m) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (RWST r w s m) :: Type #

Methods

primitive :: (State# (PrimState (RWST r w s m)) -> (#State# (PrimState (RWST r w s m)), a#)) -> RWST r w s m a #

data RealWorld :: Type #

RealWorld is deeply magical. It is primitive, but it is not unlifted (hence ptrArg). We never manipulate values of type RealWorld; it's only used in the type system, to parameterise State#.

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

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 #

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

data ST s a #

The strict state-transformer monad. A computation of type ST s a transforms an internal state indexed by s, and returns a value of type a. The s parameter is either

  • an uninstantiated type variable (inside invocations of runST), or
  • RealWorld (inside invocations of stToIO).

It serves to keep the internal states of different invocations of runST separate from each other and from invocations of stToIO.

The >>= and >> operations are strict in the state (though not in values stored in the state). For example,

runST (writeSTRef _|_ v >>= f) = _|_
Instances
Monad (ST s)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

(>>=) :: ST s a -> (a -> ST s b) -> ST s b #

(>>) :: ST s a -> ST s b -> ST s b #

return :: a -> ST s a #

fail :: String -> ST s a #

Functor (ST s)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

fmap :: (a -> b) -> ST s a -> ST s b #

(<$) :: a -> ST s b -> ST s a #

MonadFail (ST s)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

fail :: String -> ST s a #

Applicative (ST s)

Since: base-4.4.0.0

Instance details

Defined in GHC.ST

Methods

pure :: a -> ST s a #

(<*>) :: ST s (a -> b) -> ST s a -> ST s b #

liftA2 :: (a -> b -> c) -> ST s a -> ST s b -> ST s c #

(*>) :: ST s a -> ST s b -> ST s b #

(<*) :: ST s a -> ST s b -> ST s a #

PrimMonad (ST s) 
Instance details

Defined in Control.Monad.Primitive

Associated Types

type PrimState (ST s) :: Type #

Methods

primitive :: (State# (PrimState (ST s)) -> (#State# (PrimState (ST s)), a#)) -> ST s a #

PrimBase (ST s) 
Instance details

Defined in Control.Monad.Primitive

Methods

internal :: ST s a -> State# (PrimState (ST s)) -> (#State# (PrimState (ST s)), a#) #

Show (ST s a)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

showsPrec :: Int -> ST s a -> ShowS #

show :: ST s a -> String #

showList :: [ST s a] -> ShowS #

Semigroup a => Semigroup (ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

(<>) :: ST s a -> ST s a -> ST s a #

sconcat :: NonEmpty (ST s a) -> ST s a #

stimes :: Integral b => b -> ST s a -> ST s a #

Monoid a => Monoid (ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

mempty :: ST s a #

mappend :: ST s a -> ST s a -> ST s a #

mconcat :: [ST s a] -> ST s a #

type PrimState (ST s) 
Instance details

Defined in Control.Monad.Primitive

type PrimState (ST s) = s

runST :: (forall s. ST s a) -> a #

Return the value computed by a state transformer computation. The forall ensures that the internal state used by the ST computation is inaccessible to the rest of the program.

class Storable a where #

The member functions of this class facilitate writing values of primitive types to raw memory (which may have been allocated with the above mentioned routines) and reading values from blocks of raw memory. The class, furthermore, includes support for computing the storage requirements and alignment restrictions of storable types.

Memory addresses are represented as values of type Ptr a, for some a which is an instance of class Storable. The type argument to Ptr helps provide some valuable type safety in FFI code (you can't mix pointers of different types without an explicit cast), while helping the Haskell type system figure out which marshalling method is needed for a given pointer.

All marshalling between Haskell and a foreign language ultimately boils down to translating Haskell data structures into the binary representation of a corresponding data structure of the foreign language and vice versa. To code this marshalling in Haskell, it is necessary to manipulate primitive data types stored in unstructured memory blocks. The class Storable facilitates this manipulation on all types for which it is instantiated, which are the standard basic types of Haskell, the fixed size Int types (Int8, Int16, Int32, Int64), the fixed size Word types (Word8, Word16, Word32, Word64), StablePtr, all types from Foreign.C.Types, as well as Ptr.

Minimal complete definition

sizeOf, alignment, (peek | peekElemOff | peekByteOff), (poke | pokeElemOff | pokeByteOff)

Methods

peek :: Ptr a -> IO a #

Read a value from the given memory location.

Note that the peek and poke functions might require properly aligned addresses to function correctly. This is architecture dependent; thus, portable code should ensure that when peeking or poking values of some type a, the alignment constraint for a, as given by the function alignment is fulfilled.

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

Write the given value to the given memory location. Alignment restrictions might apply; see peek.

Instances
Storable Bool

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

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

peekByteOff :: Ptr b -> Int -> IO Bool #

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

peek :: Ptr Bool -> IO Bool #

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

Storable Char

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Char -> Int #

alignment :: Char -> Int #

peekElemOff :: Ptr Char -> Int -> IO Char #

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

peekByteOff :: Ptr b -> Int -> IO Char #

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

peek :: Ptr Char -> IO Char #

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

Storable Double

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Float

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

peekElemOff :: Ptr Float -> Int -> IO Float #

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

peekByteOff :: Ptr b -> Int -> IO Float #

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

peek :: Ptr Float -> IO Float #

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

Storable Int

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int -> Int #

alignment :: Int -> Int #

peekElemOff :: Ptr Int -> Int -> IO Int #

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

peekByteOff :: Ptr b -> Int -> IO Int #

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

peek :: Ptr Int -> IO Int #

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

Storable Int8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

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

peekByteOff :: Ptr b -> Int -> IO Int8 #

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

peek :: Ptr Int8 -> IO Int8 #

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

Storable Int16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

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

peekByteOff :: Ptr b -> Int -> IO Int16 #

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

peek :: Ptr Int16 -> IO Int16 #

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

Storable Int32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

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

peekByteOff :: Ptr b -> Int -> IO Int32 #

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

peek :: Ptr Int32 -> IO Int32 #

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

Storable Int64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

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

peekByteOff :: Ptr b -> Int -> IO Int64 #

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

peek :: Ptr Int64 -> IO Int64 #

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

Storable Word

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word -> Int #

alignment :: Word -> Int #

peekElemOff :: Ptr Word -> Int -> IO Word #

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

peekByteOff :: Ptr b -> Int -> IO Word #

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

peek :: Ptr Word -> IO Word #

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

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

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

peekByteOff :: Ptr b -> Int -> IO Word8 #

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

peek :: Ptr Word8 -> IO Word8 #

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

Storable Word16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable ()

Since: base-4.9.0.0

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: () -> Int #

alignment :: () -> Int #

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

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

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

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

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

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

Storable CDev 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: CDev -> Int #

alignment :: CDev -> Int #

peekElemOff :: Ptr CDev -> Int -> IO CDev #

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

peekByteOff :: Ptr b -> Int -> IO CDev #

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

peek :: Ptr CDev -> IO CDev #

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

Storable CIno 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: CIno -> Int #

alignment :: CIno -> Int #

peekElemOff :: Ptr CIno -> Int -> IO CIno #

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

peekByteOff :: Ptr b -> Int -> IO CIno #

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

peek :: Ptr CIno -> IO CIno #

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

Storable CMode 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: CMode -> Int #

alignment :: CMode -> Int #

peekElemOff :: Ptr CMode -> Int -> IO CMode #

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

peekByteOff :: Ptr b -> Int -> IO CMode #

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

peek :: Ptr CMode -> IO CMode #

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

Storable COff 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: COff -> Int #

alignment :: COff -> Int #

peekElemOff :: Ptr COff -> Int -> IO COff #

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

peekByteOff :: Ptr b -> Int -> IO COff #

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

peek :: Ptr COff -> IO COff #

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

Storable CPid 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: CPid -> Int #

alignment :: CPid -> Int #

peekElemOff :: Ptr CPid -> Int -> IO CPid #

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

peekByteOff :: Ptr b -> Int -> IO CPid #

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

peek :: Ptr CPid -> IO CPid #

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

Storable CSsize 
Instance details

Defined in System.Posix.Types

Storable CGid 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: CGid -> Int #

alignment :: CGid -> Int #

peekElemOff :: Ptr CGid -> Int -> IO CGid #

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

peekByteOff :: Ptr b -> Int -> IO CGid #

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

peek :: Ptr CGid -> IO CGid #

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

Storable CNlink 
Instance details

Defined in System.Posix.Types

Storable CUid 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: CUid -> Int #

alignment :: CUid -> Int #

peekElemOff :: Ptr CUid -> Int -> IO CUid #

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

peekByteOff :: Ptr b -> Int -> IO CUid #

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

peek :: Ptr CUid -> IO CUid #

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

Storable CCc 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: CCc -> Int #

alignment :: CCc -> Int #

peekElemOff :: Ptr CCc -> Int -> IO CCc #

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

peekByteOff :: Ptr b -> Int -> IO CCc #

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

peek :: Ptr CCc -> IO CCc #

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

Storable CSpeed 
Instance details

Defined in System.Posix.Types

Storable CTcflag 
Instance details

Defined in System.Posix.Types

Storable CRLim 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: CRLim -> Int #

alignment :: CRLim -> Int #

peekElemOff :: Ptr CRLim -> Int -> IO CRLim #

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

peekByteOff :: Ptr b -> Int -> IO CRLim #

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

peek :: Ptr CRLim -> IO CRLim #

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

Storable CBlkSize 
Instance details

Defined in System.Posix.Types

Storable CBlkCnt 
Instance details

Defined in System.Posix.Types

Storable CClockId 
Instance details

Defined in System.Posix.Types

Storable CFsBlkCnt 
Instance details

Defined in System.Posix.Types

Storable CFsFilCnt 
Instance details

Defined in System.Posix.Types

Storable CId 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: CId -> Int #

alignment :: CId -> Int #

peekElemOff :: Ptr CId -> Int -> IO CId #

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

peekByteOff :: Ptr b -> Int -> IO CId #

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

peek :: Ptr CId -> IO CId #

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

Storable CKey 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: CKey -> Int #

alignment :: CKey -> Int #

peekElemOff :: Ptr CKey -> Int -> IO CKey #

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

peekByteOff :: Ptr b -> Int -> IO CKey #

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

peek :: Ptr CKey -> IO CKey #

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

Storable CTimer 
Instance details

Defined in System.Posix.Types

Storable Fd 
Instance details

Defined in System.Posix.Types

Methods

sizeOf :: Fd -> Int #

alignment :: Fd -> Int #

peekElemOff :: Ptr Fd -> Int -> IO Fd #

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

peekByteOff :: Ptr b -> Int -> IO Fd #

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

peek :: Ptr Fd -> IO Fd #

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

Storable CChar 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CChar -> Int #

alignment :: CChar -> Int #

peekElemOff :: Ptr CChar -> Int -> IO CChar #

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

peekByteOff :: Ptr b -> Int -> IO CChar #

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

peek :: Ptr CChar -> IO CChar #

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

Storable CSChar 
Instance details

Defined in Foreign.C.Types

Storable CUChar 
Instance details

Defined in Foreign.C.Types

Storable CShort 
Instance details

Defined in Foreign.C.Types

Storable CUShort 
Instance details

Defined in Foreign.C.Types

Storable CInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CInt -> Int #

alignment :: CInt -> Int #

peekElemOff :: Ptr CInt -> Int -> IO CInt #

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

peekByteOff :: Ptr b -> Int -> IO CInt #

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

peek :: Ptr CInt -> IO CInt #

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

Storable CUInt 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CUInt -> Int #

alignment :: CUInt -> Int #

peekElemOff :: Ptr CUInt -> Int -> IO CUInt #

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

peekByteOff :: Ptr b -> Int -> IO CUInt #

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

peek :: Ptr CUInt -> IO CUInt #

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

Storable CLong 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CLong -> Int #

alignment :: CLong -> Int #

peekElemOff :: Ptr CLong -> Int -> IO CLong #

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

peekByteOff :: Ptr b -> Int -> IO CLong #

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

peek :: Ptr CLong -> IO CLong #

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

Storable CULong 
Instance details

Defined in Foreign.C.Types

Storable CLLong 
Instance details

Defined in Foreign.C.Types

Storable CULLong 
Instance details

Defined in Foreign.C.Types

Storable CBool 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CBool -> Int #

alignment :: CBool -> Int #

peekElemOff :: Ptr CBool -> Int -> IO CBool #

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

peekByteOff :: Ptr b -> Int -> IO CBool #

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

peek :: Ptr CBool -> IO CBool #

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

Storable CFloat 
Instance details

Defined in Foreign.C.Types

Storable CDouble 
Instance details

Defined in Foreign.C.Types

Storable CPtrdiff 
Instance details

Defined in Foreign.C.Types

Storable CSize 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CSize -> Int #

alignment :: CSize -> Int #

peekElemOff :: Ptr CSize -> Int -> IO CSize #

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

peekByteOff :: Ptr b -> Int -> IO CSize #

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

peek :: Ptr CSize -> IO CSize #

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

Storable CWchar 
Instance details

Defined in Foreign.C.Types

Storable CSigAtomic 
Instance details

Defined in Foreign.C.Types

Storable CClock 
Instance details

Defined in Foreign.C.Types

Storable CTime 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CTime -> Int #

alignment :: CTime -> Int #

peekElemOff :: Ptr CTime -> Int -> IO CTime #

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

peekByteOff :: Ptr b -> Int -> IO CTime #

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

peek :: Ptr CTime -> IO CTime #

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

Storable CUSeconds 
Instance details

Defined in Foreign.C.Types

Storable CSUSeconds 
Instance details

Defined in Foreign.C.Types

Storable CIntPtr 
Instance details

Defined in Foreign.C.Types

Storable CUIntPtr 
Instance details

Defined in Foreign.C.Types

Storable CIntMax 
Instance details

Defined in Foreign.C.Types

Storable CUIntMax 
Instance details

Defined in Foreign.C.Types

Storable Fingerprint

Since: base-4.4.0.0

Instance details

Defined in Foreign.Storable

(Storable a, Integral a) => Storable (Ratio a)

Since: base-4.8.0.0

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ratio a -> Int #

alignment :: Ratio a -> Int #

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

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

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

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

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

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

Storable (StablePtr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: StablePtr a -> Int #

alignment :: StablePtr a -> Int #

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

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

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

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

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

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

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 () #

Storable (FunPtr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: FunPtr a -> Int #

alignment :: FunPtr a -> Int #

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

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

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

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

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

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

Storable a => Storable (Complex a)

Since: base-4.8.0.0

Instance details

Defined in Data.Complex

Methods

sizeOf :: Complex a -> Int #

alignment :: Complex a -> Int #

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

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

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

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

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

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

Storable a => Storable (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

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

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

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

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

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

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

Prim a => Storable (PrimStorable a) 
Instance details

Defined in Data.Primitive.Types

Prim a => Storable (PVar IO a) Source #

poke+peek will result in a new copy of a PVar

Instance details

Defined in Data.Primitive.PVar.Internal

Methods

sizeOf :: PVar IO a -> Int #

alignment :: PVar IO a -> Int #

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

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

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

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

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

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

Storable a => Storable (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

sizeOf :: Const a b -> Int #

alignment :: Const a b -> Int #

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

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

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

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

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

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