primal-0.1.0.0: Primeval world of Haskell.

Copyright(c) Alexey Kuleshevich 2020
LicenseBSD3
MaintainerAlexey Kuleshevich <alexey@kuleshevi.ch>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Prim.Class

Contents

Description

 
Synopsis

Documentation

class Prim a where Source #

Invariants:

  • Reading should never fail on memory that contains only zeros
  • Writing should always overwrite all of the bytes allocated for the element. In other words, writing to a dirty (uninitilized) region of memory should never leave any garbage around. For example, if a type requires 31 bytes of memory then on any write all 31 bytes must be overwritten.
  • A single thread write/read sequence must always roundtrip
  • This is not a class for serialization, therefore memory layout of unpacked datatype is selfcontained in Prim class and representation is not expected to stay the same between different versions of software. Primitive types like Int, Word, Char are an exception to this rule for obvious reasons.

Minimal complete definition

Nothing

Associated Types

type PrimBase a :: * Source #

type SizeOf a :: Nat Source #

type Alignment a :: Nat Source #

Methods

toPrimBase :: a -> PrimBase a Source #

toPrimBase :: Coercible a (PrimBase a) => a -> PrimBase a Source #

fromPrimBase :: PrimBase a -> a Source #

fromPrimBase :: Coercible a (PrimBase a) => PrimBase a -> a Source #

sizeOf# :: Proxy# a -> Int# Source #

Returned value must match the SizeOf type level Nat

sizeOf# :: Prim (PrimBase a) => Proxy# a -> Int# Source #

Returned value must match the SizeOf type level Nat

alignment# :: Proxy# a -> Int# Source #

Returned value must match the Alignment type level Nat

alignment# :: Prim (PrimBase a) => Proxy# a -> Int# Source #

Returned value must match the Alignment type level Nat

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

indexByteOffByteArray# :: Prim (PrimBase a) => ByteArray# -> Int# -> a Source #

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

indexByteArray# :: Prim (PrimBase a) => ByteArray# -> Int# -> a Source #

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

indexOffAddr# :: Prim (PrimBase a) => Addr# -> Int# -> a Source #

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

readByteOffMutableByteArray# :: Prim (PrimBase a) => MutableByteArray# s -> Int# -> State# s -> (#State# s, a#) Source #

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

readMutableByteArray# :: Prim (PrimBase a) => MutableByteArray# s -> Int# -> State# s -> (#State# s, a#) Source #

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

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

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

writeByteOffMutableByteArray# :: Prim (PrimBase a) => MutableByteArray# s -> Int# -> a -> State# s -> State# s Source #

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

writeMutableByteArray# :: Prim (PrimBase a) => MutableByteArray# s -> Int# -> a -> State# s -> State# s Source #

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

writeOffAddr# :: Prim (PrimBase a) => Addr# -> Int# -> a -> State# s -> State# s Source #

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

Set the region of MutableByteArray to the same value. Offset is in number of elements

setMutableByteArray# :: Prim (PrimBase a) => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s Source #

Set the region of MutableByteArray to the same value. Offset is in number of elements

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

Set the region of memory to the same value. Offset is in number of elements

setOffAddr# :: Prim (PrimBase a) => Addr# -> Int# -> Int# -> a -> State# s -> State# s Source #

Set the region of memory to the same value. Offset is in number of elements

Instances
Prim Bool Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Bool :: Type Source #

type SizeOf Bool :: Nat Source #

type Alignment Bool :: Nat Source #

Prim Char Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Char :: Type Source #

type SizeOf Char :: Nat Source #

type Alignment Char :: Nat Source #

Prim Double Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Double :: Type Source #

type SizeOf Double :: Nat Source #

type Alignment Double :: Nat Source #

Prim Float Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Float :: Type Source #

type SizeOf Float :: Nat Source #

type Alignment Float :: Nat Source #

Prim Int Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Int :: Type Source #

type SizeOf Int :: Nat Source #

type Alignment Int :: Nat Source #

Prim Int8 Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Int8 :: Type Source #

type SizeOf Int8 :: Nat Source #

type Alignment Int8 :: Nat Source #

Prim Int16 Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Int16 :: Type Source #

type SizeOf Int16 :: Nat Source #

type Alignment Int16 :: Nat Source #

Prim Int32 Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Int32 :: Type Source #

type SizeOf Int32 :: Nat Source #

type Alignment Int32 :: Nat Source #

Prim Int64 Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Int64 :: Type Source #

