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

Contents

Description

 
Synopsis

Documentation

class Prim a 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.
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 #

newtype Atom a Source #

Constructors

Atom 

Fields

Instances
Enum a => Enum (Atom a) Source # 
Instance details

Defined in Data.Prim.Atom

Methods

succ :: Atom a -> Atom a #

pred :: Atom a -> Atom a #

toEnum :: Int -> Atom a #

fromEnum :: Atom a -> Int #

enumFrom :: Atom a -> [Atom a] #

enumFromThen :: Atom a -> Atom a -> [Atom a] #

enumFromTo :: Atom a -> Atom a -> [Atom a] #

enumFromThenTo :: Atom a -> Atom a -> Atom a -> [Atom a] #

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

Defined in Data.Prim.Atom

Methods

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

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

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

Defined in Data.Prim.Atom

Methods

pi :: Atom a #

exp :: Atom a -> Atom a #

log :: Atom a -> Atom a #

sqrt :: Atom a -> Atom a #

(**) :: Atom a -> Atom a -> Atom a #

logBase :: Atom a -> Atom a -> Atom a #

sin :: Atom a -> Atom a #

cos :: Atom a -> Atom a #

tan :: Atom a -> Atom a #

asin :: Atom a -> Atom a #

acos :: Atom a -> Atom a #

atan :: Atom a -> Atom a #

sinh :: Atom a -> Atom a #

cosh :: Atom a -> Atom a #

tanh :: Atom a -> Atom a #

asinh :: Atom a -> Atom a #

acosh :: Atom a -> Atom a #

atanh :: Atom a -> Atom a #

log1p :: Atom a -> Atom a #

expm1 :: Atom a -> Atom a #

log1pexp :: Atom a -> Atom a #

log1mexp :: Atom a -> Atom a #

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

Defined in Data.Prim.Atom

Methods

(/) :: Atom a -> Atom a -> Atom a #

recip :: Atom a -> Atom a #

fromRational :: Rational -> Atom a #

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

Defined in Data.Prim.Atom

Methods

quot :: Atom a -> Atom a -> Atom a #

rem :: Atom a -> Atom a -> Atom a #

div :: Atom a -> Atom a -> Atom a #

mod :: Atom a -> Atom a -> Atom a #

quotRem :: Atom a -> Atom a -> (Atom a, Atom a) #

divMod :: Atom a -> Atom a -> (Atom a, Atom a) #

toInteger :: Atom a -> Integer #

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

Defined in Data.Prim.Atom

Methods

(+) :: Atom a -> Atom a -> Atom a #

(-) :: Atom a -> Atom a -> Atom a #

(*) :: Atom a -> Atom a -> Atom a #

negate :: Atom a -> Atom a #

abs :: Atom a -> Atom a #

signum :: Atom a -> Atom a #

fromInteger :: Integer -> Atom a #

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

Defined in Data.Prim.Atom

Methods

compare :: Atom a -> Atom a -> Ordering #

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

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

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

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

max :: Atom a -> Atom a -> Atom a #

min :: Atom a -> Atom a -> Atom a #

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

Defined in Data.Prim.Atom

Methods

toRational :: Atom a -> Rational #

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

Defined in Data.Prim.Atom

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

Defined in Data.Prim.Atom

Methods

properFraction :: Integral b => Atom a -> (b, Atom a) #

truncate :: Integral b => Atom a -> b #

round :: Integral b => Atom a -> b #

ceiling :: Integral b => Atom a -> b #

floor :: Integral b => Atom a -> b #

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

Defined in Data.Prim.Atom

Methods

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

show :: Atom a -> String #

showList :: [Atom a] -> ShowS #

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

Defined in Data.Prim.Atom

Methods

(.&.) :: Atom a -> Atom a -> Atom a #

(.|.) :: Atom a -> Atom a -> Atom a #

xor :: Atom a -> Atom a -> Atom a #

complement :: Atom a -> Atom a #

shift :: Atom a -> Int -> Atom a #

rotate :: Atom a -> Int -> Atom a #

zeroBits :: Atom a #

bit :: Int -> Atom a #

setBit :: Atom a -> Int -> Atom a #

clearBit :: Atom a -> Int -> Atom a #

