primal-0.3.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

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

Instances details
Prim Bool Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Bool 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 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 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 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 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 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 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 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 Source #

type SizeOf Int64 :: Nat Source #

type Alignment Int64 :: Nat Source #

Prim Ordering Source # 
Instance details

Defined in Data.Prim.Class

Prim Word Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Word 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 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 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 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 Source #

type SizeOf Word64 :: Nat Source #

type Alignment Word64 :: Nat Source #

Prim () Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase () 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 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 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 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 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 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 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 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 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 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 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 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 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 Source #

type SizeOf CRLim :: Nat Source #

type Alignment CRLim :: Nat Source #

Prim CBlkSize Source # 
Instance details

Defined in Data.Prim.Class

Prim CBlkCnt Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CBlkCnt Source #

type SizeOf CBlkCnt :: Nat Source #

type Alignment CBlkCnt :: Nat Source #

Prim CClockId Source # 
Instance details

Defined in Data.Prim.Class

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

type SizeOf CTimer :: Nat Source #

type Alignment CTimer :: Nat Source #

Prim CSocklen Source # 
Instance details

Defined in Data.Prim.Class

Prim CNfds Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CNfds Source #

type SizeOf CNfds :: Nat Source #

type Alignment CNfds :: Nat Source #

Prim Fd Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Fd 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 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 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

Prim All Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase All 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 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 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 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 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 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 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 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 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 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 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 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 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 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 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 Source #

type SizeOf CDouble :: Nat Source #

type Alignment CDouble :: Nat Source #

Prim CPtrdiff Source # 
Instance details

Defined in Data.Prim.Class

Prim CSize Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CSize 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 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 Source #

type SizeOf CIntPtr :: Nat Source #

type Alignment CIntPtr :: Nat Source #

Prim CUIntPtr Source # 
Instance details

Defined in Data.Prim.Class

Prim CIntMax Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CIntMax Source #

type SizeOf CIntMax :: Nat Source #

type Alignment CIntMax :: Nat Source #

Prim CUIntMax Source # 
Instance details

Defined in Data.Prim.Class

Prim WordPtr Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase WordPtr 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 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 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 Size Source # 
Instance details

Defined in Data.Prim.Array

Associated Types

type PrimBase Size Source #

type SizeOf Size :: Nat Source #

type Alignment Size :: Nat Source #

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

Defined in Data.Prim.Class

Associated Types

type PrimBase (Maybe a) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) Source #

type SizeOf (Atom a) :: Nat Source #

type Alignment (Atom a) :: Nat Source #

Prim (Off e) Source # 
Instance details

Defined in Data.Prim

Associated Types

type PrimBase (Off e) Source #

type SizeOf (Off e) :: Nat Source #

type Alignment (Off e) :: Nat Source #

Prim (Count e) Source # 
Instance details

Defined in Data.Prim

Associated Types

type PrimBase (Count e) Source #

type SizeOf (Count e) :: Nat Source #

type Alignment (Count e) :: 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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) 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

Instances details
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) 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

Instances details
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

Methods

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

atomicWriteMutableByteArray# :: MutableByteArray# s -> Int# -> Ptr a -> State# s -> State# s Source #

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

atomicWriteOffAddr# :: Addr# -> Int# -> Ptr a -> State# s -> State# s Source #

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

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

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

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

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

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

Atomic (FunPtr a) Source # 
Instance details

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

Methods

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

atomicWriteMutableByteArray# :: MutableByteArray# s -> Int# -> Min a -> State# s -> State# s Source #

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

atomicWriteOffAddr# :: Addr# -> Int# -> Min a -> State# s -> State# s Source #

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

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

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

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

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

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

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

Defined in Data.Prim.Atomic

Methods

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

atomicWriteMutableByteArray# :: MutableByteArray# s -> Int# -> Max a -> State# s -> State# s Source #

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

atomicWriteOffAddr# :: Addr# -> Int# -> Max a -> State# s -> State# s Source #

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

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

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

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

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

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

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

Methods

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

atomicWriteMutableByteArray# :: MutableByteArray# s -> Int# -> Sum a -> State# s -> State# s Source #

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

atomicWriteOffAddr# :: Addr# -> Int# -> Sum a -> State# s -> State# s Source #

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

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

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

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

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

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

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

Instances details
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

Instances details
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

Instances details
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 (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 (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 (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 (IdentityT m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

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

(e ~ SomeException, 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 (ContT r m) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

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

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 #

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

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

Instances details
MonadPrimBase RealWorld IO Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

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

MonadUnliftPrim RealWorld IO Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

withRunInST :: ((forall a. IO a -> ST RealWorld a) -> ST RealWorld b) -> IO b Source #

runInPrimBase1 :: (a -> IO b) -> ((a -> State# RealWorld -> (# State# RealWorld, b #)) -> State# RealWorld -> (# State# RealWorld, c #)) -> IO c Source #

runInPrimBase2 :: (a -> IO b) -> (c -> IO d) -> ((a -> State# RealWorld -> (# State# RealWorld, b #)) -> (c -> State# RealWorld -> (# State# RealWorld, d #)) -> State# RealWorld -> (# State# RealWorld, e #)) -> IO e Source #

MonadPrim RealWorld IO Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

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

data ST s a #

The strict ST monad. The ST monad allows for destructive updates, but is escapable (unlike IO). A computation of type ST s a returns a value of type a, and execute in "thread" s. The s parameter is either

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

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

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

runST (writeSTRef _|_ v >>= f) = _|_

Instances

Instances details
MonadPrimBase s (ST s) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

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

MonadUnliftPrim s (ST s) Source # 
Instance details

Defined in Control.Prim.Monad.Internal

Methods

withRunInST :: ((forall a. ST s a -> ST s a) -> ST s b) -> ST s b Source #

runInPrimBase1 :: (a -> ST s b) -> ((a -> State# s -> (# State# s, b #)) -> State# s -> (# State# s, c #)) -> ST s c Source #

runInPrimBase2 :: (a -> ST s b) -> (c -> ST s d) -> ((a -> State# s -> (# State# s, b #)) -> (c -> State# s -> (# State# s, d #)) -> State# s -> (# State# s, e #)) -> ST s e 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 #

Monad (ST s)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

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

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

return :: a -> ST s a #

Functor (ST s)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

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

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

MonadFail (ST s)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

fail :: String -> ST s a #

Applicative (ST s)

Since: base-4.4.0.0

Instance details

Defined in GHC.ST

Methods

pure :: a -> ST s a #

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

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

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

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

MonadThrow (ST s) Source # 
Instance details

Defined in Control.Prim.Monad.Throw

Methods

throwM :: Exception e => e -> ST s a Source #

MArray (STUArray s) Word (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word -> ST s Int

newArray :: Ix i => (i, i) -> Word -> ST s (STUArray s i Word) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word)

unsafeRead :: Ix i => STUArray s i Word -> Int -> ST s Word

unsafeWrite :: Ix i => STUArray s i Word -> Int -> Word -> ST s ()

MArray (STUArray s) Word8 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word8 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word8 -> ST s Int

newArray :: Ix i => (i, i) -> Word8 -> ST s (STUArray s i Word8) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word8)

unsafeRead :: Ix i => STUArray s i Word8 -> Int -> ST s Word8

unsafeWrite :: Ix i => STUArray s i Word8 -> Int -> Word8 -> ST s ()

MArray (STUArray s) Word64 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word64 -> ST s Int

newArray :: Ix i => (i, i) -> Word64 -> ST s (STUArray s i Word64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word64)

unsafeRead :: Ix i => STUArray s i Word64 -> Int -> ST s Word64

unsafeWrite :: Ix i => STUArray s i Word64 -> Int -> Word64 -> ST s ()

MArray (STUArray s) Word32 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word32 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word32 -> ST s Int

newArray :: Ix i => (i, i) -> Word32 -> ST s (STUArray s i Word32) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word32)

unsafeRead :: Ix i => STUArray s i Word32 -> Int -> ST s Word32

unsafeWrite :: Ix i => STUArray s i Word32 -> Int -> Word32 -> ST s ()

MArray (STUArray s) Word16 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Word16 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Word16 -> ST s Int

newArray :: Ix i => (i, i) -> Word16 -> ST s (STUArray s i Word16) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word16) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Word16)

unsafeRead :: Ix i => STUArray s i Word16 -> Int -> ST s Word16

unsafeWrite :: Ix i => STUArray s i Word16 -> Int -> Word16 -> ST s ()

MArray (STUArray s) Int (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Int -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int -> ST s Int

newArray :: Ix i => (i, i) -> Int -> ST s (STUArray s i Int) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int)

unsafeRead :: Ix i => STUArray s i Int -> Int -> ST s Int

unsafeWrite :: Ix i => STUArray s i Int -> Int -> Int -> ST s ()

MArray (STUArray s) Int8 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Int8 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int8 -> ST s Int

newArray :: Ix i => (i, i) -> Int8 -> ST s (STUArray s i Int8) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int8) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int8)

unsafeRead :: Ix i => STUArray s i Int8 -> Int -> ST s Int8

unsafeWrite :: Ix i => STUArray s i Int8 -> Int -> Int8 -> ST s ()

MArray (STUArray s) Int64 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Int64 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int64 -> ST s Int

newArray :: Ix i => (i, i) -> Int64 -> ST s (STUArray s i Int64) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int64)

unsafeRead :: Ix i => STUArray s i Int64 -> Int -> ST s Int64

unsafeWrite :: Ix i => STUArray s i Int64 -> Int -> Int64 -> ST s ()

MArray (STUArray s) Int32 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Int32 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int32 -> ST s Int

newArray :: Ix i => (i, i) -> Int32 -> ST s (STUArray s i Int32) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int32) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int32)

unsafeRead :: Ix i => STUArray s i Int32 -> Int -> ST s Int32

unsafeWrite :: Ix i => STUArray s i Int32 -> Int -> Int32 -> ST s ()

MArray (STUArray s) Int16 (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Int16 -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Int16 -> ST s Int

newArray :: Ix i => (i, i) -> Int16 -> ST s (STUArray s i Int16) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int16) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Int16)

unsafeRead :: Ix i => STUArray s i Int16 -> Int -> ST s Int16

unsafeWrite :: Ix i => STUArray s i Int16 -> Int -> Int16 -> ST s ()

MArray (STUArray s) Float (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Float -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Float -> ST s Int

newArray :: Ix i => (i, i) -> Float -> ST s (STUArray s i Float) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Float) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Float)

unsafeRead :: Ix i => STUArray s i Float -> Int -> ST s Float

unsafeWrite :: Ix i => STUArray s i Float -> Int -> Float -> ST s ()

MArray (STUArray s) Double (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Double -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Double -> ST s Int

newArray :: Ix i => (i, i) -> Double -> ST s (STUArray s i Double) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Double) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Double)

unsafeRead :: Ix i => STUArray s i Double -> Int -> ST s Double

unsafeWrite :: Ix i => STUArray s i Double -> Int -> Double -> ST s ()

MArray (STUArray s) Char (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Char -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Char -> ST s Int

newArray :: Ix i => (i, i) -> Char -> ST s (STUArray s i Char) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Char) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Char)