type SizeOf Int64 :: Nat Source #

type Alignment Int64 :: Nat Source #

Prim Ordering Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Ordering :: Type Source #

type SizeOf Ordering :: Nat Source #

type Alignment Ordering :: Nat Source #

Prim Word Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Word :: Type Source #

type SizeOf Word :: Nat Source #

type Alignment Word :: Nat Source #

Prim Word8 Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Word8 :: Type Source #

type SizeOf Word8 :: Nat Source #

type Alignment Word8 :: Nat Source #

Prim Word16 Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Word16 :: Type Source #

type SizeOf Word16 :: Nat Source #

type Alignment Word16 :: Nat Source #

Prim Word32 Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Word32 :: Type Source #

type SizeOf Word32 :: Nat Source #

type Alignment Word32 :: Nat Source #

Prim Word64 Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Word64 :: Type Source #

type SizeOf Word64 :: Nat Source #

type Alignment Word64 :: Nat Source #

Prim () Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase () :: Type Source #

type SizeOf () :: Nat Source #

type Alignment () :: Nat Source #

Prim BlockReason Source # 
Instance details

Defined in Data.Prim.Class

Prim ThreadStatus Source # 
Instance details

Defined in Data.Prim.Class

Prim CDev Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CDev :: Type Source #

type SizeOf CDev :: Nat Source #

type Alignment CDev :: Nat Source #

Prim CIno Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CIno :: Type Source #

type SizeOf CIno :: Nat Source #

type Alignment CIno :: Nat Source #

Prim CMode Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CMode :: Type Source #

type SizeOf CMode :: Nat Source #

type Alignment CMode :: Nat Source #

Prim COff Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase COff :: Type Source #

type SizeOf COff :: Nat Source #

type Alignment COff :: Nat Source #

Prim CPid Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CPid :: Type Source #

type SizeOf CPid :: Nat Source #

type Alignment CPid :: Nat Source #

Prim CSsize Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CSsize :: Type Source #

type SizeOf CSsize :: Nat Source #

type Alignment CSsize :: Nat Source #

Prim CGid Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CGid :: Type Source #

type SizeOf CGid :: Nat Source #

type Alignment CGid :: Nat Source #

Prim CNlink Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CNlink :: Type Source #

type SizeOf CNlink :: Nat Source #

type Alignment CNlink :: Nat Source #

Prim CUid Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CUid :: Type Source #

type SizeOf CUid :: Nat Source #

type Alignment CUid :: Nat Source #

Prim CCc Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CCc :: Type Source #

type SizeOf CCc :: Nat Source #

type Alignment CCc :: Nat Source #

Prim CSpeed Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CSpeed :: Type Source #

type SizeOf CSpeed :: Nat Source #

type Alignment CSpeed :: Nat Source #

Prim CTcflag Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CTcflag :: Type Source #

type SizeOf CTcflag :: Nat Source #

type Alignment CTcflag :: Nat Source #

Prim CRLim Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CRLim :: Type Source #

type SizeOf CRLim :: Nat Source #

type Alignment CRLim :: Nat Source #

Prim CBlkSize Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CBlkSize :: Type Source #

type SizeOf CBlkSize :: Nat Source #

type Alignment CBlkSize :: Nat Source #

Prim CBlkCnt Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CBlkCnt :: Type Source #

type SizeOf CBlkCnt :: Nat Source #

type Alignment CBlkCnt :: Nat Source #

Prim CClockId Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CClockId :: Type Source #

type SizeOf CClockId :: Nat Source #

type Alignment CClockId :: Nat Source #

Prim CFsBlkCnt Source # 
Instance details

Defined in Data.Prim.Class

Prim CFsFilCnt Source # 
Instance details

Defined in Data.Prim.Class

Prim CId Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CId :: Type Source #

type SizeOf CId :: Nat Source #

type Alignment CId :: Nat Source #

Prim CKey Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CKey :: Type Source #

type SizeOf CKey :: Nat Source #

type Alignment CKey :: Nat Source #

Prim CTimer Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CTimer :: Type Source #

type SizeOf CTimer :: Nat Source #

type Alignment CTimer :: Nat Source #

Prim Fd Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Fd :: Type Source #

type SizeOf Fd :: Nat Source #

type Alignment Fd :: Nat Source #

Prim Errno Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Errno :: Type Source #

type SizeOf Errno :: Nat Source #

type Alignment Errno :: Nat Source #

Prim BufferMode Source # 
Instance details

Defined in Data.Prim.Class

Prim Newline Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Newline :: Type Source #