complementBit :: Atom a -> Int -> Atom a #

testBit :: Atom a -> Int -> Bool #

bitSizeMaybe :: Atom a -> Maybe Int #

bitSize :: Atom a -> Int #

isSigned :: Atom a -> Bool #

shiftL :: Atom a -> Int -> Atom a #

unsafeShiftL :: Atom a -> Int -> Atom a #

shiftR :: Atom a -> Int -> Atom a #

unsafeShiftR :: Atom a -> Int -> Atom a #

rotateL :: Atom a -> Int -> Atom a #

rotateR :: Atom a -> Int -> Atom a #

popCount :: Atom a -> Int #

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

Defined in Data.Prim.Atom

Methods

rnf :: Atom a -> () #

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 #

(Bits a, Eq a, Prim a) => AtomicBits (Atom a) Source # 
Instance details

Defined in Data.Prim.Atom

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(Num a, Eq a, Prim a) => AtomicCount (Atom a) Source # 
Instance details

Defined in Data.Prim.Atom

(Eq a, Prim a) => Atomic (Atom a) Source # 
Instance details

Defined in Data.Prim.Atom

type PrimBase (Atom a) Source # 
Instance details

Defined in Data.Prim.Atom

type PrimBase (Atom a) = Atom a
type SizeOf (Atom a) Source # 
Instance details

Defined in Data.Prim.Atom

type SizeOf (Atom a) = 1 + SizeOf a
type Alignment (Atom a) Source # 
Instance details

Defined in Data.Prim.Atom

type Alignment (Atom a) = 1 + Alignment a

class (Prim a, Eq a) => Atomic a Source #

Instances
Atomic Bool Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Char Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Int Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Int8 Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Int16 Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Int32 Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Int64 Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

Atomic Ordering Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Word Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Word8 Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Word16 Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Word32 Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Word64 Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

Atomic BlockReason Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic ThreadStatus Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Fd Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Errno Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Newline Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic NewlineMode Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic IODeviceType Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic SeekMode Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic All Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic Any Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CChar Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CSChar Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CUChar Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CShort Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CUShort Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CInt Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CUInt Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CLong Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CULong Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CLLong Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

Atomic CULLong Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

Atomic CBool Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CPtrdiff Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CSize Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CWchar Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CSigAtomic Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CIntPtr Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CUIntPtr Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CIntMax Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CUIntMax Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic WordPtr Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic IntPtr Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic IOMode Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic GeneralCategory Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic (Ptr a) Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic (FunPtr a) Source # 
Instance details

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

(Eq a, Prim a) => Atomic (Atom a) Source # 
Instance details

Defined in Data.Prim.Atom

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

Defined in Data.Prim.Atomic

Methods

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

atomicWriteMutableByteArray# :: MutableByteArray# s -> Int# -> Const a b -> State# s -> State# s Source #

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

atomicWriteOffAddr# :: Addr# -> Int# -> Const a b -> State# s -> State# s Source #

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

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

casBoolMutableByteArray# :: MutableByteArray# s -> Int# -> Const a b -> Const a b -> State# s -> (#State# s, Bool#) Source #

casBoolOffAddr# :: Addr# -> Int# -> Const a b -> Const a b -> State# s -> (#State# s, Bool#) Source #

atomicModifyMutableByteArray# :: MutableByteArray# s -> Int# -> (Const a b -> (#Const a b, b0#)) -> State# s -> (#State# s, b0#) Source #

atomicModifyOffAddr# :: Addr# -> Int# -> (Const a b -> (#Const a b, b0#)) -> State# s -> (#State# s, b0#) Source #

class Atomic a => AtomicCount a Source #

Instances
AtomicCount Int Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount Int8 Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount Int16 Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount Int32 Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount Int64 Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

AtomicCount Word Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount Word8 Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount Word16 Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount Word32 Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount Word64 Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

AtomicCount Fd Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount Errno Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CChar Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CSChar Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CUChar Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CShort Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CUShort Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CInt Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CUInt Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CLong Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CULong Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CLLong Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

AtomicCount CULLong Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

AtomicCount CBool Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CPtrdiff Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CSize Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CWchar Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CSigAtomic Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CIntPtr Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CUIntPtr Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CIntMax Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount CUIntMax Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount WordPtr Source # 
Instance details

Defined in Data.Prim.Atomic