unsafeRead :: Ix i => STUArray s i Char -> Int -> ST s Char

unsafeWrite :: Ix i => STUArray s i Char -> Int -> Char -> ST s ()

MArray (STUArray s) Bool (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i Bool -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i Bool -> ST s Int

newArray :: Ix i => (i, i) -> Bool -> ST s (STUArray s i Bool) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i Bool) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i Bool)

unsafeRead :: Ix i => STUArray s i Bool -> Int -> ST s Bool

unsafeWrite :: Ix i => STUArray s i Bool -> Int -> Bool -> ST s ()

MArray (STArray s) e (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STArray s i e -> ST s (i, i) #

getNumElements :: Ix i => STArray s i e -> ST s Int

newArray :: Ix i => (i, i) -> e -> ST s (STArray s i e) #

newArray_ :: Ix i => (i, i) -> ST s (STArray s i e) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STArray s i e)

unsafeRead :: Ix i => STArray s i e -> Int -> ST s e

unsafeWrite :: Ix i => STArray s i e -> Int -> e -> ST s ()

MArray (STUArray s) (StablePtr a) (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i (StablePtr a) -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i (StablePtr a) -> ST s Int

newArray :: Ix i => (i, i) -> StablePtr a -> ST s (STUArray s i (StablePtr a)) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i (StablePtr a)) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i (StablePtr a))

unsafeRead :: Ix i => STUArray s i (StablePtr a) -> Int -> ST s (StablePtr a)

unsafeWrite :: Ix i => STUArray s i (StablePtr a) -> Int -> StablePtr a -> ST s ()

MArray (STUArray s) (Ptr a) (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i (Ptr a) -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i (Ptr a) -> ST s Int

newArray :: Ix i => (i, i) -> Ptr a -> ST s (STUArray s i (Ptr a)) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i (Ptr a)) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i (Ptr a))

unsafeRead :: Ix i => STUArray s i (Ptr a) -> Int -> ST s (Ptr a)

unsafeWrite :: Ix i => STUArray s i (Ptr a) -> Int -> Ptr a -> ST s ()

MArray (STUArray s) (FunPtr a) (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i (FunPtr a) -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i (FunPtr a) -> ST s Int

newArray :: Ix i => (i, i) -> FunPtr a -> ST s (STUArray s i (FunPtr a)) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i (FunPtr a)) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i (FunPtr a))

unsafeRead :: Ix i => STUArray s i (FunPtr a) -> Int -> ST s (FunPtr a)

unsafeWrite :: Ix i => STUArray s i (FunPtr a) -> Int -> FunPtr a -> ST s ()

Show (ST s a)

Since: base-2.1

Instance details

Defined in GHC.ST

Methods

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

show :: ST s a -> String #

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