type SizeOf Newline :: Nat Source #

type Alignment Newline :: Nat Source #

Prim NewlineMode Source # 
Instance details

Defined in Data.Prim.Class

Prim IODeviceType Source # 
Instance details

Defined in Data.Prim.Class

Prim SeekMode Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase SeekMode :: Type Source #

type SizeOf SeekMode :: Nat Source #

type Alignment SeekMode :: Nat Source #

Prim All Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase All :: Type Source #

type SizeOf All :: Nat Source #

type Alignment All :: Nat Source #

Prim Any Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Any :: Type Source #

type SizeOf Any :: Nat Source #

type Alignment Any :: Nat Source #

Prim CChar Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CChar :: Type Source #

type SizeOf CChar :: Nat Source #

type Alignment CChar :: Nat Source #

Prim CSChar Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CSChar :: Type Source #

type SizeOf CSChar :: Nat Source #

type Alignment CSChar :: Nat Source #

Prim CUChar Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CUChar :: Type Source #

type SizeOf CUChar :: Nat Source #

type Alignment CUChar :: Nat Source #

Prim CShort Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CShort :: Type Source #

type SizeOf CShort :: Nat Source #

type Alignment CShort :: Nat Source #

Prim CUShort Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CUShort :: Type Source #

type SizeOf CUShort :: Nat Source #

type Alignment CUShort :: Nat Source #

Prim CInt Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CInt :: Type Source #

type SizeOf CInt :: Nat Source #

type Alignment CInt :: Nat Source #

Prim CUInt Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CUInt :: Type Source #

type SizeOf CUInt :: Nat Source #

type Alignment CUInt :: Nat Source #

Prim CLong Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CLong :: Type Source #

type SizeOf CLong :: Nat Source #

type Alignment CLong :: Nat Source #

Prim CULong Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CULong :: Type Source #

type SizeOf CULong :: Nat Source #

type Alignment CULong :: Nat Source #

Prim CLLong Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CLLong :: Type Source #

type SizeOf CLLong :: Nat Source #

type Alignment CLLong :: Nat Source #

Prim CULLong Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CULLong :: Type Source #

type SizeOf CULLong :: Nat Source #

type Alignment CULLong :: Nat Source #

Prim CBool Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CBool :: Type Source #

type SizeOf CBool :: Nat Source #

type Alignment CBool :: Nat Source #

Prim CFloat Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CFloat :: Type Source #

type SizeOf CFloat :: Nat Source #

type Alignment CFloat :: Nat Source #

Prim CDouble Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CDouble :: Type Source #

type SizeOf CDouble :: Nat Source #

type Alignment CDouble :: Nat Source #

Prim CPtrdiff Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CPtrdiff :: Type Source #

type SizeOf CPtrdiff :: Nat Source #

type Alignment CPtrdiff :: Nat Source #

Prim CSize Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CSize :: Type Source #

type SizeOf CSize :: Nat Source #

type Alignment CSize :: Nat Source #

Prim CWchar Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CWchar :: Type Source #

type SizeOf CWchar :: Nat Source #

type Alignment CWchar :: Nat Source #

Prim CSigAtomic Source # 
Instance details

Defined in Data.Prim.Class

Prim CIntPtr Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CIntPtr :: Type Source #

type SizeOf CIntPtr :: Nat Source #

type Alignment CIntPtr :: Nat Source #

Prim CUIntPtr Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CUIntPtr :: Type Source #

type SizeOf CUIntPtr :: Nat Source #

type Alignment CUIntPtr :: Nat Source #

Prim CIntMax Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CIntMax :: Type Source #

type SizeOf CIntMax :: Nat Source #

type Alignment CIntMax :: Nat Source #

Prim CUIntMax Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CUIntMax :: Type Source #

type SizeOf CUIntMax :: Nat Source #

type Alignment CUIntMax :: Nat Source #

Prim WordPtr Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase WordPtr :: Type Source #

type SizeOf WordPtr :: Nat Source #

type Alignment WordPtr :: Nat Source #

Prim IntPtr Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase IntPtr :: Type Source #

type SizeOf IntPtr :: Nat Source #

type Alignment IntPtr :: Nat Source #

Prim IOMode Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase IOMode :: Type Source #

type SizeOf IOMode :: Nat Source #

type Alignment IOMode :: Nat Source #

Prim Fingerprint Source # 
Instance details

Defined in Data.Prim.Class

Prim GeneralCategory Source # 
Instance details

Defined in Data.Prim.Class

