primal-0.1.0.0: Primeval world of Haskell.

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

Foreign.Prim

Contents

Description

 
Synopsis

Missing primitives

Primitive

Backwards compatibility

GHC 8.6

indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# #

Read 8-bit character; offset in bytes.

indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# #

Read 31-bit character; offset in bytes.

indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# #

Read address; offset in bytes.

indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a #

Read stable pointer; offset in bytes.

indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# #

Read float; offset in bytes.

indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# #

Read double; offset in bytes.

indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int# #

Read 16-bit int; offset in bytes.

indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int# #

Read 32-bit int; offset in bytes.

indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int# #

Read 64-bit int; offset in bytes.

indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# #

Read int; offset in bytes.

indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word# #

Read 16-bit word; offset in bytes.

indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word# #

Read 32-bit word; offset in bytes.

indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word# #

Read 64-bit word; offset in bytes.

indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# #

Read word; offset in bytes.

atomicModifyMutVar_# :: MutVar# s a -> (a -> a) -> State# s -> (#State# s, a, a#) Source #

Slightly slower reimplementation of newer primops using the old atomicModifyMutVar#

Modify the contents of a MutVar#, returning the previous contents and the result of applying the given function to the previous contents.

Warning: this can fail with an unchecked exception.

atomicModifyMutVar2# :: MutVar# s a -> (a -> (a, b)) -> State# s -> (#State# s, a, (a, b)#) Source #

Slightly slower reimplementation of newer primops using the old atomicModifyMutVar#

Modify the contents of a MutVar#, returning the previous contents and the result of applying the given function to the previous contents.

Warning: this can fail with an unchecked exception.

GHC-8.2

newtype CBool #

Haskell type representing the C bool type.

Since: base-4.10.0.0

Constructors

CBool Word8 
Instances
Bounded CBool 
Instance details

Defined in Foreign.C.Types

Enum CBool 
Instance details

Defined in Foreign.C.Types

Eq CBool 
Instance details

Defined in Foreign.C.Types

Methods

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

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

Integral CBool 
Instance details

Defined in Foreign.C.Types

Num CBool 
Instance details

Defined in Foreign.C.Types

Ord CBool 
Instance details

Defined in Foreign.C.Types

Methods

compare :: CBool -> CBool -> Ordering #

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

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

(>) :: CBool -> CBool -> Bool #

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

max :: CBool -> CBool -> CBool #

min :: CBool -> CBool -> CBool #

Read CBool 
Instance details

Defined in Foreign.C.Types

Real CBool 
Instance details

Defined in Foreign.C.Types

Methods

toRational :: CBool -> Rational #

Show CBool 
Instance details

Defined in Foreign.C.Types

Methods

showsPrec :: Int -> CBool -> ShowS #

show :: CBool -> String #

showList :: [CBool] -> ShowS #

Storable CBool 
Instance details

Defined in Foreign.C.Types

Methods

sizeOf :: CBool -> Int #

alignment :: CBool -> Int #

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

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

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

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

peek :: Ptr CBool -> IO CBool #

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

Bits CBool 
Instance details

Defined in Foreign.C.Types

FiniteBits CBool 
Instance details

Defined in Foreign.C.Types

NFData CBool

Since: deepseq-1.4.3.0

Instance details

Defined in Control.DeepSeq

Methods

rnf :: CBool -> () #

Prim CBool Source # 
Instance details

Defined in Data.Prim.Class

Associated Types

type PrimBase CBool :: Type Source #

type SizeOf CBool :: Nat Source #

type Alignment CBool :: Nat Source #

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 #

AtomicCount CBool Source # 
Instance details

Defined in Data.Prim.Atomic

Atomic CBool Source # 
Instance details

Defined in Data.Prim.Atomic

type PrimBase CBool Source # 
Instance details

Defined in Data.Prim.Class

type SizeOf CBool Source # 
Instance details

Defined in Data.Prim.Class

type Alignment CBool Source # 
Instance details

Defined in Data.Prim.Class

isByteArrayPinned# :: ByteArray# -> Int# #

Determine whether a ByteArray# is guaranteed not to move during GC.

isMutableByteArrayPinned# :: MutableByteArray# d -> Int# #

Determine whether a MutableByteArray# is guaranteed not to move during GC.

GHC-8.0

compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int# #

compareByteArrays# src1 src1_ofs src2 src2_ofs n compares n bytes starting at offset src1_ofs in the first ByteArray# src1 to the range of n bytes (i.e. same length) starting at offset src2_ofs of the second ByteArray# src2. Both arrays must fully contain the specified ranges, but this is not checked. Returns an Int# less than, equal to, or greater than zero if the range is found, respectively, to be byte-wise lexicographically less than, to match, or be greater than the second range.

getSizeofMutableByteArray# :: MutableByteArray# d -> State# d -> (#State# d, Int##) #

Return the number of elements in the array.

Forward compatibility

Extra functionality

Atomic

ioCBoolToBoolBase :: IO CBool -> State# s -> (#State# s, Bool#) Source #

Helper function for converting casBool IO actions

syncSynchronize# :: State# s -> State# s Source #

Memory barrier. This will ensure that the cache is fully updated before continuing.

withMemBarrier# :: (State# s -> (#State# s, a#)) -> State# s -> (#State# s, a#) Source #

Comparison

isSameByteArray# :: ByteArray# -> ByteArray# -> Int# Source #

Because GC is guaranteed not to move unpinned memory during the unsafe FFI call we can compare memory pointers on the C side. Because the addresses cannot change underneath us we can safely guarantee pointer equality for the same pinned or unpinned arrays

toOrdering# :: Int# -> Ordering Source #

Convert memcmp result into an ordering

Setting memory

Moving memory

memmoveAddr# Source #

Arguments

:: Addr#

Source ptr

-> Int#

Offset in bytes into source array

-> Addr#

Destination ptr

-> Int#

Offset in bytes into destination

-> Int#

Number of bytes to copy

-> IO () 

memmoveMutableByteArray# Source #

Arguments

:: MutableByteArray# s

Source array

-> Int#

Offset in bytes into source array

-> MutableByteArray# s

Destination

-> Int#

Offset in bytes into destination

-> Int#

Number of bytes to copy

-> IO () 

memmoveMutableByteArrayToAddr# Source #

Arguments

:: MutableByteArray# s

Source array

-> Int#

Offset in bytes into source array

-> Addr#

Destination ptr

-> Int#

Offset in bytes into destination

-> Int#

Number of bytes to copy

-> IO () 

memmoveMutableByteArrayFromAddr# Source #

Arguments

:: Addr#

Source Ptr

-> Int#

Offset in bytes into source array

-> MutableByteArray# s

Destination

-> Int#

Offset in bytes into destination

-> Int#

Number of bytes to copy

-> IO () 

word32ToFloat# :: Word# -> Float# Source #

Cast a 32bit Word into a Float

floatToWord32# :: Float# -> Word# Source #

Cast a Float into a 32bit Word

word64ToDouble# :: Word# -> Double# Source #

Cast a 64bit Word into a Double

doubleToWord64# :: Double# -> Word# Source #

Cast a Double into a 64bit Word

Re-exports

module GHC.Exts

module GHC.Int

module GHC.Word