Semigroup a => Semigroup (ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

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

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

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

Monoid a => Monoid (ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

mempty :: ST s a #

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

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

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

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

showsType :: Typeable t => proxy t -> ShowS Source #

Helper function that converts a type into a string

Since: 0.3.0

Prim type size

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

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

>>> import Data.Prim
>>> byteCount (Just 'a')
Count {unCount = 5}

Since: 0.1.0

byteCountType :: forall e. Prim e => 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}

Since: 0.1.0

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

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

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

Since: 0.1.0

Prim type alignment

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

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

Since: 0.1.0

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

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

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

Since: 0.1.0

alignmentProxy :: forall proxy e. Prim e => proxy e -> 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

Since: 0.1.0

Count

newtype Count e Source #

Number of elements

Constructors

Count 

Fields

Instances

Instances details
Bounded (Count e) Source # 
Instance details

Defined in Data.Prim

Methods

minBound :: Count e #

maxBound :: Count e #

Enum (Count e) Source # 
Instance details

Defined in Data.Prim

Methods

succ :: Count e -> Count e #

pred :: Count e -> Count e #

toEnum :: Int -> Count e #

fromEnum :: Count e -> Int #

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

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

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

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

Eq (Count e) Source # 
Instance details

Defined in Data.Prim

Methods

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

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

Integral (Count e) Source # 
Instance details

Defined in Data.Prim

Methods

quot :: Count e -> Count e -> Count e #

rem :: Count e -> Count e -> Count e #

div :: Count e -> Count e -> Count e #

mod :: Count e -> Count e -> Count e #

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

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

toInteger :: Count e -> Integer #

Num (Count e) Source # 
Instance details

Defined in Data.Prim

Methods

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

(-) :: Count e -> Count e -> Count e #

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

negate :: Count e -> Count e #

abs :: Count e -> Count e #

signum :: Count e -> Count e #

fromInteger :: Integer -> Count e #

Ord (Count e) Source # 
Instance details

Defined in Data.Prim

Methods

compare :: Count e -> Count e -> Ordering #

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

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

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

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

max :: Count e -> Count e -> Count e #

min :: Count e -> Count e -> Count e #

Real (Count e) Source # 
Instance details

Defined in Data.Prim

Methods

toRational :: Count e -> Rational #

Show (Count e) Source # 
Instance details

Defined in Data.Prim

Methods

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

show :: Count e -> String #

showList :: [Count e] -> ShowS #

NFData (Count e) Source # 
Instance details

Defined in Data.Prim

Methods

rnf :: Count e -> () #

Prim (Count e) Source # 
Instance details

Defined in Data.Prim

Associated Types

type PrimBase (Count e) Source #

type SizeOf (Count e) :: Nat Source #

type Alignment (Count e) :: Nat Source #

type PrimBase (Count e) Source # 
Instance details

Defined in Data.Prim

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

Defined in Data.Prim

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

Defined in Data.Prim

unCountBytes :: Prim e => Count e -> Int Source #

Covert an element count to number of bytes it coresponds to as an Int. See toByteCount for preserving the Count wrapper.

Since: 0.1.0

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

Covert to the Count of bytes

Since: 0.1.0

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

Compute how many elements of type e can fit in the supplied number of bytes.

Since: 0.1.0

countToOff :: Count e -> Off e Source #

Cast a count to an offset of the same type

Since: 0.2.0

countForType :: Count e -> e -> Count e Source #

Restrict type argument of Count to the same type as the second argument, which itself is not evaluated

Since: 0.2.0

countForProxyTypeOf :: Count e -> proxy e -> Count e Source #

Helper noop function that restricts Count to the type of proxy

Since: 0.2.0

Offset

newtype Off e Source #

Offset in number of elements

Constructors

Off 

Fields

Instances

Instances details
Bounded (Off e) Source # 
Instance details

Defined in Data.Prim

Methods

minBound :: Off e #

maxBound :: Off e #

Enum (Off e) Source # 
Instance details

Defined in Data.Prim

Methods

succ :: Off e -> Off e #

pred :: Off e -> Off e #

toEnum :: Int -> Off e #

fromEnum :: Off e -> Int #

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

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

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

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

Eq (Off e) Source # 
Instance details

Defined in Data.Prim

Methods

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

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

Integral (Off e) Source # 
Instance details

Defined in Data.Prim

Methods

quot :: Off e -> Off e -> Off e #

rem :: Off e -> Off e -> Off e #

div :: Off e -> Off e -> Off e #

mod :: Off e -> Off e -> Off e #

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

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

toInteger :: Off e -> Integer #

Num (Off e) Source # 
Instance details

Defined in Data.Prim

Methods

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

(-) :: Off e -> Off e -> Off e #

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

negate :: Off e -> Off e #

abs :: Off e -> Off e #

signum :: Off e -> Off e #

fromInteger :: Integer -> Off e #

Ord (Off e) Source # 
Instance details

Defined in Data.Prim

Methods

compare :: Off e -> Off e -> Ordering #

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

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

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

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

max :: Off e -> Off e -> Off e #

min :: Off e -> Off e -> Off e #

Real (Off e) Source # 
Instance details

Defined in Data.Prim

Methods

toRational :: Off e -> Rational #

Show (Off e) Source # 
Instance details

Defined in Data.Prim

Methods

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

show :: Off e -> String #

showList :: [Off e] -> ShowS #

NFData (Off e) Source # 
Instance details

Defined in Data.Prim

Methods

rnf :: Off e -> () #

Prim (Off e) Source # 
Instance details

Defined in Data.Prim

Associated Types

type PrimBase (Off e) Source #

type SizeOf (Off e) :: Nat Source #

type Alignment (Off e) :: Nat Source #

type PrimBase (Off e) Source # 
Instance details

Defined in Data.Prim

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

Defined in Data.Prim

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

Defined in Data.Prim

unOffBytes :: Prim e => Off e -> Int Source #

Convert an offset for some type e with Prim instance to the number of bytes as an Int.

>>> unOffBytes (10 :: Off Word64)
80

Since: 0.2.0

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

unOffBytes# :: Prim e => Off e -> Int# Source #

Convert offset of some type into number of bytes

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

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

offToCount :: Off e -> Count e Source #

Cast an offset to count. Useful for dealing with regions.

>>> import Data.Prim
>>> let totalCount = Count 10 :: Count Word
>>> let startOffset = Off 4 :: Off Word
>>> totalCount - offToCount startOffset
Count {unCount = 6}

Since: 0.2.0

offToByteCount :: Prim e => Off e -> Count Word8 Source #

Convert an offset in elements to count in bytres.

Since: 0.2.0

offForType :: Off e -> e -> Off e Source #

Restrict type argument of Off to the same type as the second argument, which itself is not evaluated

Since: 0.2.0

offForProxyTypeOf :: Off e -> proxy e -> Off e Source #

Helper noop function that restricts Offset to the type of proxy

Since: 0.2.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

Instances details
NFData1 Ptr

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

IArray UArray (Ptr a) 
Instance details

Defined in Data.Array.Base

Methods

bounds :: Ix i => UArray i (Ptr a) -> (i, i) #

numElements :: Ix i => UArray i (Ptr a) -> Int

unsafeArray :: Ix i => (i, i) -> [(Int, Ptr a)] -> UArray i (Ptr a)

unsafeAt :: Ix i => UArray i (Ptr a) -> Int -> Ptr a

unsafeReplace :: Ix i => UArray i (Ptr a) -> [(Int, Ptr a)] -> UArray i (Ptr a)

unsafeAccum :: Ix i => (Ptr a -> e' -> Ptr a) -> UArray i (Ptr a) -> [(Int, e')] -> UArray i (Ptr a)

unsafeAccumArray :: Ix i => (Ptr a -> e' -> Ptr a) -> Ptr a -> (i, i) -> [(Int, e')] -> UArray i (Ptr a)

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

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Associated Types

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

Methods

from1 :: forall (a :: k0). URec (Ptr ()) a -> Rep1 (URec (Ptr ())) a #

to1 :: forall (a :: k0). 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 #

Foldable (UAddr :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => UAddr m -> m #

foldMap :: Monoid m => (a -> m) -> UAddr a -> m #

foldMap' :: Monoid m => (a -> m) -> UAddr a -> m #

foldr :: (a -> b -> b) -> b -> UAddr a -> b #

foldr' :: (a -> b -> b) -> b -> UAddr a -> b #

foldl :: (b -> a -> b) -> b -> UAddr a -> b #

foldl' :: (b -> a -> b) -> b -> UAddr a -> b #

foldr1 :: (a -> a -> a) -> UAddr a -> a #

foldl1 :: (a -> a -> a) -> UAddr a -> a #

toList :: UAddr a -> [a] #

null :: UAddr a -> Bool #

length :: UAddr a -> Int #

elem :: Eq a => a -> UAddr a -> Bool #

maximum :: Ord a => UAddr a -> a #

minimum :: Ord a => UAddr a -> a #

sum :: Num a => UAddr a -> a #

product :: Num a => UAddr a -> a #

Traversable (UAddr :: Type -> Type)

Since: base-4.9.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => UAddr (f a) -> f (UAddr a) #

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

sequence :: Monad m => UAddr (m a) -> m (UAddr a) #

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

type SizeOf (Ptr a) :: Nat Source #

type Alignment (Ptr a) :: Nat Source #

Atomic (Ptr a) Source # 
Instance details

Defined in Data.Prim.Atomic

Methods

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

atomicWriteMutableByteArray# :: MutableByteArray# s -> Int# -> Ptr a -> State# s -> State# s Source #

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

atomicWriteOffAddr# :: Addr# -> Int# -> Ptr a -> State# s -> State# s Source #

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

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

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

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

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

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

MArray (STUArray s) (Ptr a) (ST s) 
Instance details

Defined in Data.Array.Base

Methods

getBounds :: Ix i => STUArray s i (Ptr a) -> ST s (i, i) #

getNumElements :: Ix i => STUArray s i (Ptr a) -> ST s Int

newArray :: Ix i => (i, i) -> Ptr a -> ST s (STUArray s i (Ptr a)) #

newArray_ :: Ix i => (i, i) -> ST s (STUArray s i (Ptr a)) #

unsafeNewArray_ :: Ix i => (i, i) -> ST s (STUArray s i (Ptr a))

unsafeRead :: Ix i => STUArray s i (Ptr a) -> Int -> ST s (Ptr a)

unsafeWrite :: Ix i => STUArray s i (Ptr a) -> Int -> Ptr a -> ST s ()

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 #

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)