Prim a => Prim (Maybe a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Maybe a) :: Type Source #

type SizeOf (Maybe a) :: Nat Source #

type Alignment (Maybe a) :: Nat Source #

Prim a => Prim (Ratio a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Ratio a) :: Type Source #

type SizeOf (Ratio a) :: Nat Source #

type Alignment (Ratio a) :: Nat Source #

Prim (StablePtr a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (StablePtr a) :: Type Source #

type SizeOf (StablePtr a) :: Nat Source #

type Alignment (StablePtr a) :: Nat Source #

Prim (Ptr a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Ptr a) :: Type Source #

type SizeOf (Ptr a) :: Nat Source #

type Alignment (Ptr a) :: Nat Source #

Prim (FunPtr a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (FunPtr a) :: Type Source #

type SizeOf (FunPtr a) :: Nat Source #

type Alignment (FunPtr a) :: Nat Source #

Prim a => Prim (Complex a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Complex a) :: Type Source #

type SizeOf (Complex a) :: Nat Source #

type Alignment (Complex a) :: Nat Source #

Prim a => Prim (Min a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Min a) :: Type Source #

type SizeOf (Min a) :: Nat Source #

type Alignment (Min a) :: Nat Source #

Prim a => Prim (Max a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Max a) :: Type Source #

type SizeOf (Max a) :: Nat Source #

type Alignment (Max a) :: Nat Source #

Prim a => Prim (First a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (First a) :: Type Source #

type SizeOf (First a) :: Nat Source #

type Alignment (First a) :: Nat Source #

Prim a => Prim (Last a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Last a) :: Type Source #

type SizeOf (Last a) :: Nat Source #

type Alignment (Last a) :: Nat Source #

Prim a => Prim (Identity a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Identity a) :: Type Source #

type SizeOf (Identity a) :: Nat Source #

type Alignment (Identity a) :: Nat Source #

Prim a => Prim (Dual a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Dual a) :: Type Source #

type SizeOf (Dual a) :: Nat Source #

type Alignment (Dual a) :: Nat Source #

Prim a => Prim (Sum a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Sum a) :: Type Source #

type SizeOf (Sum a) :: Nat Source #

type Alignment (Sum a) :: Nat Source #

Prim a => Prim (Product a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Product a) :: Type Source #

type SizeOf (Product a) :: Nat Source #

type Alignment (Product a) :: Nat Source #

Prim a => Prim (Down a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Down a) :: Type Source #

type SizeOf (Down a) :: Nat Source #

type Alignment (Down a) :: Nat Source #

Prim a => Prim (Atom a) Source # 
Instance details

Defined in Data.Prim.Atom

Associated Types

type PrimBase (Atom a) :: Type Source #

type SizeOf (Atom a) :: Nat Source #

type Alignment (Atom a) :: Nat Source #

Prim (Off a) Source # 
Instance details

Defined in Data.Prim

Associated Types

type PrimBase (Off a) :: Type Source #

type SizeOf (Off a) :: Nat Source #

type Alignment (Off a) :: Nat Source #

Prim (Count a) Source # 
Instance details

Defined in Data.Prim

Associated Types

type PrimBase (Count a) :: Type Source #

type SizeOf (Count a) :: Nat Source #

type Alignment (Count a) :: Nat Source #

(Prim a, Prim b) => Prim (Either a b) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Either a b) :: Type Source #

type SizeOf (Either a b) :: Nat Source #

type Alignment (Either a b) :: Nat Source #

(Prim a, Prim b) => Prim (a, b) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (a, b) :: Type Source #

type SizeOf (a, b) :: Nat Source #

type Alignment (a, b) :: Nat Source #

(Prim a, Prim b) => Prim (Arg a b) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Arg a b) :: Type Source #

type SizeOf (Arg a b) :: Nat Source #

type Alignment (Arg a b) :: Nat Source #

(Prim a, Prim b, Prim c) => Prim (a, b, c) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (a, b, c) :: Type Source #

type SizeOf (a, b, c) :: Nat Source #

type Alignment (a, b, c) :: Nat Source #

Methods

toPrimBase :: (a, b, c) -> PrimBase (a, b, c) Source #

fromPrimBase :: PrimBase (a, b, c) -> (a, b, c) Source #

sizeOf# :: Proxy# (a, b, c) -> Int# Source #

alignment# :: Proxy# (a, b, c) -> Int# Source #

indexByteOffByteArray# :: ByteArray# -> Int# -> (a, b, c) Source #

indexByteArray# :: ByteArray# -> Int# -> (a, b, c) Source #

indexOffAddr# :: Addr# -> Int# -> (a, b, c) Source #

readByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c)#) Source #

readMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c)#) Source #

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

writeByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c) -> State# s -> State# s Source #

writeMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c) -> State# s -> State# s Source #

writeOffAddr# :: Addr# -> Int# -> (a, b, c) -> State# s -> State# s Source #

setMutableByteArray# :: MutableByteArray# s -> Int# -> Int# -> (a, b, c) -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> (a, b, c) -> State# s -> State# s Source #

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

Defined in Data.Prim.Class

Associated Types

type PrimBase (Const a b) :: Type Source #

type SizeOf (Const a b) :: Nat Source #

type Alignment (Const a b) :: Nat Source #

Prim (f a) => Prim (Ap f a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Ap f a) :: Type Source #

type SizeOf (Ap f a) :: Nat Source #

type Alignment (Ap f a) :: Nat Source #

Prim (f a) => Prim (Alt f a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Alt f a) :: Type Source #

type SizeOf (Alt f a) :: Nat Source #

type Alignment (Alt f a) :: Nat Source #

a ~ b => Prim (a :~: b) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (a :~: b) :: Type Source #

type SizeOf (a :~: b) :: Nat Source #

type Alignment (a :~: b) :: Nat Source #

(Prim a, Prim b, Prim c, Prim d) => Prim (a, b, c, d) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (a, b, c, d) :: Type Source #

type SizeOf (a, b, c, d) :: Nat Source #

type Alignment (a, b, c, d) :: Nat Source #

Methods

toPrimBase :: (a, b, c, d) -> PrimBase (a, b, c, d) Source #

fromPrimBase :: PrimBase (a, b, c, d) -> (a, b, c, d) Source #

sizeOf# :: Proxy# (a, b, c, d) -> Int# Source #

alignment# :: Proxy# (a, b, c, d) -> Int# Source #

indexByteOffByteArray# :: ByteArray# -> Int# -> (a, b, c, d) Source #

indexByteArray# :: ByteArray# -> Int# -> (a, b, c, d) Source #

indexOffAddr# :: Addr# -> Int# -> (a, b, c, d) Source #

readByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d)#) Source #

readMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d)#) Source #

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

writeByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d) -> State# s -> State# s Source #

writeMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d) -> State# s -> State# s Source #

writeOffAddr# :: Addr# -> Int# -> (a, b, c, d) -> State# s -> State# s Source #

setMutableByteArray# :: MutableByteArray# s -> Int# -> Int# -> (a, b, c, d) -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> (a, b, c, d) -> State# s -> State# s Source #

(Prim (f a), Prim (g a)) => Prim (Product f g a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Product f g a) :: Type Source #

type SizeOf (Product f g a) :: Nat Source #

type Alignment (Product f g a) :: Nat Source #

a ~ b => Prim (a :~~: b) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (a :~~: b) :: Type Source #

type SizeOf (a :~~: b) :: Nat Source #

type Alignment (a :~~: b) :: Nat Source #

(Prim a, Prim b, Prim c, Prim d, Prim e) => Prim (a, b, c, d, e) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (a, b, c, d, e) :: Type Source #

type SizeOf (a, b, c, d, e) :: Nat Source #

type Alignment (a, b, c, d, e) :: Nat Source #

Methods

toPrimBase :: (a, b, c, d, e) -> PrimBase (a, b, c, d, e) Source #

fromPrimBase :: PrimBase (a, b, c, d, e) -> (a, b, c, d, e) Source #

sizeOf# :: Proxy# (a, b, c, d, e) -> Int# Source #

alignment# :: Proxy# (a, b, c, d, e) -> Int# Source #

indexByteOffByteArray# :: ByteArray# -> Int# -> (a, b, c, d, e) Source #

indexByteArray# :: ByteArray# -> Int# -> (a, b, c, d, e) Source #

indexOffAddr# :: Addr# -> Int# -> (a, b, c, d, e) Source #

readByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d, e)#) Source #

readMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d, e)#) Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, (a, b, c, d, e)#) Source #

writeByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d, e) -> State# s -> State# s Source #

writeMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d, e) -> State# s -> State# s Source #

writeOffAddr# :: Addr# -> Int# -> (a, b, c, d, e) -> State# s -> State# s Source #

