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

Foreign.Prim

Description

 
Synopsis

Missing primitives

touch# :: a -> State# s -> State# s Source #

Same as touch#, except it is not restricted to RealWorld state token.

keepAlive# Source #

Arguments

:: a

The value to preserve

-> (State# s -> (# State# s, r #))

The continuation in which the value will be preserved

-> State# s 
-> (# State# s, r #) 

Forward compatible operator that might be introduced in some future ghc version.

See: #17760

Current version is not as efficient as the version that will be introduced in the future, because it works around the ghc bug by simply preventing inlining and relying on the touch function.

Since: 0.1.0

Primitive

Backwards compatibility

GHC 8.6

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

Read 8-bit character; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) #

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read 31-bit character; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Char# #) #

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsWideChar# :: MutableByteArray# d -> Int# -> Char# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read address; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Addr# #) #

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsAddr# :: MutableByteArray# d -> Int# -> Addr# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read stable pointer; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, StablePtr# a #) #

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsStablePtr# :: MutableByteArray# d -> Int# -> StablePtr# a -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read float; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Float# #) #

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsFloat# :: MutableByteArray# d -> Int# -> Float# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read double; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Double# #) #

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsDouble# :: MutableByteArray# d -> Int# -> Double# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read 16-bit int; offset in bytes.

Warning: this can fail with an unchecked exception.

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

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsInt16# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read 32-bit int; offset in bytes.

Warning: this can fail with an unchecked exception.

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

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsInt32# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read 64-bit int; offset in bytes.

Warning: this can fail with an unchecked exception.

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

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsInt64# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read int; offset in bytes.

Warning: this can fail with an unchecked exception.

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

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsInt# :: MutableByteArray# d -> Int# -> Int# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read 16-bit word; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) #

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsWord16# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read 32-bit word; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) #

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsWord32# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read 64-bit word; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) #

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsWord64# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

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

Read word; offset in bytes.

Warning: this can fail with an unchecked exception.

readWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> State# d -> (# State# d, Word# #) #

Warning: this can fail with an unchecked exception.

writeWord8ArrayAsWord# :: MutableByteArray# d -> Int# -> Word# -> State# d -> State# d #

Warning: this can fail with an unchecked exception.

atomicModifyMutVar_# :: MutVar# d a -> (a -> a) -> State# d -> (# State# d, a, a #) #

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# d a -> (a -> c) -> State# d -> (# State# d, a, c #) #

Modify the contents of a MutVar#, returning the previous contents and the result of applying the given function to the previous contents. Note that this isn't strictly speaking the correct type for this function; it should really be MutVar# s a -> (a -> (a,b)) -> State# s -> (# State# s, a, (a, b) #), but we don't know about pairs here.

Warning: this can fail with an unchecked exception.

GHC-8.4

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.

Warning: this can fail with an unchecked exception.

GHC-8.2

newtype CBool #

Haskell type representing the C bool type. (The concrete types of Foreign.C.Types are platform-specific.)

Since: base-4.10.0.0

Constructors

CBool Word8 

Instances

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

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