AtomicCount IntPtr Source # 
Instance details

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

(Num a, Eq a, Prim a) => AtomicCount (Atom a) Source # 
Instance details

Defined in Data.Prim.Atom

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

Defined in Data.Prim.Atomic

class (Bits a, Atomic a) => AtomicBits a Source #

Instances
AtomicBits Bool Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits Int Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits Int8 Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits Int16 Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits Int32 Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits Int64 Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits Word Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits Word8 Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits Word16 Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits Word32 Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits Word64 Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits Fd Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CChar Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CSChar Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CUChar Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CShort Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CUShort Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CInt Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CUInt Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CLong Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CULong Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CLLong Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CULLong Source #

Available only on 64bit architectures

Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CBool Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CPtrdiff Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CSize Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CWchar Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CSigAtomic Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CIntPtr Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CUIntPtr Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CIntMax Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

AtomicBits CUIntMax Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

atomicXorFetchNewOffAddr# :: Addr# -> Int# -> CUIntMax -> State# s -> (#State# s, CUIntMax#) 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 #

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 #

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

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

(Bits a, Eq a, Prim a) => AtomicBits (Atom a) Source # 
Instance details

Defined in Data.Prim.Atom

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

Defined in Data.Prim.Atomic

Methods

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

class MonadThrow m => MonadPrim s m | m -> s Source #

Minimal complete definition

prim

Instances
MonadPrim RealWorld IO Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# RealWorld -> (#State# RealWorld, a#)) -> IO a Source #