setMutableByteArray# :: MutableByteArray# s -> Int# -> Int# -> (a, b, c, d, e) -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> (a, b, c, d, e) -> State# s -> State# s Source #

Prim (f (g a)) => Prim (Compose f g a) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (Compose f g a) :: Type Source #

type SizeOf (Compose f g a) :: Nat Source #

type Alignment (Compose f g a) :: Nat Source #

(Prim a, Prim b, Prim c, Prim d, Prim e, Prim f) => Prim (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (a, b, c, d, e, f) :: Type Source #

type SizeOf (a, b, c, d, e, f) :: Nat Source #

type Alignment (a, b, c, d, e, f) :: Nat Source #

Methods

toPrimBase :: (a, b, c, d, e, f) -> PrimBase (a, b, c, d, e, f) Source #

fromPrimBase :: PrimBase (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

sizeOf# :: Proxy# (a, b, c, d, e, f) -> Int# Source #

alignment# :: Proxy# (a, b, c, d, e, f) -> Int# Source #

indexByteOffByteArray# :: ByteArray# -> Int# -> (a, b, c, d, e, f) Source #

indexByteArray# :: ByteArray# -> Int# -> (a, b, c, d, e, f) Source #

indexOffAddr# :: Addr# -> Int# -> (a, b, c, d, e, f) Source #

readByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f)#) Source #

readMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f)#) Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f)#) Source #

writeByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f) -> State# s -> State# s Source #

writeMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f) -> State# s -> State# s Source #

writeOffAddr# :: Addr# -> Int# -> (a, b, c, d, e, f) -> State# s -> State# s Source #

setMutableByteArray# :: MutableByteArray# s -> Int# -> Int# -> (a, b, c, d, e, f) -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> (a, b, c, d, e, f) -> State# s -> State# s Source #

(Prim a, Prim b, Prim c, Prim d, Prim e, Prim f, Prim g) => Prim (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (a, b, c, d, e, f, g) :: Type Source #

type SizeOf (a, b, c, d, e, f, g) :: Nat Source #

type Alignment (a, b, c, d, e, f, g) :: Nat Source #

Methods

toPrimBase :: (a, b, c, d, e, f, g) -> PrimBase (a, b, c, d, e, f, g) Source #

fromPrimBase :: PrimBase (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

sizeOf# :: Proxy# (a, b, c, d, e, f, g) -> Int# Source #

alignment# :: Proxy# (a, b, c, d, e, f, g) -> Int# Source #

indexByteOffByteArray# :: ByteArray# -> Int# -> (a, b, c, d, e, f, g) Source #

indexByteArray# :: ByteArray# -> Int# -> (a, b, c, d, e, f, g) Source #

indexOffAddr# :: Addr# -> Int# -> (a, b, c, d, e, f, g) Source #

readByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f, g)#) Source #

readMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f, g)#) Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f, g)#) Source #

writeByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f, g) -> State# s -> State# s Source #

writeMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f, g) -> State# s -> State# s Source #

writeOffAddr# :: Addr# -> Int# -> (a, b, c, d, e, f, g) -> State# s -> State# s Source #

setMutableByteArray# :: MutableByteArray# s -> Int# -> Int# -> (a, b, c, d, e, f, g) -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> (a, b, c, d, e, f, g) -> State# s -> State# s Source #

(Prim a, Prim b, Prim c, Prim d, Prim e, Prim f, Prim g, Prim h) => Prim (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (a, b, c, d, e, f, g, h) :: Type Source #

type SizeOf (a, b, c, d, e, f, g, h) :: Nat Source #

type Alignment (a, b, c, d, e, f, g, h) :: Nat Source #

Methods

toPrimBase :: (a, b, c, d, e, f, g, h) -> PrimBase (a, b, c, d, e, f, g, h) Source #

fromPrimBase :: PrimBase (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

sizeOf# :: Proxy# (a, b, c, d, e, f, g, h) -> Int# Source #

alignment# :: Proxy# (a, b, c, d, e, f, g, h) -> Int# Source #

indexByteOffByteArray# :: ByteArray# -> Int# -> (a, b, c, d, e, f, g, h) Source #

indexByteArray# :: ByteArray# -> Int# -> (a, b, c, d, e, f, g, h) Source #

indexOffAddr# :: Addr# -> Int# -> (a, b, c, d, e, f, g, h) Source #

readByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f, g, h)#) Source #

readMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f, g, h)#) Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f, g, h)#) Source #

writeByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f, g, h) -> State# s -> State# s Source #

writeMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f, g, h) -> State# s -> State# s Source #

writeOffAddr# :: Addr# -> Int# -> (a, b, c, d, e, f, g, h) -> State# s -> State# s Source #

setMutableByteArray# :: MutableByteArray# s -> Int# -> Int# -> (a, b, c, d, e, f, g, h) -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> (a, b, c, d, e, f, g, h) -> State# s -> State# s Source #

(Prim a, Prim b, Prim c, Prim d, Prim e, Prim f, Prim g, Prim h, Prim i) => Prim (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase (a, b, c, d, e, f, g, h, i) :: Type Source #

type SizeOf (a, b, c, d, e, f, g, h, i) :: Nat Source #

type Alignment (a, b, c, d, e, f, g, h, i) :: Nat Source #

Methods

toPrimBase :: (a, b, c, d, e, f, g, h, i) -> PrimBase (a, b, c, d, e, f, g, h, i) Source #

fromPrimBase :: PrimBase (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

sizeOf# :: Proxy# (a, b, c, d, e, f, g, h, i) -> Int# Source #

alignment# :: Proxy# (a, b, c, d, e, f, g, h, i) -> Int# Source #

indexByteOffByteArray# :: ByteArray# -> Int# -> (a, b, c, d, e, f, g, h, i) Source #

indexByteArray# :: ByteArray# -> Int# -> (a, b, c, d, e, f, g, h, i) Source #

indexOffAddr# :: Addr# -> Int# -> (a, b, c, d, e, f, g, h, i) Source #

readByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f, g, h, i)#) Source #

readMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f, g, h, i)#) Source #

readOffAddr# :: Addr# -> Int# -> State# s -> (#State# s, (a, b, c, d, e, f, g, h, i)#) Source #

writeByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f, g, h, i) -> State# s -> State# s Source #

writeMutableByteArray# :: MutableByteArray# s -> Int# -> (a, b, c, d, e, f, g, h, i) -> State# s -> State# s Source #

writeOffAddr# :: Addr# -> Int# -> (a, b, c, d, e, f, g, h, i) -> State# s -> State# s Source #

setMutableByteArray# :: MutableByteArray# s -> Int# -> Int# -> (a, b, c, d, e, f, g, h, i) -> State# s -> State# s Source #

setOffAddr# :: Addr# -> Int# -> Int# -> (a, b, c, d, e, f, g, h, i) -> State# s -> State# s Source #

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

A loop that uses writeMutableByteArray# to set the values in the region. It is a suboptimal way to fill the memory with a single value that is why it is only provided here for convenience

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

Backwards compatibility

newtype WordPtr #

An unsigned integral type that can be losslessly converted to and from Ptr. This type is also compatible with the C99 type uintptr_t, and can be marshalled to and from that type safely.

Constructors

WordPtr Word 
Instances
Bounded WordPtr 
Instance details

Defined in Foreign.Ptr

Enum WordPtr 
Instance details

Defined in Foreign.Ptr

Eq WordPtr 
Instance details

Defined in Foreign.Ptr

Methods

(==) :: WordPtr -> WordPtr -> Bool #

(/=) :: WordPtr -> WordPtr -> Bool #

Integral WordPtr 
Instance details

Defined in Foreign.Ptr

Num WordPtr 
Instance details

Defined in Foreign.Ptr

Ord WordPtr 
Instance details

Defined in Foreign.Ptr

Read WordPtr 
Instance details

Defined in Foreign.Ptr

Real WordPtr 
Instance details

Defined in Foreign.Ptr

Show WordPtr 
Instance details

Defined in Foreign.Ptr

Storable WordPtr 
Instance details

Defined in Foreign.Ptr

Bits WordPtr 
Instance details

Defined in Foreign.Ptr

FiniteBits WordPtr 
Instance details

Defined in Foreign.Ptr

Prim WordPtr Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase WordPtr :: Type Source #

type SizeOf WordPtr :: Nat Source #

type Alignment WordPtr :: Nat Source #

AtomicBits WordPtr Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