Since: base-4.9.0.0

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

Instances details
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) #

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

Instances details
Generic1 (Proxy :: k -> Type)

Since: base-4.6.0.0

Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> Type #

Methods

from1 :: forall (a :: k0). Proxy a -> Rep1 Proxy a #

to1 :: forall (a :: k0). 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 #

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 #

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)

Since: base-4.6.0.0

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

(#.) :: forall a b c proxy. Coercible b c => proxy b c -> (a -> b) -> a -> c Source #

Coerce result of a function (it is also a hidden function in Data.Functor.Utils)

Since: 0.3.0

(.#) :: forall a b c proxy. Coercible b c => (a -> b) -> proxy b c -> a -> c Source #

Coerce result of a function. Flipped version of (#.)

Since: 0.3.0

class Semigroup a => Monoid a where #

The class of monoids (types with an associative binary operation that has an identity). Instances should satisfy the following:

Right identity
x <> mempty = x
Left identity
mempty <> x = x
Associativity
x <> (y <> z) = (x <> y) <> z (Semigroup law)
Concatenation
mconcat = foldr (<>) mempty

The method names refer to the monoid of lists under concatenation, but there are many other instances.

Some types can be viewed as a monoid in more than one way, e.g. both addition and multiplication on numbers. In such cases we often define newtypes and make those instances of Monoid, e.g. Sum and Product.

NOTE: Semigroup is a superclass of Monoid since base-4.11.0.0.

Minimal complete definition

mempty

Methods

mempty :: a #

Identity of mappend

>>> "Hello world" <> mempty
"Hello world"

mappend :: a -> a -> a #

An associative operation

NOTE: This method is redundant and has the default implementation mappend = (<>) since base-4.11.0.0. Should it be implemented manually, since mappend is a synonym for (<>), it is expected that the two functions are defined the same way. In a future GHC release mappend will be removed from Monoid.

mconcat :: [a] -> a #

Fold a list using the monoid.

For most types, the default definition for mconcat will be used, but the function is included in the class definition so that an optimized version can be provided for specific types.

>>> mconcat ["Hello", " ", "Haskell", "!"]
"Hello Haskell!"

Instances

Instances details
Monoid Ordering

Since: base-2.1

Instance details

Defined in GHC.Base

Monoid ()

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: () #

mappend :: () -> () -> () #

mconcat :: [()] -> () #

Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

Monoid [a]

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: [a] #

mappend :: [a] -> [a] -> [a] #

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

Semigroup a => Monoid (Maybe a)

Lift a semigroup into Maybe forming a Monoid according to http://en.wikipedia.org/wiki/Monoid: "Any semigroup S may be turned into a monoid simply by adjoining an element e not in S and defining e*e = e and e*s = s = s*e for all s ∈ S."

Since 4.11.0: constraint on inner a value generalised from Monoid to Semigroup.

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: Maybe a #

mappend :: Maybe a -> Maybe a -> Maybe a #

mconcat :: [Maybe a] -> Maybe a #

Monoid a => Monoid (IO a)

Since: base-4.9.0.0

Instance details

Defined in GHC.Base

Methods

mempty :: IO a #

mappend :: IO a -> IO a -> IO a #

mconcat :: [IO a] -> IO a #

Monoid p => Monoid (Par1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Par1 p #

mappend :: Par1 p -> Par1 p -> Par1 p #

mconcat :: [Par1 p] -> Par1 p #

(Ord a, Bounded a) => Monoid (Min a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Min a #

mappend :: Min a -> Min a -> Min a #

mconcat :: [Min a] -> Min a #

(Ord a, Bounded a) => Monoid (Max a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Max a #

mappend :: Max a -> Max a -> Max a #

mconcat :: [Max a] -> Max a #

Monoid m => Monoid (WrappedMonoid m)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Semigroup a => Monoid (Option a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup

Methods

mempty :: Option a #

mappend :: Option a -> Option a -> Option a #

mconcat :: [Option a] -> Option a #

Monoid a => Monoid (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

mempty :: Identity a #

mappend :: Identity a -> Identity a -> Identity a #

mconcat :: [Identity a] -> Identity a #

Monoid (First a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: First a #

mappend :: First a -> First a -> First a #

mconcat :: [First a] -> First a #

Monoid (Last a)

Since: base-2.1

Instance details

Defined in Data.Monoid

Methods

mempty :: Last a #

mappend :: Last a -> Last a -> Last a #

mconcat :: [Last a] -> Last a #

Monoid a => Monoid (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

Monoid (Endo a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

Monoid a => Monoid (Down a)

Since: base-4.11.0.0

Instance details

Defined in Data.Ord

Methods

mempty :: Down a #

mappend :: Down a -> Down a -> Down a #

mconcat :: [Down a] -> Down a #

Prim e => Monoid (UArray e) Source # 
Instance details

Defined in Data.Prim.Array

Methods

mempty :: UArray e #

mappend :: UArray e -> UArray e -> UArray e #

mconcat :: [UArray e] -> UArray e #

Monoid (SBArray e) Source # 
Instance details

Defined in Data.Prim.Array

Methods

mempty :: SBArray e #

mappend :: SBArray e -> SBArray e -> SBArray e #

mconcat :: [SBArray e] -> SBArray e #

Monoid (BArray e) Source # 
Instance details

Defined in Data.Prim.Array

Methods

mempty :: BArray e #

mappend :: BArray e -> BArray e -> BArray e #

mconcat :: [BArray e] -> BArray e #

Monoid b => Monoid (a -> b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: a -> b #

mappend :: (a -> b) -> (a -> b) -> a -> b #

mconcat :: [a -> b] -> a -> b #

Monoid (U1 p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: U1 p #

mappend :: U1 p -> U1 p -> U1 p #

mconcat :: [U1 p] -> U1 p #

(Monoid a, Monoid b) => Monoid (a, b)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b) #

mappend :: (a, b) -> (a, b) -> (a, b) #

mconcat :: [(a, b)] -> (a, b) #

Monoid a => Monoid (ST s a)

Since: base-4.11.0.0

Instance details

Defined in GHC.ST

Methods

mempty :: ST s a #

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

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

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 #

Monoid (f p) => Monoid (Rec1 f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: Rec1 f p #

mappend :: Rec1 f p -> Rec1 f p -> Rec1 f p #

mconcat :: [Rec1 f p] -> Rec1 f p #

(Monoid a, Monoid b, Monoid c) => Monoid (a, b, c)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c) #

mappend :: (a, b, c) -> (a, b, c) -> (a, b, c) #

mconcat :: [(a, b, c)] -> (a, b, c) #

Monoid a => Monoid (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

mempty :: Const a b #

mappend :: Const a b -> Const a b -> Const a b #

mconcat :: [Const a b] -> Const a b #

(Applicative f, Monoid a) => Monoid (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mempty :: Ap f a #

mappend :: Ap f a -> Ap f a -> Ap f a #

mconcat :: [Ap f a] -> Ap f a #

Alternative f => Monoid (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Alt f a #

mappend :: Alt f a -> Alt f a -> Alt f a #

mconcat :: [Alt f a] -> Alt f a #

Monoid c => Monoid (K1 i c p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: K1 i c p #

mappend :: K1 i c p -> K1 i c p -> K1 i c p #

mconcat :: [K1 i c p] -> K1 i c p #

(Monoid (f p), Monoid (g p)) => Monoid ((f :*: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :*: g) p #

mappend :: (f :*: g) p -> (f :*: g) p -> (f :*: g) p #

mconcat :: [(f :*: g) p] -> (f :*: g) p #

(Monoid a, Monoid b, Monoid c, Monoid d) => Monoid (a, b, c, d)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d) #

mappend :: (a, b, c, d) -> (a, b, c, d) -> (a, b, c, d) #

mconcat :: [(a, b, c, d)] -> (a, b, c, d) #

Monoid (f p) => Monoid (M1 i c f p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: M1 i c f p #

mappend :: M1 i c f p -> M1 i c f p -> M1 i c f p #

mconcat :: [M1 i c f p] -> M1 i c f p #

Monoid (f (g p)) => Monoid ((f :.: g) p)

Since: base-4.12.0.0

Instance details

Defined in GHC.Generics

Methods

mempty :: (f :.: g) p #

mappend :: (f :.: g) p -> (f :.: g) p -> (f :.: g) p #

mconcat :: [(f :.: g) p] -> (f :.: g) p #

(Monoid a, Monoid b, Monoid c, Monoid d, Monoid e) => Monoid (a, b, c, d, e)

Since: base-2.1

Instance details

Defined in GHC.Base

Methods

mempty :: (a, b, c, d, e) #

mappend :: (a, b, c, d, e) -> (a, b, c, d, e) -> (a, b, c, d, e) #

mconcat :: [(a, b, c, d, e)] -> (a, b, c, d, e) #

newtype Ap (f :: k -> Type) (a :: k) #

This data type witnesses the lifting of a Monoid into an Applicative pointwise.

Since: base-4.12.0.0

Constructors

Ap 

Fields

Instances

Instances details
Generic1 (Ap f :: k -> Type)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep1 (Ap f) :: k -> Type #

Methods

from1 :: forall (a :: k0). Ap f a -> Rep1 (Ap f) a #

to1 :: forall (a :: k0). Rep1 (Ap f) a -> Ap f a #

Monad f => Monad (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(>>=) :: Ap f a -> (a -> Ap f b) -> Ap f b #

(>>) :: Ap f a -> Ap f b -> Ap f b #

return :: a -> Ap f a #

Functor f => Functor (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

fmap :: (a -> b) -> Ap f a -> Ap f b #

(<$) :: a -> Ap f b -> Ap f a #

MonadFail f => MonadFail (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

fail :: String -> Ap f a #

Applicative f => Applicative (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

pure :: a -> Ap f a #

(<*>) :: Ap f (a -> b) -> Ap f a -> Ap f b #

liftA2 :: (a -> b -> c) -> Ap f a -> Ap f b -> Ap f c #

(*>) :: Ap f a -> Ap f b -> Ap f b #

(<*) :: Ap f a -> Ap f b -> Ap f a #

Foldable f => Foldable (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Ap f m -> m #

foldMap :: Monoid m => (a -> m) -> Ap f a -> m #

foldMap' :: Monoid m => (a -> m) -> Ap f a -> m #

foldr :: (a -> b -> b) -> b -> Ap f a -> b #

foldr' :: (a -> b -> b) -> b -> Ap f a -> b #

foldl :: (b -> a -> b) -> b -> Ap f a -> b #

foldl' :: (b -> a -> b) -> b -> Ap f a -> b #

foldr1 :: (a -> a -> a) -> Ap f a -> a #

foldl1 :: (a -> a -> a) -> Ap f a -> a #

toList :: Ap f a -> [a] #

null :: Ap f a -> Bool #

length :: Ap f a -> Int #

elem :: Eq a => a -> Ap f a -> Bool #

maximum :: Ord a => Ap f a -> a #

minimum :: Ord a => Ap f a -> a #

sum :: Num a => Ap f a -> a #

product :: Num a => Ap f a -> a #

Traversable f => Traversable (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Ap f a -> f0 (Ap f b) #

sequenceA :: Applicative f0 => Ap f (f0 a) -> f0 (Ap f a) #

mapM :: Monad m => (a -> m b) -> Ap f a -> m (Ap f b) #

sequence :: Monad m => Ap f (m a) -> m (Ap f a) #

Alternative f => Alternative (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

empty :: Ap f a #

(<|>) :: Ap f a -> Ap f a -> Ap f a #

some :: Ap f a -> Ap f [a] #

many :: Ap f a -> Ap f [a] #

MonadPlus f => MonadPlus (Ap f)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mzero :: Ap f a #

mplus :: Ap f a -> Ap f a -> Ap f a #

(Applicative f, Bounded a) => Bounded (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

minBound :: Ap f a #

maxBound :: Ap f a #

Enum (f a) => Enum (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

succ :: Ap f a -> Ap f a #

pred :: Ap f a -> Ap f a #

toEnum :: Int -> Ap f a #

fromEnum :: Ap f a -> Int #

enumFrom :: Ap f a -> [Ap f a] #

enumFromThen :: Ap f a -> Ap f a -> [Ap f a] #

enumFromTo :: Ap f a -> Ap f a -> [Ap f a] #

enumFromThenTo :: Ap f a -> Ap f a -> Ap f a -> [Ap f a] #

Eq (f a) => Eq (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(==) :: Ap f a -> Ap f a -> Bool #

(/=) :: Ap f a -> Ap f a -> Bool #

(Applicative f, Num a) => Num (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(+) :: Ap f a -> Ap f a -> Ap f a #

(-) :: Ap f a -> Ap f a -> Ap f a #

(*) :: Ap f a -> Ap f a -> Ap f a #

negate :: Ap f a -> Ap f a #

abs :: Ap f a -> Ap f a #

signum :: Ap f a -> Ap f a #

fromInteger :: Integer -> Ap f a #

Ord (f a) => Ord (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

compare :: Ap f a -> Ap f a -> Ordering #

(<) :: Ap f a -> Ap f a -> Bool #

(<=) :: Ap f a -> Ap f a -> Bool #

(>) :: Ap f a -> Ap f a -> Bool #

(>=) :: Ap f a -> Ap f a -> Bool #

max :: Ap f a -> Ap f a -> Ap f a #

min :: Ap f a -> Ap f a -> Ap f a #

Read (f a) => Read (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

readsPrec :: Int -> ReadS (Ap f a) #

readList :: ReadS [Ap f a] #

readPrec :: ReadPrec (Ap f a) #

readListPrec :: ReadPrec [Ap f a] #

Show (f a) => Show (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

showsPrec :: Int -> Ap f a -> ShowS #

show :: Ap f a -> String #

showList :: [Ap f a] -> ShowS #

Generic (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Associated Types

type Rep (Ap f a) :: Type -> Type #

Methods

from :: Ap f a -> Rep (Ap f a) x #

to :: Rep (Ap f a) x -> Ap f a #

(Applicative f, Semigroup a) => Semigroup (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

(<>) :: Ap f a -> Ap f a -> Ap f a #

sconcat :: NonEmpty (Ap f a) -> Ap f a #

stimes :: Integral b => b -> Ap f a -> Ap f a #

(Applicative f, Monoid a) => Monoid (Ap f a)

Since: base-4.12.0.0

Instance details

Defined in Data.Monoid

Methods

mempty :: Ap f a #

mappend :: Ap f a -> Ap f a -> Ap f a #

mconcat :: [Ap f a] -> Ap f a #

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

Defined in Data.Prim.Class

Associated Types

type PrimBase (Ap f a) Source #

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

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

type Rep1 (Ap f :: k -> Type) 
Instance details

Defined in Data.Monoid

type Rep1 (Ap f :: k -> Type) = D1 ('MetaData "Ap" "Data.Monoid" "base" 'True) (C1 ('MetaCons "Ap" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)))
type Rep (Ap f a) 
Instance details

Defined in Data.Monoid

type Rep (Ap f a) = D1 ('MetaData "Ap" "Data.Monoid" "base" 'True) (C1 ('MetaCons "Ap" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAp") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))
type PrimBase (Ap f a) Source # 
Instance details

Defined in Data.Prim.Class

type PrimBase (Ap f a) = f a
type SizeOf (Ap f a) Source # 
Instance details

Defined in Data.Prim.Class

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

Defined in Data.Prim.Class

type Alignment (Ap f a) = Alignment (PrimBase (Ap f a))

newtype Dual a #

The dual of a Monoid, obtained by swapping the arguments of mappend.

>>> getDual (mappend (Dual "Hello") (Dual "World"))
"WorldHello"

Constructors

Dual 

Fields

Instances

Instances details
Monad Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Dual a -> (a -> Dual b) -> Dual b #

(>>) :: Dual a -> Dual b -> Dual b #

return :: a -> Dual a #

Functor Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Dual a -> Dual b #

(<$) :: a -> Dual b -> Dual a #

Applicative Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Dual a #

(<*>) :: Dual (a -> b) -> Dual a -> Dual b #

liftA2 :: (a -> b -> c) -> Dual a -> Dual b -> Dual c #

(*>) :: Dual a -> Dual b -> Dual b #

(<*) :: Dual a -> Dual b -> Dual a #

Foldable Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Dual m -> m #

foldMap :: Monoid m => (a -> m) -> Dual a -> m #

foldMap' :: Monoid m => (a -> m) -> Dual a -> m #

foldr :: (a -> b -> b) -> b -> Dual a -> b #

foldr' :: (a -> b -> b) -> b -> Dual a -> b #

foldl :: (b -> a -> b) -> b -> Dual a -> b #

foldl' :: (b -> a -> b) -> b -> Dual a -> b #

foldr1 :: (a -> a -> a) -> Dual a -> a #

foldl1 :: (a -> a -> a) -> Dual a -> a #

toList :: Dual a -> [a] #

null :: Dual a -> Bool #

length :: Dual a -> Int #

elem :: Eq a => a -> Dual a -> Bool #

maximum :: Ord a => Dual a -> a #

minimum :: Ord a => Dual a -> a #

sum :: Num a => Dual a -> a #

product :: Num a => Dual a -> a #

Traversable Dual

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => Dual (f a) -> f (Dual a) #

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

sequence :: Monad m => Dual (m a) -> m (Dual a) #

NFData1 Dual

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

Bounded a => Bounded (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: Dual a #

maxBound :: Dual a #

Eq a => Eq (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Ord a => Ord (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Dual a -> Dual a -> Ordering #

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

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

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

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

max :: Dual a -> Dual a -> Dual a #

min :: Dual a -> Dual a -> Dual a #

Read a => Read (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

show :: Dual a -> String #

showList :: [Dual a] -> ShowS #

Generic (Dual a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Dual a) :: Type -> Type #

Methods

from :: Dual a -> Rep (Dual a) x #

to :: Rep (Dual a) x -> Dual a #

Semigroup a => Semigroup (Dual a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Dual a -> Dual a -> Dual a #

sconcat :: NonEmpty (Dual a) -> Dual a #

stimes :: Integral b => b -> Dual a -> Dual a #

Monoid a => Monoid (Dual a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Dual a #

mappend :: Dual a -> Dual a -> Dual a #

mconcat :: [Dual a] -> Dual a #

NFData a => NFData (Dual a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Dual a -> () #

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

Defined in Data.Prim.Class

Associated Types

type PrimBase (Dual a) Source #

type SizeOf (Dual a) :: Nat Source #

type Alignment (Dual a) :: Nat Source #

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

Generic1 Dual

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Dual :: k -> Type #

Methods

from1 :: forall (a :: k). Dual a -> Rep1 Dual a #

to1 :: forall (a :: k). Rep1 Dual a -> Dual a #

type Rep (Dual a) 
Instance details

Defined in Data.Semigroup.Internal

type Rep (Dual a) = D1 ('MetaData "Dual" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type PrimBase (Dual a) Source # 
Instance details

Defined in Data.Prim.Class

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

Defined in Data.Prim.Class

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

Defined in Data.Prim.Class

type Rep1 Dual 
Instance details

Defined in Data.Semigroup.Internal

type Rep1 Dual = D1 ('MetaData "Dual" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Dual" 'PrefixI 'True) (S1 ('MetaSel ('Just "getDual") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

newtype Endo a #

The monoid of endomorphisms under composition.

>>> let computation = Endo ("Hello, " ++) <> Endo (++ "!")
>>> appEndo computation "Haskell"
"Hello, Haskell!"

Constructors

Endo 

Fields

Instances

Instances details
Generic (Endo a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Endo a) :: Type -> Type #

Methods

from :: Endo a -> Rep (Endo a) x #

to :: Rep (Endo a) x -> Endo a #

Semigroup (Endo a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Endo a -> Endo a -> Endo a #

sconcat :: NonEmpty (Endo a) -> Endo a #

stimes :: Integral b => b -> Endo a -> Endo a #

Monoid (Endo a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Endo a #

mappend :: Endo a -> Endo a -> Endo a #

mconcat :: [Endo a] -> Endo a #

type Rep (Endo a) 
Instance details

Defined in Data.Semigroup.Internal

type Rep (Endo a) = D1 ('MetaData "Endo" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Endo" 'PrefixI 'True) (S1 ('MetaSel ('Just "appEndo") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (a -> a))))

newtype All #

Boolean monoid under conjunction (&&).

>>> getAll (All True <> mempty <> All False)
False
>>> getAll (mconcat (map (\x -> All (even x)) [2,4,6,7,8]))
False

Constructors

All 

Fields

Instances

Instances details
Bounded All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: All #

maxBound :: All #

Eq All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Ord All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: All -> All -> Ordering #

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

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

(>) :: All -> All -> Bool #

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

max :: All -> All -> All #

min :: All -> All -> All #

Read All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> All -> ShowS #

show :: All -> String #

showList :: [All] -> ShowS #

Generic All

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep All :: Type -> Type #

Methods

from :: All -> Rep All x #

to :: Rep All x -> All #

Semigroup All

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: All -> All -> All #

sconcat :: NonEmpty All -> All #

stimes :: Integral b => b -> All -> All #

Monoid All

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: All #

mappend :: All -> All -> All #

mconcat :: [All] -> All #

NFData All

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: All -> () #

Prim All Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase All Source #

type SizeOf All :: Nat Source #

type Alignment All :: Nat Source #

Atomic All Source # 
Instance details

Defined in Data.Prim.Atomic

type Rep All 
Instance details

Defined in Data.Semigroup.Internal

type Rep All = D1 ('MetaData "All" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "All" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAll") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))
type PrimBase All Source # 
Instance details

Defined in Data.Prim.Class

type SizeOf All Source # 
Instance details

Defined in Data.Prim.Class

type Alignment All Source # 
Instance details

Defined in Data.Prim.Class

newtype Any #

Boolean monoid under disjunction (||).

>>> getAny (Any True <> mempty <> Any False)
True
>>> getAny (mconcat (map (\x -> Any (even x)) [2,4,6,7,8]))
True

Constructors

Any 

Fields

Instances

Instances details
Bounded Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: Any #

maxBound :: Any #

Eq Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Ord Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Any -> Any -> Ordering #

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

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

(>) :: Any -> Any -> Bool #

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

max :: Any -> Any -> Any #

min :: Any -> Any -> Any #

Read Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Any -> ShowS #

show :: Any -> String #

showList :: [Any] -> ShowS #

Generic Any

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep Any :: Type -> Type #

Methods

from :: Any -> Rep Any x #

to :: Rep Any x -> Any #

Semigroup Any

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Any -> Any -> Any #

sconcat :: NonEmpty Any -> Any #

stimes :: Integral b => b -> Any -> Any #

Monoid Any

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Any #

mappend :: Any -> Any -> Any #

mconcat :: [Any] -> Any #

NFData Any

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Any -> () #

Prim Any Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase Any Source #

type SizeOf Any :: Nat Source #

type Alignment Any :: Nat Source #

Atomic Any Source # 
Instance details

Defined in Data.Prim.Atomic

type Rep Any 
Instance details

Defined in Data.Semigroup.Internal

type Rep Any = D1 ('MetaData "Any" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Any" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAny") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Bool)))
type PrimBase Any Source # 
Instance details

Defined in Data.Prim.Class

type SizeOf Any Source # 
Instance details

Defined in Data.Prim.Class

type Alignment Any Source # 
Instance details

Defined in Data.Prim.Class

newtype Sum a #

Monoid under addition.

>>> getSum (Sum 1 <> Sum 2 <> mempty)
3

Constructors

Sum 

Fields

Instances

Instances details
Monad Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Sum a -> (a -> Sum b) -> Sum b #

(>>) :: Sum a -> Sum b -> Sum b #

return :: a -> Sum a #

Functor Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Sum a -> Sum b #

(<$) :: a -> Sum b -> Sum a #

Applicative Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Sum a #

(<*>) :: Sum (a -> b) -> Sum a -> Sum b #

liftA2 :: (a -> b -> c) -> Sum a -> Sum b -> Sum c #

(*>) :: Sum a -> Sum b -> Sum b #

(<*) :: Sum a -> Sum b -> Sum a #

Foldable Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Sum m -> m #

foldMap :: Monoid m => (a -> m) -> Sum a -> m #

foldMap' :: Monoid m => (a -> m) -> Sum a -> m #

foldr :: (a -> b -> b) -> b -> Sum a -> b #

foldr' :: (a -> b -> b) -> b -> Sum a -> b #

foldl :: (b -> a -> b) -> b -> Sum a -> b #

foldl' :: (b -> a -> b) -> b -> Sum a -> b #

foldr1 :: (a -> a -> a) -> Sum a -> a #

foldl1 :: (a -> a -> a) -> Sum a -> a #

toList :: Sum a -> [a] #

null :: Sum a -> Bool #

length :: Sum a -> Int #

elem :: Eq a => a -> Sum a -> Bool #

maximum :: Ord a => Sum a -> a #

minimum :: Ord a => Sum a -> a #

sum :: Num a => Sum a -> a #

product :: Num a => Sum a -> a #

Traversable Sum

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => Sum (f a) -> f (Sum a) #

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

sequence :: Monad m => Sum (m a) -> m (Sum a) #

NFData1 Sum

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

Bounded a => Bounded (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

minBound :: Sum a #

maxBound :: Sum a #

Eq a => Eq (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Num a => Num (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

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

(-) :: Sum a -> Sum a -> Sum a #

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

negate :: Sum a -> Sum a #

abs :: Sum a -> Sum a #

signum :: Sum a -> Sum a #

fromInteger :: Integer -> Sum a #

Ord a => Ord (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Sum a -> Sum a -> Ordering #

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

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

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

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

max :: Sum a -> Sum a -> Sum a #

min :: Sum a -> Sum a -> Sum a #

Read a => Read (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

show :: Sum a -> String #

showList :: [Sum a] -> ShowS #

Generic (Sum a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Sum a) :: Type -> Type #

Methods

from :: Sum a -> Rep (Sum a) x #

to :: Rep (Sum a) x -> Sum a #

Num a => Semigroup (Sum a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Sum a -> Sum a -> Sum a #

sconcat :: NonEmpty (Sum a) -> Sum a #

stimes :: Integral b => b -> Sum a -> Sum a #

Num a => Monoid (Sum a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Sum a #

mappend :: Sum a -> Sum a -> Sum a #

mconcat :: [Sum a] -> Sum a #

NFData a => NFData (Sum a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Sum a -> () #

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

Defined in Data.Prim.Class

Associated Types

type PrimBase (Sum a) Source #

type SizeOf (Sum a) :: Nat Source #

type Alignment (Sum a) :: Nat Source #

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

Methods

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

atomicWriteMutableByteArray# :: MutableByteArray# s -> Int# -> Sum a -> State# s -> State# s Source #

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

atomicWriteOffAddr# :: Addr# -> Int# -> Sum a -> State# s -> State# s Source #

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

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

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

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

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

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

Generic1 Sum

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Sum :: k -> Type #

Methods

from1 :: forall (a :: k). Sum a -> Rep1 Sum a #

to1 :: forall (a :: k). Rep1 Sum a -> Sum a #

type Rep (Sum a) 
Instance details

Defined in Data.Semigroup.Internal

type Rep (Sum a) = D1 ('MetaData "Sum" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type PrimBase (Sum a) Source # 
Instance details

Defined in Data.Prim.Class

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

Defined in Data.Prim.Class

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

Defined in Data.Prim.Class

type Rep1 Sum 
Instance details

Defined in Data.Semigroup.Internal

type Rep1 Sum = D1 ('MetaData "Sum" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Sum" 'PrefixI 'True) (S1 ('MetaSel ('Just "getSum") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

newtype Product a #

Monoid under multiplication.

>>> getProduct (Product 3 <> Product 4 <> mempty)
12

Constructors

Product 

Fields

Instances

Instances details
Monad Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Product a -> (a -> Product b) -> Product b #

(>>) :: Product a -> Product b -> Product b #

return :: a -> Product a #

Functor Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Product a -> Product b #

(<$) :: a -> Product b -> Product a #

Applicative Product

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Product a #

(<*>) :: Product (a -> b) -> Product a -> Product b #

liftA2 :: (a -> b -> c) -> Product a -> Product b -> Product c #

(*>) :: Product a -> Product b -> Product b #

(<*) :: Product a -> Product b -> Product a #

Foldable Product

Since: base-4.8.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Product m -> m #

foldMap :: Monoid m => (a -> m) -> Product a -> m #

foldMap' :: Monoid m => (a -> m) -> Product a -> m #

foldr :: (a -> b -> b) -> b -> Product a -> b #

foldr' :: (a -> b -> b) -> b -> Product a -> b #

foldl :: (b -> a -> b) -> b -> Product a -> b #

foldl' :: (b -> a -> b) -> b -> Product a -> b #

foldr1 :: (a -> a -> a) -> Product a -> a #

foldl1 :: (a -> a -> a) -> Product a -> a #

toList :: Product a -> [a] #

null :: Product a -> Bool #

length :: Product a -> Int #

elem :: Eq a => a -> Product a -> Bool #

maximum :: Ord a => Product a -> a #

minimum :: Ord a => Product a -> a #

sum :: Num a => Product a -> a #

product :: Num a => Product a -> a #

Traversable Product

Since: base-4.8.0.0

Instance details

Defined in Data.Traversable

Methods

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

sequenceA :: Applicative f => Product (f a) -> f (Product a) #

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

sequence :: Monad m => Product (m a) -> m (Product a) #

NFData1 Product

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

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

Bounded a => Bounded (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Eq a => Eq (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

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

Num a => Num (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

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

(-) :: Product a -> Product a -> Product a #

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

negate :: Product a -> Product a #

abs :: Product a -> Product a #

signum :: Product a -> Product a #

fromInteger :: Integer -> Product a #

Ord a => Ord (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Product a -> Product a -> Ordering #

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

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

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

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

max :: Product a -> Product a -> Product a #

min :: Product a -> Product a -> Product a #

Read a => Read (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Show a => Show (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

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

show :: Product a -> String #

showList :: [Product a] -> ShowS #

Generic (Product a)

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Product a) :: Type -> Type #

Methods

from :: Product a -> Rep (Product a) x #

to :: Rep (Product a) x -> Product a #

Num a => Semigroup (Product a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Product a -> Product a -> Product a #

sconcat :: NonEmpty (Product a) -> Product a #

stimes :: Integral b => b -> Product a -> Product a #

Num a => Monoid (Product a)

Since: base-2.1

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Product a #

mappend :: Product a -> Product a -> Product a #

mconcat :: [Product a] -> Product a #

NFData a => NFData (Product a)

Since: deepseq-1.4.0.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: Product a -> () #

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

Defined in Data.Prim.Class

Associated Types

type PrimBase (Product a) Source #

type SizeOf (Product a) :: Nat Source #

type Alignment (Product a) :: Nat Source #

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

Defined in Data.Prim.Atomic

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

Defined in Data.Prim.Atomic

Generic1 Product

Since: base-4.7.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 Product :: k -> Type #

Methods

from1 :: forall (a :: k). Product a -> Rep1 Product a #

to1 :: forall (a :: k). Rep1 Product a -> Product a #

type Rep (Product a) 
Instance details

Defined in Data.Semigroup.Internal

type Rep (Product a) = D1 ('MetaData "Product" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type PrimBase (Product a) Source # 
Instance details

Defined in Data.Prim.Class

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

Defined in Data.Prim.Class

type Alignment (Product a) Source # 
Instance details

Defined in Data.Prim.Class

type Rep1 Product 
Instance details

Defined in Data.Semigroup.Internal

type Rep1 Product = D1 ('MetaData "Product" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Product" 'PrefixI 'True) (S1 ('MetaSel ('Just "getProduct") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))

newtype Alt (f :: k -> Type) (a :: k) #

Monoid under <|>.

>>> getAlt (Alt (Just 12) <> Alt (Just 24))
Just 12
>>> getAlt $ Alt Nothing <> Alt (Just 24)
Just 24

Since: base-4.8.0.0

Constructors

Alt 

Fields

Instances

Instances details
Generic1 (Alt f :: k -> Type)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep1 (Alt f) :: k -> Type #

Methods

from1 :: forall (a :: k0). Alt f a -> Rep1 (Alt f) a #

to1 :: forall (a :: k0). Rep1 (Alt f) a -> Alt f a #

Monad f => Monad (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(>>=) :: Alt f a -> (a -> Alt f b) -> Alt f b #

(>>) :: Alt f a -> Alt f b -> Alt f b #

return :: a -> Alt f a #

Functor f => Functor (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

fmap :: (a -> b) -> Alt f a -> Alt f b #

(<$) :: a -> Alt f b -> Alt f a #

Applicative f => Applicative (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

pure :: a -> Alt f a #

(<*>) :: Alt f (a -> b) -> Alt f a -> Alt f b #

liftA2 :: (a -> b -> c) -> Alt f a -> Alt f b -> Alt f c #

(*>) :: Alt f a -> Alt f b -> Alt f b #

(<*) :: Alt f a -> Alt f b -> Alt f a #

Foldable f => Foldable (Alt f)

Since: base-4.12.0.0

Instance details

Defined in Data.Foldable

Methods

fold :: Monoid m => Alt f m -> m #

foldMap :: Monoid m => (a -> m) -> Alt f a -> m #

foldMap' :: Monoid m => (a -> m) -> Alt f a -> m #

foldr :: (a -> b -> b) -> b -> Alt f a -> b #

foldr' :: (a -> b -> b) -> b -> Alt f a -> b #

foldl :: (b -> a -> b) -> b -> Alt f a -> b #

foldl' :: (b -> a -> b) -> b -> Alt f a -> b #

foldr1 :: (a -> a -> a) -> Alt f a -> a #

foldl1 :: (a -> a -> a) -> Alt f a -> a #

toList :: Alt f a -> [a] #

null :: Alt f a -> Bool #

length :: Alt f a -> Int #

elem :: Eq a => a -> Alt f a -> Bool #

maximum :: Ord a => Alt f a -> a #

minimum :: Ord a => Alt f a -> a #

sum :: Num a => Alt f a -> a #

product :: Num a => Alt f a -> a #

Traversable f => Traversable (Alt f)

Since: base-4.12.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Alt f a -> f0 (Alt f b) #

sequenceA :: Applicative f0 => Alt f (f0 a) -> f0 (Alt f a) #

mapM :: Monad m => (a -> m b) -> Alt f a -> m (Alt f b) #

sequence :: Monad m => Alt f (m a) -> m (Alt f a) #

Alternative f => Alternative (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

empty :: Alt f a #

(<|>) :: Alt f a -> Alt f a -> Alt f a #

some :: Alt f a -> Alt f [a] #

many :: Alt f a -> Alt f [a] #

MonadPlus f => MonadPlus (Alt f)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mzero :: Alt f a #

mplus :: Alt f a -> Alt f a -> Alt f a #

Enum (f a) => Enum (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

succ :: Alt f a -> Alt f a #

pred :: Alt f a -> Alt f a #

toEnum :: Int -> Alt f a #

fromEnum :: Alt f a -> Int #

enumFrom :: Alt f a -> [Alt f a] #

enumFromThen :: Alt f a -> Alt f a -> [Alt f a] #

enumFromTo :: Alt f a -> Alt f a -> [Alt f a] #

enumFromThenTo :: Alt f a -> Alt f a -> Alt f a -> [Alt f a] #

Eq (f a) => Eq (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(==) :: Alt f a -> Alt f a -> Bool #

(/=) :: Alt f a -> Alt f a -> Bool #

Num (f a) => Num (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(+) :: Alt f a -> Alt f a -> Alt f a #

(-) :: Alt f a -> Alt f a -> Alt f a #

(*) :: Alt f a -> Alt f a -> Alt f a #

negate :: Alt f a -> Alt f a #

abs :: Alt f a -> Alt f a #

signum :: Alt f a -> Alt f a #

fromInteger :: Integer -> Alt f a #

Ord (f a) => Ord (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

compare :: Alt f a -> Alt f a -> Ordering #

(<) :: Alt f a -> Alt f a -> Bool #

(<=) :: Alt f a -> Alt f a -> Bool #

(>) :: Alt f a -> Alt f a -> Bool #

(>=) :: Alt f a -> Alt f a -> Bool #

max :: Alt f a -> Alt f a -> Alt f a #

min :: Alt f a -> Alt f a -> Alt f a #

Read (f a) => Read (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

readsPrec :: Int -> ReadS (Alt f a) #

readList :: ReadS [Alt f a] #

readPrec :: ReadPrec (Alt f a) #

readListPrec :: ReadPrec [Alt f a] #

Show (f a) => Show (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

showsPrec :: Int -> Alt f a -> ShowS #

show :: Alt f a -> String #

showList :: [Alt f a] -> ShowS #

Generic (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Associated Types

type Rep (Alt f a) :: Type -> Type #

Methods

from :: Alt f a -> Rep (Alt f a) x #

to :: Rep (Alt f a) x -> Alt f a #

Alternative f => Semigroup (Alt f a)

Since: base-4.9.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

(<>) :: Alt f a -> Alt f a -> Alt f a #

sconcat :: NonEmpty (Alt f a) -> Alt f a #

stimes :: Integral b => b -> Alt f a -> Alt f a #

Alternative f => Monoid (Alt f a)

Since: base-4.8.0.0

Instance details

Defined in Data.Semigroup.Internal

Methods

mempty :: Alt f a #

mappend :: Alt f a -> Alt f a -> Alt f a #

mconcat :: [Alt f a] -> Alt f a #

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

Defined in Data.Prim.Class

Associated Types

type PrimBase (Alt f a) Source #

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

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

type Rep1 (Alt f :: k -> Type) 
Instance details

Defined in Data.Semigroup.Internal

type Rep1 (Alt f :: k -> Type) = D1 ('MetaData "Alt" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Alt" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAlt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec1 f)))
type Rep (Alt f a) 
Instance details

Defined in Data.Semigroup.Internal

type Rep (Alt f a) = D1 ('MetaData "Alt" "Data.Semigroup.Internal" "base" 'True) (C1 ('MetaCons "Alt" 'PrefixI 'True) (S1 ('MetaSel ('Just "getAlt") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (f a))))
type PrimBase (Alt f a) Source # 
Instance details

Defined in Data.Prim.Class

type PrimBase (Alt f a) = f a
type SizeOf (Alt f a) Source # 
Instance details

Defined in Data.Prim.Class

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

Defined in Data.Prim.Class

type Alignment (Alt f a) = Alignment (PrimBase (Alt f a))