MonadPrim s m => MonadPrim s (MaybeT m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> MaybeT m a Source #

MonadPrim s (ST s) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> ST s a Source #

MonadPrim s m => MonadPrim s (SelectT r m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> SelectT r m a Source #

(Monoid w, MonadPrim s m) => MonadPrim s (AccumT w m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> AccumT w m a Source #

(Monoid w, MonadPrim s m) => MonadPrim s (WriterT w m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> WriterT w m a Source #

(Monoid w, MonadPrim s m) => MonadPrim s (WriterT w m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> WriterT w m a Source #

MonadPrim s m => MonadPrim s (StateT st m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> StateT st m a Source #

MonadPrim s m => MonadPrim s (StateT st m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> StateT st m a Source #

MonadPrim s m => MonadPrim s (IdentityT m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> IdentityT m a Source #

MonadPrim s m => MonadPrim s (ExceptT e m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> ExceptT e m a Source #

MonadPrim s m => MonadPrim s (ReaderT r m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> ReaderT r m a Source #

MonadPrim s m => MonadPrim s (ContT r m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> ContT r m a Source #

(Monoid w, MonadPrim s m) => MonadPrim s (RWST r w st m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> RWST r w st m a Source #

(Monoid w, MonadPrim s m) => MonadPrim s (RWST r w st m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# s -> (#State# s, a#)) -> RWST r w st m a Source #

type RW = RealWorld Source #

A shorter synonym for the magical RealWorld

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#.

Instances
MonadPrim RealWorld IO Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

prim :: (State# RealWorld -> (#State# RealWorld, a#)) -> IO a Source #

MonadUnliftPrim RealWorld IO Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

withRunInPrimBase :: MonadPrimBase RealWorld n => ((forall a. IO a -> n a) -> n b) -> IO b Source #

MonadPrimBase RealWorld IO Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

primBase :: IO a -> State# RealWorld -> (#State# RealWorld, a#) Source #

Prim type size

byteCount :: forall a. Prim a => a -> Count Word8 Source #

Get the size of the data type in bytes. Argument is not evaluated.

byteCountType :: forall a. Prim a => Count Word8 Source #

Same as sizeOf, except that the type can be supplied as a type level argument

>>> :set -XTypeApplications
>>> import Data.Prim
>>> byteCountType @Int64
Count {unCount = 8}

byteCountProxy :: forall proxy a. Prim a => proxy a -> Count Word8 Source #

Same as sizeOf, but argument is a Proxy of a, instead of the type itself.

>>> import Data.Prim
>>> import Data.Proxy
>>> byteCountProxy (Proxy :: Proxy Int64)
Count {unCount = 8}

Prim type alignment

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

Get the alignemnt of the type in bytes. Argument is not evaluated.

alignmentType :: forall a. Prim a => Int Source #

Same as alignment, except that the type can be supplied with TypeApplications

>>> :set -XTypeApplications
>>> import Data.Prim
>>> alignmentType @Int32
4

alignmentProxy :: forall proxy a. Prim a => proxy a -> Int Source #

Same as alignment, but argument is a Proxy of a, instead of the type itself.

>>> import Data.Proxy
>>> alignmentProxy (Proxy :: Proxy Int64)
8

newtype Size Source #

Constructors

Size 

Fields

Instances
Bounded Size Source # 
Instance details

Defined in Data.Prim

Enum Size Source # 
Instance details

Defined in Data.Prim

Methods

succ :: Size -> Size #

pred :: Size -> Size #

toEnum :: Int -> Size #

fromEnum :: Size -> Int #

enumFrom :: Size -> [Size] #

enumFromThen :: Size -> Size -> [Size] #

enumFromTo :: Size -> Size -> [Size] #

enumFromThenTo :: Size -> Size -> Size -> [Size] #

Eq Size Source # 
Instance details

Defined in Data.Prim

Methods

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

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

Integral Size Source # 
Instance details

Defined in Data.Prim

Methods

quot :: Size -> Size -> Size #

rem :: Size -> Size -> Size #

div :: Size -> Size -> Size #

mod :: Size -> Size -> Size #

quotRem :: Size -> Size -> (Size, Size) #

divMod :: Size -> Size -> (Size, Size) #

toInteger :: Size -> Integer #

Num Size Source # 
Instance details

Defined in Data.Prim

Methods

(+) :: Size -> Size -> Size #

(-) :: Size -> Size -> Size #

(*) :: Size -> Size -> Size #

negate :: Size -> Size #

abs :: Size -> Size #

signum :: Size -> Size #

fromInteger :: Integer -> Size #

Ord Size Source # 
Instance details

Defined in Data.Prim

Methods

compare :: Size -> Size -> Ordering #

(<) :: Size -> Size -> Bool #

(<=) :: Size -> Size -> Bool #

(>) :: Size -> Size -> Bool #

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

max :: Size -> Size -> Size #

min :: Size -> Size -> Size #

Real Size Source # 
Instance details

Defined in Data.Prim

Methods

toRational :: Size -> Rational #

Show Size Source # 
Instance details

Defined in Data.Prim

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

newtype Count a Source #

Number of elements

Constructors

Count 

Fields

Instances
Bounded (Count a) Source # 
Instance details

Defined in Data.Prim

Methods

minBound :: Count a #

maxBound :: Count a #

Enum (Count a) Source # 
Instance details

Defined in Data.Prim

Methods

succ :: Count a -> Count a #

pred :: Count a -> Count a #

toEnum :: Int -> Count a #

fromEnum :: Count a -> Int #

enumFrom :: Count a -> [Count a] #

enumFromThen :: Count a -> Count a -> [Count a] #

enumFromTo :: Count a -> Count a -> [Count a] #

enumFromThenTo :: Count a -> Count a -> Count a -> [Count a] #

Eq (Count a) Source # 
Instance details

Defined in Data.Prim

Methods

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

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

Integral (Count a) Source # 
Instance details

Defined in Data.Prim

Methods

quot :: Count a -> Count a -> Count a #

rem :: Count a -> Count a -> Count a #

div :: Count a -> Count a -> Count a #

mod :: Count a -> Count a -> Count a #

quotRem :: Count a -> Count a -> (Count a, Count a) #

divMod :: Count a -> Count a -> (Count a, Count a) #

toInteger :: Count a -> Integer #

Num (Count a) Source # 
Instance details

Defined in Data.Prim

Methods

(+) :: Count a -> Count a -> Count a #

(-) :: Count a -> Count a -> Count a #

(*) :: Count a -> Count a -> Count a #

negate :: Count a -> Count a #

abs :: Count a -> Count a #

signum :: Count a -> Count a #

fromInteger :: Integer -> Count a #

Ord (Count a) Source # 
Instance details

Defined in Data.Prim

Methods

compare :: Count a -> Count a -> Ordering #

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

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

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

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

max :: Count a -> Count a -> Count a #

min :: Count a -> Count a -> Count a #

Real (Count a) Source # 
Instance details

Defined in Data.Prim

Methods

toRational :: Count a -> Rational #

Show (Count a) Source # 
Instance details

Defined in Data.Prim

Methods

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

show :: Count a -> String #

showList :: [Count a] -> ShowS #

NFData (Count a) Source # 
Instance details

Defined in Data.Prim

Methods

rnf :: Count a -> () #

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 #

type PrimBase (Count a) Source # 
Instance details

Defined in Data.Prim

type PrimBase (Count a) = Int
type SizeOf (Count a) Source # 
Instance details

Defined in Data.Prim

type SizeOf (Count a) = SizeOf (PrimBase (Count a))
type Alignment (Count a) Source # 
Instance details

Defined in Data.Prim

fromCount :: Prim a => Count a -> Int Source #

Covert to number of bytes as an Int

Since: 0.1.0

toByteCount :: Prim a => Count a -> Count Word8 Source #

Covert to the Count of bytes

Since: 0.1.0

fromByteCount :: forall a. Prim a => Count Word8 -> Count a Source #

countAsProxy :: proxy a -> Count a -> Count a Source #

Helper noop function that restricts Count to the type of proxy

Since: 0.1.0

newtype Off a Source #

Offset in number of elements

Constructors

Off 

Fields

Instances
Bounded (Off a) Source # 
Instance details

Defined in Data.Prim

Methods

minBound :: Off a #

maxBound :: Off a #

Enum (Off a) Source # 
Instance details

Defined in Data.Prim

Methods

succ :: Off a -> Off a #

pred :: Off a -> Off a #

toEnum :: Int -> Off a #

fromEnum :: Off a -> Int #

enumFrom :: Off a -> [Off a] #

enumFromThen :: Off a -> Off a -> [Off a] #

enumFromTo :: Off a -> Off a -> [Off a] #

enumFromThenTo :: Off a -> Off a -> Off a -> [Off a] #

Eq (Off a) Source # 
Instance details

Defined in Data.Prim

Methods

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

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

Integral (Off a) Source # 
Instance details

Defined in Data.Prim

Methods

quot :: Off a -> Off a -> Off a #

rem :: Off a -> Off a -> Off a #

div :: Off a -> Off a -> Off a #

mod :: Off a -> Off a -> Off a #

quotRem :: Off a -> Off a -> (Off a, Off a) #

divMod :: Off a -> Off a -> (Off a, Off a) #

toInteger :: Off a -> Integer #

Num (Off a) Source # 
Instance details

Defined in Data.Prim

Methods

(+) :: Off a -> Off a -> Off a #

(-) :: Off a -> Off a -> Off a #

(*) :: Off a -> Off a -> Off a #

negate :: Off a -> Off a #

abs :: Off a -> Off a #

signum :: Off a -> Off a #

fromInteger :: Integer -> Off a #

Ord (Off a) Source # 
Instance details

Defined in Data.Prim

Methods

compare :: Off a -> Off a -> Ordering #

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

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

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

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

max :: Off a -> Off a -> Off a #

min :: Off a -> Off a -> Off a #

Real (Off a) Source # 
Instance details

Defined in Data.Prim

Methods

toRational :: Off a -> Rational #

Show (Off a) Source # 
Instance details

Defined in Data.Prim

Methods

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

show :: Off a -> String #

showList :: [Off a] -> ShowS #

NFData (Off a) Source # 
Instance details

Defined in Data.Prim

Methods

rnf :: Off a -> () #

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 #

type PrimBase (Off a) Source # 
Instance details

Defined in Data.Prim

type PrimBase (Off a) = Int
type SizeOf (Off a) Source # 
Instance details

Defined in Data.Prim

type SizeOf (Off a) = SizeOf (PrimBase (Off a))
type Alignment (Off a) Source # 
Instance details

Defined in Data.Prim

toByteOff :: Prim e => Off e -> Off Word8 Source #

Compute byte offset from an offset of Prim type

>>> toByteOff (10 :: Off Word64)
Off {unOff = 80}

Since: 0.1.0

fromOff# :: Prim a => Off a -> Int# Source #

Convert offset of some type into number of bytes

fromByteOff :: forall a. Prim a => Off Word8 -> Off a Source #

fromByteOffRem :: forall a. Prim a => Off Word8 -> (Off a, Off Word8) Source #

offAsProxy :: proxy a -> Off a -> Off a Source #

Helper noop function that restricts Offset to the type of proxy

Since: 0.1.0

Prefetch

prefetchValue0 :: MonadPrim s m => a -> m () Source #

prefetchValue1 :: MonadPrim s m => a -> m () Source #

prefetchValue2 :: MonadPrim s m => a -> m () Source #

prefetchValue3 :: MonadPrim s m => a -> m () Source #

Re-export

module Data.Word

module Data.Int

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.

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 #

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 #

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.Prim.Class

Associated Types

type PrimBase (Ptr a) :: Type Source #

type SizeOf (Ptr a) :: Nat Source #

type Alignment (Ptr a) :: Nat Source #

Atomic (Ptr a) Source # 
Instance details

Defined in Data.Prim.Atomic

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 PrimBase (Ptr a) Source # 
Instance details

Defined in Data.Prim.Class

type PrimBase (Ptr a) = Ptr a
type SizeOf (Ptr a) Source # 
Instance details

Defined in Data.Prim.Class

type SizeOf (Ptr a) = 8
type Alignment (Ptr a) Source # 
Instance details

Defined in Data.Prim.Class

type Alignment (Ptr a) = 8
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)))

data ForeignPtr a #

The type ForeignPtr represents references to objects that are maintained in a foreign language, i.e., that are not part of the data structures usually managed by the Haskell storage manager. The essential difference between ForeignPtrs and vanilla memory references of type Ptr a is that the former may be associated with finalizers. A finalizer is a routine that is invoked when the Haskell storage manager detects that - within the Haskell heap and stack - there are no more references left that are pointing to the ForeignPtr. Typically, the finalizer will, then, invoke routines in the foreign language that free the resources bound by the foreign object.

The ForeignPtr is parameterised in the same way as Ptr. The type argument of ForeignPtr should normally be an instance of class Storable.

Instances
Eq (ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Methods

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

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

Ord (ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

Show (ForeignPtr a)

Since: base-2.1

Instance details

Defined in GHC.ForeignPtr

class Typeable (a :: k) #

The class Typeable allows a concrete representation of a type to be calculated.

Minimal complete definition

typeRep#

data Proxy (t :: k) :: forall k. k -> Type #

Proxy is a type that holds no data, but has a phantom parameter of arbitrary type (or even kind). Its use is to provide type information, even though there is no value available of that type (or it may be too costly to create one).

Historically, Proxy :: Proxy a is a safer alternative to the 'undefined :: a' idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 
Instances
Generic1 (Proxy :: k -> Type) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: Proxy a -> Rep1 Proxy a #

to1 :: Rep1 Proxy a -> Proxy a #

Monad (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

fail :: String -> Proxy a #

Functor (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Applicative (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Foldable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Proxy m -> m #

foldMap :: Monoid m => (a -> m) -> Proxy a -> m #

foldr :: (a -> b -> b) -> b -> Proxy a -> b #

foldr' :: (a -> b -> b) -> b -> Proxy a -> b #

foldl :: (b -> a -> b) -> b -> Proxy a -> b #

foldl' :: (b -> a -> b) -> b -> Proxy a -> b #

foldr1 :: (a -> a -> a) -> Proxy a -> a #

foldl1 :: (a -> a -> a) -> Proxy a -> a #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Traversable (Proxy :: Type -> Type)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

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

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

Eq1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftEq :: (a -> b -> Bool) -> Proxy a -> Proxy b -> Bool #

Ord1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftCompare :: (a -> b -> Ordering) -> Proxy a -> Proxy b -> Ordering #

Read1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Proxy a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Proxy a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Proxy a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Proxy a] #

Show1 (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Classes

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Proxy a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Proxy a] -> ShowS #

Alternative (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

MonadPlus (Proxy :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

NFData1 (Proxy :: Type -> Type)

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

Bounded (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: Type -> Type #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

NFData (Proxy a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Proxy a -> () #

type Rep1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> Type) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: k -> Type))
type Rep (Proxy t)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: Type -> Type))