atomicAndFetchOldMutableByteArray# :: MutableByteArray# s -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicAndFetchNewMutableByteArray# :: MutableByteArray# s -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicNandFetchOldMutableByteArray# :: MutableByteArray# s -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicNandFetchNewMutableByteArray# :: MutableByteArray# s -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicOrFetchOldMutableByteArray# :: MutableByteArray# s -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicOrFetchNewMutableByteArray# :: MutableByteArray# s -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicXorFetchOldMutableByteArray# :: MutableByteArray# s -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicXorFetchNewMutableByteArray# :: MutableByteArray# s -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicAndFetchOldOffAddr# :: Addr# -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicAndFetchNewOffAddr# :: Addr# -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicNandFetchOldOffAddr# :: Addr# -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicNandFetchNewOffAddr# :: Addr# -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicOrFetchOldOffAddr# :: Addr# -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicOrFetchNewOffAddr# :: Addr# -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicXorFetchOldOffAddr# :: Addr# -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

atomicXorFetchNewOffAddr# :: Addr# -> Int# -> WordPtr -> State# s -> (#State# s, WordPtr#) Source #

AtomicCount WordPtr Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic WordPtr Source # 
Instance details

Defined in Data.Prim.Atomic

type PrimBase WordPtr Source # 
Instance details

Defined in Data.Prim.Class

type SizeOf WordPtr Source # 
Instance details

Defined in Data.Prim.Class

type Alignment WordPtr Source # 
Instance details

Defined in Data.Prim.Class

ptrToWordPtr :: Ptr a -> WordPtr #

casts a Ptr to a WordPtr

wordPtrToPtr :: WordPtr -> Ptr a #

casts a WordPtr to a Ptr

newtype IntPtr #

A signed integral type that can be losslessly converted to and from Ptr. This type is also compatible with the C99 type intptr_t, and can be marshalled to and from that type safely.

Constructors

IntPtr Int 
Instances
Bounded IntPtr 
Instance details

Defined in Foreign.Ptr

Enum IntPtr 
Instance details

Defined in Foreign.Ptr

Eq IntPtr 
Instance details

Defined in Foreign.Ptr

Methods

(==) :: IntPtr -> IntPtr -> Bool #

(/=) :: IntPtr -> IntPtr -> Bool #

Integral IntPtr 
Instance details

Defined in Foreign.Ptr

Num IntPtr 
Instance details

Defined in Foreign.Ptr

Ord IntPtr 
Instance details

Defined in Foreign.Ptr

Read IntPtr 
Instance details

Defined in Foreign.Ptr

Real IntPtr 
Instance details

Defined in Foreign.Ptr

Show IntPtr 
Instance details

Defined in Foreign.Ptr

Storable IntPtr 
Instance details

Defined in Foreign.Ptr

Bits IntPtr 
Instance details

Defined in Foreign.Ptr

FiniteBits IntPtr 
Instance details

Defined in Foreign.Ptr

Prim IntPtr Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase IntPtr :: Type Source #

type SizeOf IntPtr :: Nat Source #

type Alignment IntPtr :: Nat Source #

AtomicBits IntPtr Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

atomicAndFetchOldMutableByteArray# :: MutableByteArray# s -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicAndFetchNewMutableByteArray# :: MutableByteArray# s -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicNandFetchOldMutableByteArray# :: MutableByteArray# s -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicNandFetchNewMutableByteArray# :: MutableByteArray# s -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicOrFetchOldMutableByteArray# :: MutableByteArray# s -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicOrFetchNewMutableByteArray# :: MutableByteArray# s -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicXorFetchOldMutableByteArray# :: MutableByteArray# s -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicXorFetchNewMutableByteArray# :: MutableByteArray# s -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicAndFetchOldOffAddr# :: Addr# -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicAndFetchNewOffAddr# :: Addr# -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicNandFetchOldOffAddr# :: Addr# -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicNandFetchNewOffAddr# :: Addr# -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicOrFetchOldOffAddr# :: Addr# -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicOrFetchNewOffAddr# :: Addr# -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicXorFetchOldOffAddr# :: Addr# -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

atomicXorFetchNewOffAddr# :: Addr# -> Int# -> IntPtr -> State# s -> (#State# s, IntPtr#) Source #

AtomicCount IntPtr Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic IntPtr Source # 
Instance details

Defined in Data.Prim.Atomic

type PrimBase IntPtr Source # 
Instance details

Defined in Data.Prim.Class

type SizeOf IntPtr Source # 
Instance details

Defined in Data.Prim.Class

type Alignment IntPtr Source # 
Instance details

Defined in Data.Prim.Class

ptrToIntPtr :: Ptr a -> IntPtr #

casts a Ptr to an IntPtr

intPtrToPtr :: IntPtr -> Ptr a #

casts an IntPtr to a Ptr