{- This is a generated file (generated by genprimopcode). It is not code to actually be used. Its only purpose is to be consumed by haddock. -} ----------------------------------------------------------------------------- -- | -- Module : GHC.Prim -- -- Maintainer : ghc-devs@haskell.org -- Stability : internal -- Portability : non-portable (GHC extensions) -- -- GHC's primitive types and operations. -- Use GHC.Exts from the base package instead of importing this -- module directly. -- ----------------------------------------------------------------------------- {-# LANGUAGE Unsafe #-} {-# LANGUAGE MagicHash #-} {-# LANGUAGE MultiParamTypeClasses #-} {-# LANGUAGE NoImplicitPrelude #-} {-# LANGUAGE UnboxedTuples #-} {-# LANGUAGE NegativeLiterals #-} {-# OPTIONS_GHC -fno-warn-redundant-constraints #-} module GHC.Prim ( -- * The word size story. -- |Haskell98 specifies that signed integers (type @Int@) -- must contain at least 30 bits. GHC always implements @Int@ using the primitive type @Int\#@, whose size equals -- the @MachDeps.h@ constant @WORD\_SIZE\_IN\_BITS@. -- This is normally set based on the @config.h@ parameter -- @SIZEOF\_HSWORD@, i.e., 32 bits on 32-bit machines, 64 -- bits on 64-bit machines. However, it can also be explicitly -- set to a smaller number than 64, e.g., 62 bits, to allow the -- possibility of using tag bits. Currently GHC itself has only -- 32-bit and 64-bit variants, but 61, 62, or 63-bit code can be -- exported as an external core file for use in other back ends. -- 30 and 31-bit code is no longer supported. -- -- GHC also implements a primitive unsigned integer type @Word\#@ which always has the same number of bits as @Int\#@. -- -- In addition, GHC supports families of explicit-sized integers -- and words at 8, 16, 32, and 64 bits, with the usual -- arithmetic operations, comparisons, and a range of -- conversions. The 8-bit and 16-bit sizes are always -- represented as @Int\#@ and @Word\#@, and the -- operations implemented in terms of the primops on these -- types, with suitable range restrictions on the results (using -- the @narrow$n$Int\#@ and @narrow$n$Word\#@ families -- of primops. The 32-bit sizes are represented using @Int\#@ and @Word\#@ when @WORD\_SIZE\_IN\_BITS@ -- $\geq$ 32; otherwise, these are represented using distinct -- primitive types @Int32\#@ and @Word32\#@. These (when -- needed) have a complete set of corresponding operations; -- however, nearly all of these are implemented as external C -- functions rather than as primops. Exactly the same story -- applies to the 64-bit sizes. All of these details are hidden -- under the @PrelInt@ and @PrelWord@ modules, which use -- @\#if@-defs to invoke the appropriate types and -- operators. -- -- Word size also matters for the families of primops for -- indexing\/reading\/writing fixed-size quantities at offsets -- from an array base, address, or foreign pointer. Here, a -- slightly different approach is taken. The names of these -- primops are fixed, but their /types/ vary according to -- the value of @WORD\_SIZE\_IN\_BITS@. For example, if word -- size is at least 32 bits then an operator like -- @indexInt32Array\#@ has type @ByteArray\# -> Int\# -> Int\#@; otherwise it has type @ByteArray\# -> Int\# -> Int32\#@. This approach confines the necessary @\#if@-defs to this file; no conditional compilation is needed -- in the files that expose these primops. -- -- Finally, there are strongly deprecated primops for coercing -- between @Addr\#@, the primitive type of machine -- addresses, and @Int\#@. These are pretty bogus anyway, -- but will work on existing 32-bit and 64-bit GHC targets; they -- are completely bogus when tag bits are used in @Int\#@, -- so are not available in this case. -- * Char# -- |Operations on 31-bit characters. Char#, gtChar#, geChar#, eqChar#, neChar#, ltChar#, leChar#, ord#, -- * Int# -- |Operations on native-size integers (32+ bits). Int#, (+#), (-#), (*#), mulIntMayOflo#, quotInt#, remInt#, quotRemInt#, andI#, orI#, xorI#, notI#, negateInt#, addIntC#, subIntC#, (>#), (>=#), (==#), (/=#), (<#), (<=#), chr#, int2Word#, int2Float#, int2Double#, word2Float#, word2Double#, uncheckedIShiftL#, uncheckedIShiftRA#, uncheckedIShiftRL#, -- * Int8# -- |Operations on 8-bit integers. Int8#, extendInt8#, narrowInt8#, negateInt8#, plusInt8#, subInt8#, timesInt8#, quotInt8#, remInt8#, quotRemInt8#, eqInt8#, geInt8#, gtInt8#, leInt8#, ltInt8#, neInt8#, -- * Word8# -- |Operations on 8-bit unsigned integers. Word8#, extendWord8#, narrowWord8#, notWord8#, plusWord8#, subWord8#, timesWord8#, quotWord8#, remWord8#, quotRemWord8#, eqWord8#, geWord8#, gtWord8#, leWord8#, ltWord8#, neWord8#, -- * Int16# -- |Operations on 16-bit integers. Int16#, extendInt16#, narrowInt16#, negateInt16#, plusInt16#, subInt16#, timesInt16#, quotInt16#, remInt16#, quotRemInt16#, eqInt16#, geInt16#, gtInt16#, leInt16#, ltInt16#, neInt16#, -- * Word16# -- |Operations on 16-bit unsigned integers. Word16#, extendWord16#, narrowWord16#, notWord16#, plusWord16#, subWord16#, timesWord16#, quotWord16#, remWord16#, quotRemWord16#, eqWord16#, geWord16#, gtWord16#, leWord16#, ltWord16#, neWord16#, -- * Word# -- |Operations on native-sized unsigned words (32+ bits). Word#, plusWord#, addWordC#, subWordC#, plusWord2#, minusWord#, timesWord#, timesWord2#, quotWord#, remWord#, quotRemWord#, quotRemWord2#, and#, or#, xor#, not#, uncheckedShiftL#, uncheckedShiftRL#, word2Int#, gtWord#, geWord#, eqWord#, neWord#, ltWord#, leWord#, popCnt8#, popCnt16#, popCnt32#, popCnt64#, popCnt#, pdep8#, pdep16#, pdep32#, pdep64#, pdep#, pext8#, pext16#, pext32#, pext64#, pext#, clz8#, clz16#, clz32#, clz64#, clz#, ctz8#, ctz16#, ctz32#, ctz64#, ctz#, byteSwap16#, byteSwap32#, byteSwap64#, byteSwap#, bitReverse8#, bitReverse16#, bitReverse32#, bitReverse64#, bitReverse#, -- * Narrowings -- |Explicit narrowing of native-sized ints or words. narrow8Int#, narrow16Int#, narrow32Int#, narrow8Word#, narrow16Word#, narrow32Word#, -- * Double# -- |Operations on double-precision (64 bit) floating-point numbers. Double#, (>##), (>=##), (==##), (/=##), (<##), (<=##), (+##), (-##), (*##), (/##), negateDouble#, fabsDouble#, double2Int#, double2Float#, expDouble#, expm1Double#, logDouble#, log1pDouble#, sqrtDouble#, sinDouble#, cosDouble#, tanDouble#, asinDouble#, acosDouble#, atanDouble#, sinhDouble#, coshDouble#, tanhDouble#, asinhDouble#, acoshDouble#, atanhDouble#, (**##), decodeDouble_2Int#, decodeDouble_Int64#, -- * Float# -- |Operations on single-precision (32-bit) floating-point numbers. Float#, gtFloat#, geFloat#, eqFloat#, neFloat#, ltFloat#, leFloat#, plusFloat#, minusFloat#, timesFloat#, divideFloat#, negateFloat#, fabsFloat#, float2Int#, expFloat#, expm1Float#, logFloat#, log1pFloat#, sqrtFloat#, sinFloat#, cosFloat#, tanFloat#, asinFloat#, acosFloat#, atanFloat#, sinhFloat#, coshFloat#, tanhFloat#, asinhFloat#, acoshFloat#, atanhFloat#, powerFloat#, float2Double#, decodeFloat_Int#, -- * Arrays -- |Operations on @Array\#@. Array#, MutableArray#, newArray#, sameMutableArray#, readArray#, writeArray#, sizeofArray#, sizeofMutableArray#, indexArray#, unsafeFreezeArray#, unsafeThawArray#, copyArray#, copyMutableArray#, cloneArray#, cloneMutableArray#, freezeArray#, thawArray#, casArray#, -- * Small Arrays -- |Operations on @SmallArray\#@. A @SmallArray\#@ works -- just like an @Array\#@, but with different space use and -- performance characteristics (that are often useful with small -- arrays). The @SmallArray\#@ and @SmallMutableArray#@ -- lack a \`card table\'. The purpose of a card table is to avoid -- having to scan every element of the array on each GC by -- keeping track of which elements have changed since the last GC -- and only scanning those that have changed. So the consequence -- of there being no card table is that the representation is -- somewhat smaller and the writes are somewhat faster (because -- the card table does not need to be updated). The disadvantage -- of course is that for a @SmallMutableArray#@ the whole -- array has to be scanned on each GC. Thus it is best suited for -- use cases where the mutable array is not long lived, e.g. -- where a mutable array is initialised quickly and then frozen -- to become an immutable @SmallArray\#@. -- SmallArray#, SmallMutableArray#, newSmallArray#, sameSmallMutableArray#, shrinkSmallMutableArray#, readSmallArray#, writeSmallArray#, sizeofSmallArray#, sizeofSmallMutableArray#, getSizeofSmallMutableArray#, indexSmallArray#, unsafeFreezeSmallArray#, unsafeThawSmallArray#, copySmallArray#, copySmallMutableArray#, cloneSmallArray#, cloneSmallMutableArray#, freezeSmallArray#, thawSmallArray#, casSmallArray#, -- * Byte Arrays -- |Operations on @ByteArray\#@. A @ByteArray\#@ is a just a region of -- raw memory in the garbage-collected heap, which is not -- scanned for pointers. It carries its own size (in bytes). -- There are -- three sets of operations for accessing byte array contents: -- index for reading from immutable byte arrays, and read\/write -- for mutable byte arrays. Each set contains operations for a -- range of useful primitive data types. Each operation takes -- an offset measured in terms of the size of the primitive type -- being read or written. ByteArray#, MutableByteArray#, newByteArray#, newPinnedByteArray#, newAlignedPinnedByteArray#, isMutableByteArrayPinned#, isByteArrayPinned#, byteArrayContents#, sameMutableByteArray#, shrinkMutableByteArray#, resizeMutableByteArray#, unsafeFreezeByteArray#, sizeofByteArray#, sizeofMutableByteArray#, getSizeofMutableByteArray#, indexCharArray#, indexWideCharArray#, indexIntArray#, indexWordArray#, indexAddrArray#, indexFloatArray#, indexDoubleArray#, indexStablePtrArray#, indexInt8Array#, indexInt16Array#, indexInt32Array#, indexInt64Array#, indexWord8Array#, indexWord16Array#, indexWord32Array#, indexWord64Array#, indexWord8ArrayAsChar#, indexWord8ArrayAsWideChar#, indexWord8ArrayAsAddr#, indexWord8ArrayAsFloat#, indexWord8ArrayAsDouble#, indexWord8ArrayAsStablePtr#, indexWord8ArrayAsInt16#, indexWord8ArrayAsInt32#, indexWord8ArrayAsInt64#, indexWord8ArrayAsInt#, indexWord8ArrayAsWord16#, indexWord8ArrayAsWord32#, indexWord8ArrayAsWord64#, indexWord8ArrayAsWord#, readCharArray#, readWideCharArray#, readIntArray#, readWordArray#, readAddrArray#, readFloatArray#, readDoubleArray#, readStablePtrArray#, readInt8Array#, readInt16Array#, readInt32Array#, readInt64Array#, readWord8Array#, readWord16Array#, readWord32Array#, readWord64Array#, readWord8ArrayAsChar#, readWord8ArrayAsWideChar#, readWord8ArrayAsAddr#, readWord8ArrayAsFloat#, readWord8ArrayAsDouble#, readWord8ArrayAsStablePtr#, readWord8ArrayAsInt16#, readWord8ArrayAsInt32#, readWord8ArrayAsInt64#, readWord8ArrayAsInt#, readWord8ArrayAsWord16#, readWord8ArrayAsWord32#, readWord8ArrayAsWord64#, readWord8ArrayAsWord#, writeCharArray#, writeWideCharArray#, writeIntArray#, writeWordArray#, writeAddrArray#, writeFloatArray#, writeDoubleArray#, writeStablePtrArray#, writeInt8Array#, writeInt16Array#, writeInt32Array#, writeInt64Array#, writeWord8Array#, writeWord16Array#, writeWord32Array#, writeWord64Array#, writeWord8ArrayAsChar#, writeWord8ArrayAsWideChar#, writeWord8ArrayAsAddr#, writeWord8ArrayAsFloat#, writeWord8ArrayAsDouble#, writeWord8ArrayAsStablePtr#, writeWord8ArrayAsInt16#, writeWord8ArrayAsInt32#, writeWord8ArrayAsInt64#, writeWord8ArrayAsInt#, writeWord8ArrayAsWord16#, writeWord8ArrayAsWord32#, writeWord8ArrayAsWord64#, writeWord8ArrayAsWord#, compareByteArrays#, copyByteArray#, copyMutableByteArray#, copyByteArrayToAddr#, copyMutableByteArrayToAddr#, copyAddrToByteArray#, setByteArray#, atomicReadIntArray#, atomicWriteIntArray#, casIntArray#, fetchAddIntArray#, fetchSubIntArray#, fetchAndIntArray#, fetchNandIntArray#, fetchOrIntArray#, fetchXorIntArray#, -- * Arrays of arrays -- |Operations on @ArrayArray\#@. An @ArrayArray\#@ contains references to /unpointed/ -- arrays, such as @ByteArray\#s@. Hence, it is not parameterised by the element types, -- just like a @ByteArray\#@, but it needs to be scanned during GC, just like an @Array\#@. -- We represent an @ArrayArray\#@ exactly as a @Array\#@, but provide element-type-specific -- indexing, reading, and writing. ArrayArray#, MutableArrayArray#, newArrayArray#, sameMutableArrayArray#, unsafeFreezeArrayArray#, sizeofArrayArray#, sizeofMutableArrayArray#, indexByteArrayArray#, indexArrayArrayArray#, readByteArrayArray#, readMutableByteArrayArray#, readArrayArrayArray#, readMutableArrayArrayArray#, writeByteArrayArray#, writeMutableByteArrayArray#, writeArrayArrayArray#, writeMutableArrayArrayArray#, copyArrayArray#, copyMutableArrayArray#, -- * Addr# -- | Addr#, nullAddr#, plusAddr#, minusAddr#, remAddr#, addr2Int#, int2Addr#, gtAddr#, geAddr#, eqAddr#, neAddr#, ltAddr#, leAddr#, indexCharOffAddr#, indexWideCharOffAddr#, indexIntOffAddr#, indexWordOffAddr#, indexAddrOffAddr#, indexFloatOffAddr#, indexDoubleOffAddr#, indexStablePtrOffAddr#, indexInt8OffAddr#, indexInt16OffAddr#, indexInt32OffAddr#, indexInt64OffAddr#, indexWord8OffAddr#, indexWord16OffAddr#, indexWord32OffAddr#, indexWord64OffAddr#, readCharOffAddr#, readWideCharOffAddr#, readIntOffAddr#, readWordOffAddr#, readAddrOffAddr#, readFloatOffAddr#, readDoubleOffAddr#, readStablePtrOffAddr#, readInt8OffAddr#, readInt16OffAddr#, readInt32OffAddr#, readInt64OffAddr#, readWord8OffAddr#, readWord16OffAddr#, readWord32OffAddr#, readWord64OffAddr#, writeCharOffAddr#, writeWideCharOffAddr#, writeIntOffAddr#, writeWordOffAddr#, writeAddrOffAddr#, writeFloatOffAddr#, writeDoubleOffAddr#, writeStablePtrOffAddr#, writeInt8OffAddr#, writeInt16OffAddr#, writeInt32OffAddr#, writeInt64OffAddr#, writeWord8OffAddr#, writeWord16OffAddr#, writeWord32OffAddr#, writeWord64OffAddr#, -- * Mutable variables -- |Operations on MutVar\#s. MutVar#, newMutVar#, readMutVar#, writeMutVar#, sameMutVar#, atomicModifyMutVar2#, atomicModifyMutVar_#, casMutVar#, -- * Exceptions -- | catch#, raise#, raiseIO#, maskAsyncExceptions#, maskUninterruptible#, unmaskAsyncExceptions#, getMaskingState#, -- * STM-accessible Mutable Variables -- | TVar#, atomically#, retry#, catchRetry#, catchSTM#, newTVar#, readTVar#, readTVarIO#, writeTVar#, sameTVar#, -- * Synchronized Mutable Variables -- |Operations on @MVar\#@s. MVar#, newMVar#, takeMVar#, tryTakeMVar#, putMVar#, tryPutMVar#, readMVar#, tryReadMVar#, sameMVar#, isEmptyMVar#, -- * Delay\/wait operations -- | delay#, waitRead#, waitWrite#, -- * Concurrency primitives -- | State#, RealWorld, ThreadId#, fork#, forkOn#, killThread#, yield#, myThreadId#, labelThread#, isCurrentThreadBound#, noDuplicate#, threadStatus#, -- * Weak pointers -- | Weak#, mkWeak#, mkWeakNoFinalizer#, addCFinalizerToWeak#, deRefWeak#, finalizeWeak#, touch#, -- * Stable pointers and names -- | StablePtr#, StableName#, makeStablePtr#, deRefStablePtr#, eqStablePtr#, makeStableName#, eqStableName#, stableNameToInt#, -- * Compact normal form -- |Primitives for working with compact regions. The @ghc\-compact@ -- library and the @compact@ library demonstrate how to use these -- primitives. The documentation below draws a distinction between -- a CNF and a compact block. A CNF contains one or more compact -- blocks. The source file @rts\\/sm\\/CNF.c@ -- diagrams this relationship. When discussing a compact -- block, an additional distinction is drawn between capacity and -- utilized bytes. The capacity is the maximum number of bytes that -- the compact block can hold. The utilized bytes is the number of -- bytes that are actually used by the compact block. -- Compact#, compactNew#, compactResize#, compactContains#, compactContainsAny#, compactGetFirstBlock#, compactGetNextBlock#, compactAllocateBlock#, compactFixupPointers#, compactAdd#, compactAddWithSharing#, compactSize#, -- * Unsafe pointer equality -- | reallyUnsafePtrEquality#, -- * Parallelism -- | par#, spark#, seq#, getSpark#, numSparks#, -- * Tag to enum stuff -- |Convert back and forth between values of enumerated types -- and small integers. dataToTag#, tagToEnum#, -- * Bytecode operations -- |Support for manipulating bytecode objects used by the interpreter and -- linker. -- -- Bytecode objects are heap objects which represent top-level bindings and -- contain a list of instructions and data needed by these instructions. BCO#, addrToAny#, anyToAddr#, mkApUpd0#, newBCO#, unpackClosure#, closureSize#, getApStackVal#, -- * Misc -- |These aren\'t nearly as wired in as Etc... getCCSOf#, getCurrentCCS#, clearCCS#, -- * Etc -- |Miscellaneous built-ins Proxy#, proxy#, seq, unsafeCoerce#, traceEvent#, traceBinaryEvent#, traceMarker#, setThreadAllocationCounter#, -- * Safe coercions -- | coerce, -- * SIMD Vectors -- |Operations on SIMD vectors. Int8X16#, Int16X8#, Int32X4#, Int64X2#, Int8X32#, Int16X16#, Int32X8#, Int64X4#, Int8X64#, Int16X32#, Int32X16#, Int64X8#, Word8X16#, Word16X8#, Word32X4#, Word64X2#, Word8X32#, Word16X16#, Word32X8#, Word64X4#, Word8X64#, Word16X32#, Word32X16#, Word64X8#, FloatX4#, DoubleX2#, FloatX8#, DoubleX4#, FloatX16#, DoubleX8#, broadcastInt8X16#, broadcastInt16X8#, broadcastInt32X4#, broadcastInt64X2#, broadcastInt8X32#, broadcastInt16X16#, broadcastInt32X8#, broadcastInt64X4#, broadcastInt8X64#, broadcastInt16X32#, broadcastInt32X16#, broadcastInt64X8#, broadcastWord8X16#, broadcastWord16X8#, broadcastWord32X4#, broadcastWord64X2#, broadcastWord8X32#, broadcastWord16X16#, broadcastWord32X8#, broadcastWord64X4#, broadcastWord8X64#, broadcastWord16X32#, broadcastWord32X16#, broadcastWord64X8#, broadcastFloatX4#, broadcastDoubleX2#, broadcastFloatX8#, broadcastDoubleX4#, broadcastFloatX16#, broadcastDoubleX8#, packInt8X16#, packInt16X8#, packInt32X4#, packInt64X2#, packInt8X32#, packInt16X16#, packInt32X8#, packInt64X4#, packInt8X64#, packInt16X32#, packInt32X16#, packInt64X8#, packWord8X16#, packWord16X8#, packWord32X4#, packWord64X2#, packWord8X32#, packWord16X16#, packWord32X8#, packWord64X4#, packWord8X64#, packWord16X32#, packWord32X16#, packWord64X8#, packFloatX4#, packDoubleX2#, packFloatX8#, packDoubleX4#, packFloatX16#, packDoubleX8#, unpackInt8X16#, unpackInt16X8#, unpackInt32X4#, unpackInt64X2#, unpackInt8X32#, unpackInt16X16#, unpackInt32X8#, unpackInt64X4#, unpackInt8X64#, unpackInt16X32#, unpackInt32X16#, unpackInt64X8#, unpackWord8X16#, unpackWord16X8#, unpackWord32X4#, unpackWord64X2#, unpackWord8X32#, unpackWord16X16#, unpackWord32X8#, unpackWord64X4#, unpackWord8X64#, unpackWord16X32#, unpackWord32X16#, unpackWord64X8#, unpackFloatX4#, unpackDoubleX2#, unpackFloatX8#, unpackDoubleX4#, unpackFloatX16#, unpackDoubleX8#, insertInt8X16#, insertInt16X8#, insertInt32X4#, insertInt64X2#, insertInt8X32#, insertInt16X16#, insertInt32X8#, insertInt64X4#, insertInt8X64#, insertInt16X32#, insertInt32X16#, insertInt64X8#, insertWord8X16#, insertWord16X8#, insertWord32X4#, insertWord64X2#, insertWord8X32#, insertWord16X16#, insertWord32X8#, insertWord64X4#, insertWord8X64#, insertWord16X32#, insertWord32X16#, insertWord64X8#, insertFloatX4#, insertDoubleX2#, insertFloatX8#, insertDoubleX4#, insertFloatX16#, insertDoubleX8#, plusInt8X16#, plusInt16X8#, plusInt32X4#, plusInt64X2#, plusInt8X32#, plusInt16X16#, plusInt32X8#, plusInt64X4#, plusInt8X64#, plusInt16X32#, plusInt32X16#, plusInt64X8#, plusWord8X16#, plusWord16X8#, plusWord32X4#, plusWord64X2#, plusWord8X32#, plusWord16X16#, plusWord32X8#, plusWord64X4#, plusWord8X64#, plusWord16X32#, plusWord32X16#, plusWord64X8#, plusFloatX4#, plusDoubleX2#, plusFloatX8#, plusDoubleX4#, plusFloatX16#, plusDoubleX8#, minusInt8X16#, minusInt16X8#, minusInt32X4#, minusInt64X2#, minusInt8X32#, minusInt16X16#, minusInt32X8#, minusInt64X4#, minusInt8X64#, minusInt16X32#, minusInt32X16#, minusInt64X8#, minusWord8X16#, minusWord16X8#, minusWord32X4#, minusWord64X2#, minusWord8X32#, minusWord16X16#, minusWord32X8#, minusWord64X4#, minusWord8X64#, minusWord16X32#, minusWord32X16#, minusWord64X8#, minusFloatX4#, minusDoubleX2#, minusFloatX8#, minusDoubleX4#, minusFloatX16#, minusDoubleX8#, timesInt8X16#, timesInt16X8#, timesInt32X4#, timesInt64X2#, timesInt8X32#, timesInt16X16#, timesInt32X8#, timesInt64X4#, timesInt8X64#, timesInt16X32#, timesInt32X16#, timesInt64X8#, timesWord8X16#, timesWord16X8#, timesWord32X4#, timesWord64X2#, timesWord8X32#, timesWord16X16#, timesWord32X8#, timesWord64X4#, timesWord8X64#, timesWord16X32#, timesWord32X16#, timesWord64X8#, timesFloatX4#, timesDoubleX2#, timesFloatX8#, timesDoubleX4#, timesFloatX16#, timesDoubleX8#, divideFloatX4#, divideDoubleX2#, divideFloatX8#, divideDoubleX4#, divideFloatX16#, divideDoubleX8#, quotInt8X16#, quotInt16X8#, quotInt32X4#, quotInt64X2#, quotInt8X32#, quotInt16X16#, quotInt32X8#, quotInt64X4#, quotInt8X64#, quotInt16X32#, quotInt32X16#, quotInt64X8#, quotWord8X16#, quotWord16X8#, quotWord32X4#, quotWord64X2#, quotWord8X32#, quotWord16X16#, quotWord32X8#, quotWord64X4#, quotWord8X64#, quotWord16X32#, quotWord32X16#, quotWord64X8#, remInt8X16#, remInt16X8#, remInt32X4#, remInt64X2#, remInt8X32#, remInt16X16#, remInt32X8#, remInt64X4#, remInt8X64#, remInt16X32#, remInt32X16#, remInt64X8#, remWord8X16#, remWord16X8#, remWord32X4#, remWord64X2#, remWord8X32#, remWord16X16#, remWord32X8#, remWord64X4#, remWord8X64#, remWord16X32#, remWord32X16#, remWord64X8#, negateInt8X16#, negateInt16X8#, negateInt32X4#, negateInt64X2#, negateInt8X32#, negateInt16X16#, negateInt32X8#, negateInt64X4#, negateInt8X64#, negateInt16X32#, negateInt32X16#, negateInt64X8#, negateFloatX4#, negateDoubleX2#, negateFloatX8#, negateDoubleX4#, negateFloatX16#, negateDoubleX8#, indexInt8X16Array#, indexInt16X8Array#, indexInt32X4Array#, indexInt64X2Array#, indexInt8X32Array#, indexInt16X16Array#, indexInt32X8Array#, indexInt64X4Array#, indexInt8X64Array#, indexInt16X32Array#, indexInt32X16Array#, indexInt64X8Array#, indexWord8X16Array#, indexWord16X8Array#, indexWord32X4Array#, indexWord64X2Array#, indexWord8X32Array#, indexWord16X16Array#, indexWord32X8Array#, indexWord64X4Array#, indexWord8X64Array#, indexWord16X32Array#, indexWord32X16Array#, indexWord64X8Array#, indexFloatX4Array#, indexDoubleX2Array#, indexFloatX8Array#, indexDoubleX4Array#, indexFloatX16Array#, indexDoubleX8Array#, readInt8X16Array#, readInt16X8Array#, readInt32X4Array#, readInt64X2Array#, readInt8X32Array#, readInt16X16Array#, readInt32X8Array#, readInt64X4Array#, readInt8X64Array#, readInt16X32Array#, readInt32X16Array#, readInt64X8Array#, readWord8X16Array#, readWord16X8Array#, readWord32X4Array#, readWord64X2Array#, readWord8X32Array#, readWord16X16Array#, readWord32X8Array#, readWord64X4Array#, readWord8X64Array#, readWord16X32Array#, readWord32X16Array#, readWord64X8Array#, readFloatX4Array#, readDoubleX2Array#, readFloatX8Array#, readDoubleX4Array#, readFloatX16Array#, readDoubleX8Array#, writeInt8X16Array#, writeInt16X8Array#, writeInt32X4Array#, writeInt64X2Array#, writeInt8X32Array#, writeInt16X16Array#, writeInt32X8Array#, writeInt64X4Array#, writeInt8X64Array#, writeInt16X32Array#, writeInt32X16Array#, writeInt64X8Array#, writeWord8X16Array#, writeWord16X8Array#, writeWord32X4Array#, writeWord64X2Array#, writeWord8X32Array#, writeWord16X16Array#, writeWord32X8Array#, writeWord64X4Array#, writeWord8X64Array#, writeWord16X32Array#, writeWord32X16Array#, writeWord64X8Array#, writeFloatX4Array#, writeDoubleX2Array#, writeFloatX8Array#, writeDoubleX4Array#, writeFloatX16Array#, writeDoubleX8Array#, indexInt8X16OffAddr#, indexInt16X8OffAddr#, indexInt32X4OffAddr#, indexInt64X2OffAddr#, indexInt8X32OffAddr#, indexInt16X16OffAddr#, indexInt32X8OffAddr#, indexInt64X4OffAddr#, indexInt8X64OffAddr#, indexInt16X32OffAddr#, indexInt32X16OffAddr#, indexInt64X8OffAddr#, indexWord8X16OffAddr#, indexWord16X8OffAddr#, indexWord32X4OffAddr#, indexWord64X2OffAddr#, indexWord8X32OffAddr#, indexWord16X16OffAddr#, indexWord32X8OffAddr#, indexWord64X4OffAddr#, indexWord8X64OffAddr#, indexWord16X32OffAddr#, indexWord32X16OffAddr#, indexWord64X8OffAddr#, indexFloatX4OffAddr#, indexDoubleX2OffAddr#, indexFloatX8OffAddr#, indexDoubleX4OffAddr#, indexFloatX16OffAddr#, indexDoubleX8OffAddr#, readInt8X16OffAddr#, readInt16X8OffAddr#, readInt32X4OffAddr#, readInt64X2OffAddr#, readInt8X32OffAddr#, readInt16X16OffAddr#, readInt32X8OffAddr#, readInt64X4OffAddr#, readInt8X64OffAddr#, readInt16X32OffAddr#, readInt32X16OffAddr#, readInt64X8OffAddr#, readWord8X16OffAddr#, readWord16X8OffAddr#, readWord32X4OffAddr#, readWord64X2OffAddr#, readWord8X32OffAddr#, readWord16X16OffAddr#, readWord32X8OffAddr#, readWord64X4OffAddr#, readWord8X64OffAddr#, readWord16X32OffAddr#, readWord32X16OffAddr#, readWord64X8OffAddr#, readFloatX4OffAddr#, readDoubleX2OffAddr#, readFloatX8OffAddr#, readDoubleX4OffAddr#, readFloatX16OffAddr#, readDoubleX8OffAddr#, writeInt8X16OffAddr#, writeInt16X8OffAddr#, writeInt32X4OffAddr#, writeInt64X2OffAddr#, writeInt8X32OffAddr#, writeInt16X16OffAddr#, writeInt32X8OffAddr#, writeInt64X4OffAddr#, writeInt8X64OffAddr#, writeInt16X32OffAddr#, writeInt32X16OffAddr#, writeInt64X8OffAddr#, writeWord8X16OffAddr#, writeWord16X8OffAddr#, writeWord32X4OffAddr#, writeWord64X2OffAddr#, writeWord8X32OffAddr#, writeWord16X16OffAddr#, writeWord32X8OffAddr#, writeWord64X4OffAddr#, writeWord8X64OffAddr#, writeWord16X32OffAddr#, writeWord32X16OffAddr#, writeWord64X8OffAddr#, writeFloatX4OffAddr#, writeDoubleX2OffAddr#, writeFloatX8OffAddr#, writeDoubleX4OffAddr#, writeFloatX16OffAddr#, writeDoubleX8OffAddr#, indexInt8ArrayAsInt8X16#, indexInt16ArrayAsInt16X8#, indexInt32ArrayAsInt32X4#, indexInt64ArrayAsInt64X2#, indexInt8ArrayAsInt8X32#, indexInt16ArrayAsInt16X16#, indexInt32ArrayAsInt32X8#, indexInt64ArrayAsInt64X4#, indexInt8ArrayAsInt8X64#, indexInt16ArrayAsInt16X32#, indexInt32ArrayAsInt32X16#, indexInt64ArrayAsInt64X8#, indexWord8ArrayAsWord8X16#, indexWord16ArrayAsWord16X8#, indexWord32ArrayAsWord32X4#, indexWord64ArrayAsWord64X2#, indexWord8ArrayAsWord8X32#, indexWord16ArrayAsWord16X16#, indexWord32ArrayAsWord32X8#, indexWord64ArrayAsWord64X4#, indexWord8ArrayAsWord8X64#, indexWord16ArrayAsWord16X32#, indexWord32ArrayAsWord32X16#, indexWord64ArrayAsWord64X8#, indexFloatArrayAsFloatX4#, indexDoubleArrayAsDoubleX2#, indexFloatArrayAsFloatX8#, indexDoubleArrayAsDoubleX4#, indexFloatArrayAsFloatX16#, indexDoubleArrayAsDoubleX8#, readInt8ArrayAsInt8X16#, readInt16ArrayAsInt16X8#, readInt32ArrayAsInt32X4#, readInt64ArrayAsInt64X2#, readInt8ArrayAsInt8X32#, readInt16ArrayAsInt16X16#, readInt32ArrayAsInt32X8#, readInt64ArrayAsInt64X4#, readInt8ArrayAsInt8X64#, readInt16ArrayAsInt16X32#, readInt32ArrayAsInt32X16#, readInt64ArrayAsInt64X8#, readWord8ArrayAsWord8X16#, readWord16ArrayAsWord16X8#, readWord32ArrayAsWord32X4#, readWord64ArrayAsWord64X2#, readWord8ArrayAsWord8X32#, readWord16ArrayAsWord16X16#, readWord32ArrayAsWord32X8#, readWord64ArrayAsWord64X4#, readWord8ArrayAsWord8X64#, readWord16ArrayAsWord16X32#, readWord32ArrayAsWord32X16#, readWord64ArrayAsWord64X8#, readFloatArrayAsFloatX4#, readDoubleArrayAsDoubleX2#, readFloatArrayAsFloatX8#, readDoubleArrayAsDoubleX4#, readFloatArrayAsFloatX16#, readDoubleArrayAsDoubleX8#, writeInt8ArrayAsInt8X16#, writeInt16ArrayAsInt16X8#, writeInt32ArrayAsInt32X4#, writeInt64ArrayAsInt64X2#, writeInt8ArrayAsInt8X32#, writeInt16ArrayAsInt16X16#, writeInt32ArrayAsInt32X8#, writeInt64ArrayAsInt64X4#, writeInt8ArrayAsInt8X64#, writeInt16ArrayAsInt16X32#, writeInt32ArrayAsInt32X16#, writeInt64ArrayAsInt64X8#, writeWord8ArrayAsWord8X16#, writeWord16ArrayAsWord16X8#, writeWord32ArrayAsWord32X4#, writeWord64ArrayAsWord64X2#, writeWord8ArrayAsWord8X32#, writeWord16ArrayAsWord16X16#, writeWord32ArrayAsWord32X8#, writeWord64ArrayAsWord64X4#, writeWord8ArrayAsWord8X64#, writeWord16ArrayAsWord16X32#, writeWord32ArrayAsWord32X16#, writeWord64ArrayAsWord64X8#, writeFloatArrayAsFloatX4#, writeDoubleArrayAsDoubleX2#, writeFloatArrayAsFloatX8#, writeDoubleArrayAsDoubleX4#, writeFloatArrayAsFloatX16#, writeDoubleArrayAsDoubleX8#, indexInt8OffAddrAsInt8X16#, indexInt16OffAddrAsInt16X8#, indexInt32OffAddrAsInt32X4#, indexInt64OffAddrAsInt64X2#, indexInt8OffAddrAsInt8X32#, indexInt16OffAddrAsInt16X16#, indexInt32OffAddrAsInt32X8#, indexInt64OffAddrAsInt64X4#, indexInt8OffAddrAsInt8X64#, indexInt16OffAddrAsInt16X32#, indexInt32OffAddrAsInt32X16#, indexInt64OffAddrAsInt64X8#, indexWord8OffAddrAsWord8X16#, indexWord16OffAddrAsWord16X8#, indexWord32OffAddrAsWord32X4#, indexWord64OffAddrAsWord64X2#, indexWord8OffAddrAsWord8X32#, indexWord16OffAddrAsWord16X16#, indexWord32OffAddrAsWord32X8#, indexWord64OffAddrAsWord64X4#, indexWord8OffAddrAsWord8X64#, indexWord16OffAddrAsWord16X32#, indexWord32OffAddrAsWord32X16#, indexWord64OffAddrAsWord64X8#, indexFloatOffAddrAsFloatX4#, indexDoubleOffAddrAsDoubleX2#, indexFloatOffAddrAsFloatX8#, indexDoubleOffAddrAsDoubleX4#, indexFloatOffAddrAsFloatX16#, indexDoubleOffAddrAsDoubleX8#, readInt8OffAddrAsInt8X16#, readInt16OffAddrAsInt16X8#, readInt32OffAddrAsInt32X4#, readInt64OffAddrAsInt64X2#, readInt8OffAddrAsInt8X32#, readInt16OffAddrAsInt16X16#, readInt32OffAddrAsInt32X8#, readInt64OffAddrAsInt64X4#, readInt8OffAddrAsInt8X64#, readInt16OffAddrAsInt16X32#, readInt32OffAddrAsInt32X16#, readInt64OffAddrAsInt64X8#, readWord8OffAddrAsWord8X16#, readWord16OffAddrAsWord16X8#, readWord32OffAddrAsWord32X4#, readWord64OffAddrAsWord64X2#, readWord8OffAddrAsWord8X32#, readWord16OffAddrAsWord16X16#, readWord32OffAddrAsWord32X8#, readWord64OffAddrAsWord64X4#, readWord8OffAddrAsWord8X64#, readWord16OffAddrAsWord16X32#, readWord32OffAddrAsWord32X16#, readWord64OffAddrAsWord64X8#, readFloatOffAddrAsFloatX4#, readDoubleOffAddrAsDoubleX2#, readFloatOffAddrAsFloatX8#, readDoubleOffAddrAsDoubleX4#, readFloatOffAddrAsFloatX16#, readDoubleOffAddrAsDoubleX8#, writeInt8OffAddrAsInt8X16#, writeInt16OffAddrAsInt16X8#, writeInt32OffAddrAsInt32X4#, writeInt64OffAddrAsInt64X2#, writeInt8OffAddrAsInt8X32#, writeInt16OffAddrAsInt16X16#, writeInt32OffAddrAsInt32X8#, writeInt64OffAddrAsInt64X4#, writeInt8OffAddrAsInt8X64#, writeInt16OffAddrAsInt16X32#, writeInt32OffAddrAsInt32X16#, writeInt64OffAddrAsInt64X8#, writeWord8OffAddrAsWord8X16#, writeWord16OffAddrAsWord16X8#, writeWord32OffAddrAsWord32X4#, writeWord64OffAddrAsWord64X2#, writeWord8OffAddrAsWord8X32#, writeWord16OffAddrAsWord16X16#, writeWord32OffAddrAsWord32X8#, writeWord64OffAddrAsWord64X4#, writeWord8OffAddrAsWord8X64#, writeWord16OffAddrAsWord16X32#, writeWord32OffAddrAsWord32X16#, writeWord64OffAddrAsWord64X8#, writeFloatOffAddrAsFloatX4#, writeDoubleOffAddrAsDoubleX2#, writeFloatOffAddrAsFloatX8#, writeDoubleOffAddrAsDoubleX4#, writeFloatOffAddrAsFloatX16#, writeDoubleOffAddrAsDoubleX8#, -- * Prefetch -- |Prefetch operations: Note how every prefetch operation has a name -- with the pattern prefetch*N#, where N is either 0,1,2, or 3. -- -- This suffix number, N, is the \"locality level\" of the prefetch, following the -- convention in GCC and other compilers. -- Higher locality numbers correspond to the memory being loaded in more -- levels of the cpu cache, and being retained after initial use. The naming -- convention follows the naming convention of the prefetch intrinsic found -- in the GCC and Clang C compilers. -- -- On the LLVM backend, prefetch*N# uses the LLVM prefetch intrinsic -- with locality level N. The code generated by LLVM is target architecture -- dependent, but should agree with the GHC NCG on x86 systems. -- -- On the Sparc and PPC native backends, prefetch*N is a No-Op. -- -- On the x86 NCG, N=0 will generate prefetchNTA, -- N=1 generates prefetcht2, N=2 generates prefetcht1, and -- N=3 generates prefetcht0. -- -- For streaming workloads, the prefetch*0 operations are recommended. -- For workloads which do many reads or writes to a memory location in a short period of time, -- prefetch*3 operations are recommended. -- -- For further reading about prefetch and associated systems performance optimization, -- the instruction set and optimization manuals by Intel and other CPU vendors are -- excellent starting place. -- -- -- The \"Intel 64 and IA-32 Architectures Optimization Reference Manual\" is -- especially a helpful read, even if your software is meant for other CPU -- architectures or vendor hardware. The manual can be found at -- http:\/\/www.intel.com\/content\/www\/us\/en\/architecture-and-technology\/64-ia-32-architectures-optimization-manual.html . -- -- The @prefetch*@ family of operations has the order of operations -- determined by passing around the @State#@ token. -- -- To get a \"pure\" version of these operations, use @inlinePerformIO@ which is quite safe in this context. -- -- It is important to note that while the prefetch operations will never change the -- answer to a pure computation, They CAN change the memory locations resident -- in a CPU cache and that may change the performance and timing characteristics -- of an application. The prefetch operations are marked has_side_effects=True -- to reflect that these operations have side effects with respect to the runtime -- performance characteristics of the resulting code. Additionally, if the prefetchValue -- operations did not have this attribute, GHC does a float out transformation that -- results in a let\/app violation, at least with the current design. -- prefetchByteArray3#, prefetchMutableByteArray3#, prefetchAddr3#, prefetchValue3#, prefetchByteArray2#, prefetchMutableByteArray2#, prefetchAddr2#, prefetchValue2#, prefetchByteArray1#, prefetchMutableByteArray1#, prefetchAddr1#, prefetchValue1#, prefetchByteArray0#, prefetchMutableByteArray0#, prefetchAddr0#, prefetchValue0#, ) where {- has_side_effects = False out_of_line = False can_fail = False commutable = False code_size = { primOpCodeSizeDefault } strictness = { \ arity -> mkClosedStrictSig (replicate arity topDmd) topRes } fixity = Nothing llvm_only = False deprecated_msg = { } -} import GHC.Types (Coercible) default () -- |The builtin function type, written in infix form as @a -> b@ and -- in prefix form as @(->) a b@. Values of this type are functions -- taking inputs of type @a@ and producing outputs of type @b@. -- -- Note that @a -> b@ permits levity-polymorphism in both @a@ and -- @b@, so that types like @Int\# -> Int\#@ can still be well-kinded. -- infixr -1 -> data (->) a b data Char# gtChar# :: Char# -> Char# -> Int# gtChar# = gtChar# geChar# :: Char# -> Char# -> Int# geChar# = geChar# eqChar# :: Char# -> Char# -> Int# eqChar# = eqChar# neChar# :: Char# -> Char# -> Int# neChar# = neChar# ltChar# :: Char# -> Char# -> Int# ltChar# = ltChar# leChar# :: Char# -> Char# -> Int# leChar# = leChar# ord# :: Char# -> Int# ord# = ord# data Int# infixl 6 +# (+#) :: Int# -> Int# -> Int# (+#) = (+#) infixl 6 -# (-#) :: Int# -> Int# -> Int# (-#) = (-#) -- |Low word of signed integer multiply. infixl 7 *# (*#) :: Int# -> Int# -> Int# (*#) = (*#) -- |Return non-zero if there is any possibility that the upper word of a -- signed integer multiply might contain useful information. Return -- zero only if you are completely sure that no overflow can occur. -- On a 32-bit platform, the recommended implementation is to do a -- 32 x 32 -> 64 signed multiply, and subtract result[63:32] from -- (result[31] >>signed 31). If this is zero, meaning that the -- upper word is merely a sign extension of the lower one, no -- overflow can occur. -- -- On a 64-bit platform it is not always possible to -- acquire the top 64 bits of the result. Therefore, a recommended -- implementation is to take the absolute value of both operands, and -- return 0 iff bits[63:31] of them are zero, since that means that their -- magnitudes fit within 31 bits, so the magnitude of the product must fit -- into 62 bits. -- -- If in doubt, return non-zero, but do make an effort to create the -- correct answer for small args, since otherwise the performance of -- @(*) :: Integer -> Integer -> Integer@ will be poor. -- mulIntMayOflo# :: Int# -> Int# -> Int# mulIntMayOflo# = mulIntMayOflo# -- |Rounds towards zero. The behavior is undefined if the second argument is -- zero. -- -- -- __/Warning:/__ this can fail with an unchecked exception. quotInt# :: Int# -> Int# -> Int# quotInt# = quotInt# -- |Satisfies @(quotInt\# x y) *\# y +\# (remInt\# x y) == x@. The -- behavior is undefined if the second argument is zero. -- -- -- __/Warning:/__ this can fail with an unchecked exception. remInt# :: Int# -> Int# -> Int# remInt# = remInt# -- |Rounds towards zero. -- -- __/Warning:/__ this can fail with an unchecked exception. quotRemInt# :: Int# -> Int# -> (# Int#,Int# #) quotRemInt# = quotRemInt# -- |Bitwise \"and\". andI# :: Int# -> Int# -> Int# andI# = andI# -- |Bitwise \"or\". orI# :: Int# -> Int# -> Int# orI# = orI# -- |Bitwise \"xor\". xorI# :: Int# -> Int# -> Int# xorI# = xorI# -- |Bitwise \"not\", also known as the binary complement. notI# :: Int# -> Int# notI# = notI# -- |Unary negation. -- Since the negative @Int#@ range extends one further than the -- positive range, @negateInt#@ of the most negative number is an -- identity operation. This way, @negateInt#@ is always its own inverse. negateInt# :: Int# -> Int# negateInt# = negateInt# -- |Add signed integers reporting overflow. -- First member of result is the sum truncated to an @Int#@; -- second member is zero if the true sum fits in an @Int#@, -- nonzero if overflow occurred (the sum is either too large -- or too small to fit in an @Int#@). addIntC# :: Int# -> Int# -> (# Int#,Int# #) addIntC# = addIntC# -- |Subtract signed integers reporting overflow. -- First member of result is the difference truncated to an @Int#@; -- second member is zero if the true difference fits in an @Int#@, -- nonzero if overflow occurred (the difference is either too large -- or too small to fit in an @Int#@). subIntC# :: Int# -> Int# -> (# Int#,Int# #) subIntC# = subIntC# infix 4 ># (>#) :: Int# -> Int# -> Int# (>#) = (>#) infix 4 >=# (>=#) :: Int# -> Int# -> Int# (>=#) = (>=#) infix 4 ==# (==#) :: Int# -> Int# -> Int# (==#) = (==#) infix 4 /=# (/=#) :: Int# -> Int# -> Int# (/=#) = (/=#) infix 4 <# (<#) :: Int# -> Int# -> Int# (<#) = (<#) infix 4 <=# (<=#) :: Int# -> Int# -> Int# (<=#) = (<=#) chr# :: Int# -> Char# chr# = chr# int2Word# :: Int# -> Word# int2Word# = int2Word# int2Float# :: Int# -> Float# int2Float# = int2Float# int2Double# :: Int# -> Double# int2Double# = int2Double# word2Float# :: Word# -> Float# word2Float# = word2Float# word2Double# :: Word# -> Double# word2Double# = word2Double# -- |Shift left. Result undefined if shift amount is not -- in the range 0 to word size - 1 inclusive. uncheckedIShiftL# :: Int# -> Int# -> Int# uncheckedIShiftL# = uncheckedIShiftL# -- |Shift right arithmetic. Result undefined if shift amount is not -- in the range 0 to word size - 1 inclusive. uncheckedIShiftRA# :: Int# -> Int# -> Int# uncheckedIShiftRA# = uncheckedIShiftRA# -- |Shift right logical. Result undefined if shift amount is not -- in the range 0 to word size - 1 inclusive. uncheckedIShiftRL# :: Int# -> Int# -> Int# uncheckedIShiftRL# = uncheckedIShiftRL# data Int8# extendInt8# :: Int8# -> Int# extendInt8# = extendInt8# narrowInt8# :: Int# -> Int8# narrowInt8# = narrowInt8# negateInt8# :: Int8# -> Int8# negateInt8# = negateInt8# plusInt8# :: Int8# -> Int8# -> Int8# plusInt8# = plusInt8# subInt8# :: Int8# -> Int8# -> Int8# subInt8# = subInt8# timesInt8# :: Int8# -> Int8# -> Int8# timesInt8# = timesInt8# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. quotInt8# :: Int8# -> Int8# -> Int8# quotInt8# = quotInt8# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. remInt8# :: Int8# -> Int8# -> Int8# remInt8# = remInt8# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. quotRemInt8# :: Int8# -> Int8# -> (# Int8#,Int8# #) quotRemInt8# = quotRemInt8# eqInt8# :: Int8# -> Int8# -> Int# eqInt8# = eqInt8# geInt8# :: Int8# -> Int8# -> Int# geInt8# = geInt8# gtInt8# :: Int8# -> Int8# -> Int# gtInt8# = gtInt8# leInt8# :: Int8# -> Int8# -> Int# leInt8# = leInt8# ltInt8# :: Int8# -> Int8# -> Int# ltInt8# = ltInt8# neInt8# :: Int8# -> Int8# -> Int# neInt8# = neInt8# data Word8# extendWord8# :: Word8# -> Word# extendWord8# = extendWord8# narrowWord8# :: Word# -> Word8# narrowWord8# = narrowWord8# notWord8# :: Word8# -> Word8# notWord8# = notWord8# plusWord8# :: Word8# -> Word8# -> Word8# plusWord8# = plusWord8# subWord8# :: Word8# -> Word8# -> Word8# subWord8# = subWord8# timesWord8# :: Word8# -> Word8# -> Word8# timesWord8# = timesWord8# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. quotWord8# :: Word8# -> Word8# -> Word8# quotWord8# = quotWord8# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. remWord8# :: Word8# -> Word8# -> Word8# remWord8# = remWord8# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. quotRemWord8# :: Word8# -> Word8# -> (# Word8#,Word8# #) quotRemWord8# = quotRemWord8# eqWord8# :: Word8# -> Word8# -> Int# eqWord8# = eqWord8# geWord8# :: Word8# -> Word8# -> Int# geWord8# = geWord8# gtWord8# :: Word8# -> Word8# -> Int# gtWord8# = gtWord8# leWord8# :: Word8# -> Word8# -> Int# leWord8# = leWord8# ltWord8# :: Word8# -> Word8# -> Int# ltWord8# = ltWord8# neWord8# :: Word8# -> Word8# -> Int# neWord8# = neWord8# data Int16# extendInt16# :: Int16# -> Int# extendInt16# = extendInt16# narrowInt16# :: Int# -> Int16# narrowInt16# = narrowInt16# negateInt16# :: Int16# -> Int16# negateInt16# = negateInt16# plusInt16# :: Int16# -> Int16# -> Int16# plusInt16# = plusInt16# subInt16# :: Int16# -> Int16# -> Int16# subInt16# = subInt16# timesInt16# :: Int16# -> Int16# -> Int16# timesInt16# = timesInt16# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. quotInt16# :: Int16# -> Int16# -> Int16# quotInt16# = quotInt16# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. remInt16# :: Int16# -> Int16# -> Int16# remInt16# = remInt16# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. quotRemInt16# :: Int16# -> Int16# -> (# Int16#,Int16# #) quotRemInt16# = quotRemInt16# eqInt16# :: Int16# -> Int16# -> Int# eqInt16# = eqInt16# geInt16# :: Int16# -> Int16# -> Int# geInt16# = geInt16# gtInt16# :: Int16# -> Int16# -> Int# gtInt16# = gtInt16# leInt16# :: Int16# -> Int16# -> Int# leInt16# = leInt16# ltInt16# :: Int16# -> Int16# -> Int# ltInt16# = ltInt16# neInt16# :: Int16# -> Int16# -> Int# neInt16# = neInt16# data Word16# extendWord16# :: Word16# -> Word# extendWord16# = extendWord16# narrowWord16# :: Word# -> Word16# narrowWord16# = narrowWord16# notWord16# :: Word16# -> Word16# notWord16# = notWord16# plusWord16# :: Word16# -> Word16# -> Word16# plusWord16# = plusWord16# subWord16# :: Word16# -> Word16# -> Word16# subWord16# = subWord16# timesWord16# :: Word16# -> Word16# -> Word16# timesWord16# = timesWord16# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. quotWord16# :: Word16# -> Word16# -> Word16# quotWord16# = quotWord16# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. remWord16# :: Word16# -> Word16# -> Word16# remWord16# = remWord16# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. quotRemWord16# :: Word16# -> Word16# -> (# Word16#,Word16# #) quotRemWord16# = quotRemWord16# eqWord16# :: Word16# -> Word16# -> Int# eqWord16# = eqWord16# geWord16# :: Word16# -> Word16# -> Int# geWord16# = geWord16# gtWord16# :: Word16# -> Word16# -> Int# gtWord16# = gtWord16# leWord16# :: Word16# -> Word16# -> Int# leWord16# = leWord16# ltWord16# :: Word16# -> Word16# -> Int# ltWord16# = ltWord16# neWord16# :: Word16# -> Word16# -> Int# neWord16# = neWord16# data Word# plusWord# :: Word# -> Word# -> Word# plusWord# = plusWord# -- |Add unsigned integers reporting overflow. -- The first element of the pair is the result. The second element is -- the carry flag, which is nonzero on overflow. See also @plusWord2#@. addWordC# :: Word# -> Word# -> (# Word#,Int# #) addWordC# = addWordC# -- |Subtract unsigned integers reporting overflow. -- The first element of the pair is the result. The second element is -- the carry flag, which is nonzero on overflow. subWordC# :: Word# -> Word# -> (# Word#,Int# #) subWordC# = subWordC# -- |Add unsigned integers, with the high part (carry) in the first -- component of the returned pair and the low part in the second -- component of the pair. See also @addWordC#@. plusWord2# :: Word# -> Word# -> (# Word#,Word# #) plusWord2# = plusWord2# minusWord# :: Word# -> Word# -> Word# minusWord# = minusWord# timesWord# :: Word# -> Word# -> Word# timesWord# = timesWord# timesWord2# :: Word# -> Word# -> (# Word#,Word# #) timesWord2# = timesWord2# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. quotWord# :: Word# -> Word# -> Word# quotWord# = quotWord# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. remWord# :: Word# -> Word# -> Word# remWord# = remWord# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. quotRemWord# :: Word# -> Word# -> (# Word#,Word# #) quotRemWord# = quotRemWord# -- | Takes high word of dividend, then low word of dividend, then divisor. -- Requires that high word \< divisor. -- -- __/Warning:/__ this can fail with an unchecked exception. quotRemWord2# :: Word# -> Word# -> Word# -> (# Word#,Word# #) quotRemWord2# = quotRemWord2# and# :: Word# -> Word# -> Word# and# = and# or# :: Word# -> Word# -> Word# or# = or# xor# :: Word# -> Word# -> Word# xor# = xor# not# :: Word# -> Word# not# = not# -- |Shift left logical. Result undefined if shift amount is not -- in the range 0 to word size - 1 inclusive. uncheckedShiftL# :: Word# -> Int# -> Word# uncheckedShiftL# = uncheckedShiftL# -- |Shift right logical. Result undefined if shift amount is not -- in the range 0 to word size - 1 inclusive. uncheckedShiftRL# :: Word# -> Int# -> Word# uncheckedShiftRL# = uncheckedShiftRL# word2Int# :: Word# -> Int# word2Int# = word2Int# gtWord# :: Word# -> Word# -> Int# gtWord# = gtWord# geWord# :: Word# -> Word# -> Int# geWord# = geWord# eqWord# :: Word# -> Word# -> Int# eqWord# = eqWord# neWord# :: Word# -> Word# -> Int# neWord# = neWord# ltWord# :: Word# -> Word# -> Int# ltWord# = ltWord# leWord# :: Word# -> Word# -> Int# leWord# = leWord# -- |Count the number of set bits in the lower 8 bits of a word. popCnt8# :: Word# -> Word# popCnt8# = popCnt8# -- |Count the number of set bits in the lower 16 bits of a word. popCnt16# :: Word# -> Word# popCnt16# = popCnt16# -- |Count the number of set bits in the lower 32 bits of a word. popCnt32# :: Word# -> Word# popCnt32# = popCnt32# -- |Count the number of set bits in a 64-bit word. popCnt64# :: Word# -> Word# popCnt64# = popCnt64# -- |Count the number of set bits in a word. popCnt# :: Word# -> Word# popCnt# = popCnt# -- |Deposit bits to lower 8 bits of a word at locations specified by a mask. pdep8# :: Word# -> Word# -> Word# pdep8# = pdep8# -- |Deposit bits to lower 16 bits of a word at locations specified by a mask. pdep16# :: Word# -> Word# -> Word# pdep16# = pdep16# -- |Deposit bits to lower 32 bits of a word at locations specified by a mask. pdep32# :: Word# -> Word# -> Word# pdep32# = pdep32# -- |Deposit bits to a word at locations specified by a mask. pdep64# :: Word# -> Word# -> Word# pdep64# = pdep64# -- |Deposit bits to a word at locations specified by a mask. pdep# :: Word# -> Word# -> Word# pdep# = pdep# -- |Extract bits from lower 8 bits of a word at locations specified by a mask. pext8# :: Word# -> Word# -> Word# pext8# = pext8# -- |Extract bits from lower 16 bits of a word at locations specified by a mask. pext16# :: Word# -> Word# -> Word# pext16# = pext16# -- |Extract bits from lower 32 bits of a word at locations specified by a mask. pext32# :: Word# -> Word# -> Word# pext32# = pext32# -- |Extract bits from a word at locations specified by a mask. pext64# :: Word# -> Word# -> Word# pext64# = pext64# -- |Extract bits from a word at locations specified by a mask. pext# :: Word# -> Word# -> Word# pext# = pext# -- |Count leading zeros in the lower 8 bits of a word. clz8# :: Word# -> Word# clz8# = clz8# -- |Count leading zeros in the lower 16 bits of a word. clz16# :: Word# -> Word# clz16# = clz16# -- |Count leading zeros in the lower 32 bits of a word. clz32# :: Word# -> Word# clz32# = clz32# -- |Count leading zeros in a 64-bit word. clz64# :: Word# -> Word# clz64# = clz64# -- |Count leading zeros in a word. clz# :: Word# -> Word# clz# = clz# -- |Count trailing zeros in the lower 8 bits of a word. ctz8# :: Word# -> Word# ctz8# = ctz8# -- |Count trailing zeros in the lower 16 bits of a word. ctz16# :: Word# -> Word# ctz16# = ctz16# -- |Count trailing zeros in the lower 32 bits of a word. ctz32# :: Word# -> Word# ctz32# = ctz32# -- |Count trailing zeros in a 64-bit word. ctz64# :: Word# -> Word# ctz64# = ctz64# -- |Count trailing zeros in a word. ctz# :: Word# -> Word# ctz# = ctz# -- |Swap bytes in the lower 16 bits of a word. The higher bytes are undefined. byteSwap16# :: Word# -> Word# byteSwap16# = byteSwap16# -- |Swap bytes in the lower 32 bits of a word. The higher bytes are undefined. byteSwap32# :: Word# -> Word# byteSwap32# = byteSwap32# -- |Swap bytes in a 64 bits of a word. byteSwap64# :: Word# -> Word# byteSwap64# = byteSwap64# -- |Swap bytes in a word. byteSwap# :: Word# -> Word# byteSwap# = byteSwap# -- |Reverse the order of the bits in a 8-bit word. bitReverse8# :: Word# -> Word# bitReverse8# = bitReverse8# -- |Reverse the order of the bits in a 16-bit word. bitReverse16# :: Word# -> Word# bitReverse16# = bitReverse16# -- |Reverse the order of the bits in a 32-bit word. bitReverse32# :: Word# -> Word# bitReverse32# = bitReverse32# -- |Reverse the order of the bits in a 64-bit word. bitReverse64# :: Word# -> Word# bitReverse64# = bitReverse64# -- |Reverse the order of the bits in a word. bitReverse# :: Word# -> Word# bitReverse# = bitReverse# narrow8Int# :: Int# -> Int# narrow8Int# = narrow8Int# narrow16Int# :: Int# -> Int# narrow16Int# = narrow16Int# narrow32Int# :: Int# -> Int# narrow32Int# = narrow32Int# narrow8Word# :: Word# -> Word# narrow8Word# = narrow8Word# narrow16Word# :: Word# -> Word# narrow16Word# = narrow16Word# narrow32Word# :: Word# -> Word# narrow32Word# = narrow32Word# data Double# infix 4 >## (>##) :: Double# -> Double# -> Int# (>##) = (>##) infix 4 >=## (>=##) :: Double# -> Double# -> Int# (>=##) = (>=##) infix 4 ==## (==##) :: Double# -> Double# -> Int# (==##) = (==##) infix 4 /=## (/=##) :: Double# -> Double# -> Int# (/=##) = (/=##) infix 4 <## (<##) :: Double# -> Double# -> Int# (<##) = (<##) infix 4 <=## (<=##) :: Double# -> Double# -> Int# (<=##) = (<=##) infixl 6 +## (+##) :: Double# -> Double# -> Double# (+##) = (+##) infixl 6 -## (-##) :: Double# -> Double# -> Double# (-##) = (-##) infixl 7 *## (*##) :: Double# -> Double# -> Double# (*##) = (*##) -- | -- -- __/Warning:/__ this can fail with an unchecked exception. infixl 7 /## (/##) :: Double# -> Double# -> Double# (/##) = (/##) negateDouble# :: Double# -> Double# negateDouble# = negateDouble# fabsDouble# :: Double# -> Double# fabsDouble# = fabsDouble# -- |Truncates a @Double#@ value to the nearest @Int#@. -- Results are undefined if the truncation if truncation yields -- a value outside the range of @Int#@. double2Int# :: Double# -> Int# double2Int# = double2Int# double2Float# :: Double# -> Float# double2Float# = double2Float# expDouble# :: Double# -> Double# expDouble# = expDouble# expm1Double# :: Double# -> Double# expm1Double# = expm1Double# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. logDouble# :: Double# -> Double# logDouble# = logDouble# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. log1pDouble# :: Double# -> Double# log1pDouble# = log1pDouble# sqrtDouble# :: Double# -> Double# sqrtDouble# = sqrtDouble# sinDouble# :: Double# -> Double# sinDouble# = sinDouble# cosDouble# :: Double# -> Double# cosDouble# = cosDouble# tanDouble# :: Double# -> Double# tanDouble# = tanDouble# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. asinDouble# :: Double# -> Double# asinDouble# = asinDouble# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. acosDouble# :: Double# -> Double# acosDouble# = acosDouble# atanDouble# :: Double# -> Double# atanDouble# = atanDouble# sinhDouble# :: Double# -> Double# sinhDouble# = sinhDouble# coshDouble# :: Double# -> Double# coshDouble# = coshDouble# tanhDouble# :: Double# -> Double# tanhDouble# = tanhDouble# asinhDouble# :: Double# -> Double# asinhDouble# = asinhDouble# acoshDouble# :: Double# -> Double# acoshDouble# = acoshDouble# atanhDouble# :: Double# -> Double# atanhDouble# = atanhDouble# -- |Exponentiation. (**##) :: Double# -> Double# -> Double# (**##) = (**##) -- |Convert to integer. -- First component of the result is -1 or 1, indicating the sign of the -- mantissa. The next two are the high and low 32 bits of the mantissa -- respectively, and the last is the exponent. decodeDouble_2Int# :: Double# -> (# Int#,Word#,Word#,Int# #) decodeDouble_2Int# = decodeDouble_2Int# -- |Decode @Double\#@ into mantissa and base-2 exponent. decodeDouble_Int64# :: Double# -> (# Int#,Int# #) decodeDouble_Int64# = decodeDouble_Int64# data Float# gtFloat# :: Float# -> Float# -> Int# gtFloat# = gtFloat# geFloat# :: Float# -> Float# -> Int# geFloat# = geFloat# eqFloat# :: Float# -> Float# -> Int# eqFloat# = eqFloat# neFloat# :: Float# -> Float# -> Int# neFloat# = neFloat# ltFloat# :: Float# -> Float# -> Int# ltFloat# = ltFloat# leFloat# :: Float# -> Float# -> Int# leFloat# = leFloat# plusFloat# :: Float# -> Float# -> Float# plusFloat# = plusFloat# minusFloat# :: Float# -> Float# -> Float# minusFloat# = minusFloat# timesFloat# :: Float# -> Float# -> Float# timesFloat# = timesFloat# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. divideFloat# :: Float# -> Float# -> Float# divideFloat# = divideFloat# negateFloat# :: Float# -> Float# negateFloat# = negateFloat# fabsFloat# :: Float# -> Float# fabsFloat# = fabsFloat# -- |Truncates a @Float#@ value to the nearest @Int#@. -- Results are undefined if the truncation if truncation yields -- a value outside the range of @Int#@. float2Int# :: Float# -> Int# float2Int# = float2Int# expFloat# :: Float# -> Float# expFloat# = expFloat# expm1Float# :: Float# -> Float# expm1Float# = expm1Float# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. logFloat# :: Float# -> Float# logFloat# = logFloat# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. log1pFloat# :: Float# -> Float# log1pFloat# = log1pFloat# sqrtFloat# :: Float# -> Float# sqrtFloat# = sqrtFloat# sinFloat# :: Float# -> Float# sinFloat# = sinFloat# cosFloat# :: Float# -> Float# cosFloat# = cosFloat# tanFloat# :: Float# -> Float# tanFloat# = tanFloat# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. asinFloat# :: Float# -> Float# asinFloat# = asinFloat# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. acosFloat# :: Float# -> Float# acosFloat# = acosFloat# atanFloat# :: Float# -> Float# atanFloat# = atanFloat# sinhFloat# :: Float# -> Float# sinhFloat# = sinhFloat# coshFloat# :: Float# -> Float# coshFloat# = coshFloat# tanhFloat# :: Float# -> Float# tanhFloat# = tanhFloat# asinhFloat# :: Float# -> Float# asinhFloat# = asinhFloat# acoshFloat# :: Float# -> Float# acoshFloat# = acoshFloat# atanhFloat# :: Float# -> Float# atanhFloat# = atanhFloat# powerFloat# :: Float# -> Float# -> Float# powerFloat# = powerFloat# float2Double# :: Float# -> Double# float2Double# = float2Double# -- |Convert to integers. -- First @Int\#@ in result is the mantissa; second is the exponent. decodeFloat_Int# :: Float# -> (# Int#,Int# #) decodeFloat_Int# = decodeFloat_Int# data Array# a data MutableArray# s a -- |Create a new mutable array with the specified number of elements, -- in the specified state thread, -- with each element containing the specified initial value. newArray# :: Int# -> a -> State# s -> (# State# s,MutableArray# s a #) newArray# = newArray# sameMutableArray# :: MutableArray# s a -> MutableArray# s a -> Int# sameMutableArray# = sameMutableArray# -- |Read from specified index of mutable array. Result is not yet evaluated. -- -- __/Warning:/__ this can fail with an unchecked exception. readArray# :: MutableArray# s a -> Int# -> State# s -> (# State# s,a #) readArray# = readArray# -- |Write to specified index of mutable array. -- -- __/Warning:/__ this can fail with an unchecked exception. writeArray# :: MutableArray# s a -> Int# -> a -> State# s -> State# s writeArray# = writeArray# -- |Return the number of elements in the array. sizeofArray# :: Array# a -> Int# sizeofArray# = sizeofArray# -- |Return the number of elements in the array. sizeofMutableArray# :: MutableArray# s a -> Int# sizeofMutableArray# = sizeofMutableArray# -- |Read from the specified index of an immutable array. The result is packaged -- into an unboxed unary tuple; the result itself is not yet -- evaluated. Pattern matching on the tuple forces the indexing of the -- array to happen but does not evaluate the element itself. Evaluating -- the thunk prevents additional thunks from building up on the -- heap. Avoiding these thunks, in turn, reduces references to the -- argument array, allowing it to be garbage collected more promptly. -- -- __/Warning:/__ this can fail with an unchecked exception. indexArray# :: Array# a -> Int# -> (# a #) indexArray# = indexArray# -- |Make a mutable array immutable, without copying. unsafeFreezeArray# :: MutableArray# s a -> State# s -> (# State# s,Array# a #) unsafeFreezeArray# = unsafeFreezeArray# -- |Make an immutable array mutable, without copying. unsafeThawArray# :: Array# a -> State# s -> (# State# s,MutableArray# s a #) unsafeThawArray# = unsafeThawArray# -- |Given a source array, an offset into the source array, a -- destination array, an offset into the destination array, and a -- number of elements to copy, copy the elements from the source array -- to the destination array. Both arrays must fully contain the -- specified ranges, but this is not checked. The two arrays must not -- be the same array in different states, but this is not checked -- either. -- -- __/Warning:/__ this can fail with an unchecked exception. copyArray# :: Array# a -> Int# -> MutableArray# s a -> Int# -> Int# -> State# s -> State# s copyArray# = copyArray# -- |Given a source array, an offset into the source array, a -- destination array, an offset into the destination array, and a -- number of elements to copy, copy the elements from the source array -- to the destination array. Both arrays must fully contain the -- specified ranges, but this is not checked. In the case where -- the source and destination are the same array the source and -- destination regions may overlap. -- -- __/Warning:/__ this can fail with an unchecked exception. copyMutableArray# :: MutableArray# s a -> Int# -> MutableArray# s a -> Int# -> Int# -> State# s -> State# s copyMutableArray# = copyMutableArray# -- |Given a source array, an offset into the source array, and a number -- of elements to copy, create a new array with the elements from the -- source array. The provided array must fully contain the specified -- range, but this is not checked. -- -- __/Warning:/__ this can fail with an unchecked exception. cloneArray# :: Array# a -> Int# -> Int# -> Array# a cloneArray# = cloneArray# -- |Given a source array, an offset into the source array, and a number -- of elements to copy, create a new array with the elements from the -- source array. The provided array must fully contain the specified -- range, but this is not checked. -- -- __/Warning:/__ this can fail with an unchecked exception. cloneMutableArray# :: MutableArray# s a -> Int# -> Int# -> State# s -> (# State# s,MutableArray# s a #) cloneMutableArray# = cloneMutableArray# -- |Given a source array, an offset into the source array, and a number -- of elements to copy, create a new array with the elements from the -- source array. The provided array must fully contain the specified -- range, but this is not checked. -- -- __/Warning:/__ this can fail with an unchecked exception. freezeArray# :: MutableArray# s a -> Int# -> Int# -> State# s -> (# State# s,Array# a #) freezeArray# = freezeArray# -- |Given a source array, an offset into the source array, and a number -- of elements to copy, create a new array with the elements from the -- source array. The provided array must fully contain the specified -- range, but this is not checked. -- -- __/Warning:/__ this can fail with an unchecked exception. thawArray# :: Array# a -> Int# -> Int# -> State# s -> (# State# s,MutableArray# s a #) thawArray# = thawArray# -- |Given an array, an offset, the expected old value, and -- the new value, perform an atomic compare and swap (i.e. write the new -- value if the current value and the old value are the same pointer). -- Returns 0 if the swap succeeds and 1 if it fails. Additionally, returns -- the element at the offset after the operation completes. This means that -- on a success the new value is returned, and on a failure the actual old -- value (not the expected one) is returned. Implies a full memory barrier. -- The use of a pointer equality on a lifted value makes this function harder -- to use correctly than @casIntArray\#@. All of the difficulties -- of using @reallyUnsafePtrEquality\#@ correctly apply to -- @casArray\#@ as well. -- casArray# :: MutableArray# s a -> Int# -> a -> a -> State# s -> (# State# s,Int#,a #) casArray# = casArray# data SmallArray# a data SmallMutableArray# s a -- |Create a new mutable array with the specified number of elements, -- in the specified state thread, -- with each element containing the specified initial value. newSmallArray# :: Int# -> a -> State# s -> (# State# s,SmallMutableArray# s a #) newSmallArray# = newSmallArray# sameSmallMutableArray# :: SmallMutableArray# s a -> SmallMutableArray# s a -> Int# sameSmallMutableArray# = sameSmallMutableArray# -- |Shrink mutable array to new specified size, in -- the specified state thread. The new size argument must be less than or -- equal to the current size as reported by @sizeofSmallMutableArray\#@. shrinkSmallMutableArray# :: SmallMutableArray# s a -> Int# -> State# s -> State# s shrinkSmallMutableArray# = shrinkSmallMutableArray# -- |Read from specified index of mutable array. Result is not yet evaluated. -- -- __/Warning:/__ this can fail with an unchecked exception. readSmallArray# :: SmallMutableArray# s a -> Int# -> State# s -> (# State# s,a #) readSmallArray# = readSmallArray# -- |Write to specified index of mutable array. -- -- __/Warning:/__ this can fail with an unchecked exception. writeSmallArray# :: SmallMutableArray# s a -> Int# -> a -> State# s -> State# s writeSmallArray# = writeSmallArray# -- |Return the number of elements in the array. sizeofSmallArray# :: SmallArray# a -> Int# sizeofSmallArray# = sizeofSmallArray# -- |Return the number of elements in the array. Note that this is deprecated -- as it is unsafe in the presence of resize operations on the -- same byte array. {-# DEPRECATED sizeofSmallMutableArray# " Use 'getSizeofSmallMutableArray#' instead " #-} sizeofSmallMutableArray# :: SmallMutableArray# s a -> Int# sizeofSmallMutableArray# = sizeofSmallMutableArray# -- |Return the number of elements in the array. getSizeofSmallMutableArray# :: SmallMutableArray# s a -> State# s -> (# State# s,Int# #) getSizeofSmallMutableArray# = getSizeofSmallMutableArray# -- |Read from specified index of immutable array. Result is packaged into -- an unboxed singleton; the result itself is not yet evaluated. -- -- __/Warning:/__ this can fail with an unchecked exception. indexSmallArray# :: SmallArray# a -> Int# -> (# a #) indexSmallArray# = indexSmallArray# -- |Make a mutable array immutable, without copying. unsafeFreezeSmallArray# :: SmallMutableArray# s a -> State# s -> (# State# s,SmallArray# a #) unsafeFreezeSmallArray# = unsafeFreezeSmallArray# -- |Make an immutable array mutable, without copying. unsafeThawSmallArray# :: SmallArray# a -> State# s -> (# State# s,SmallMutableArray# s a #) unsafeThawSmallArray# = unsafeThawSmallArray# -- |Given a source array, an offset into the source array, a -- destination array, an offset into the destination array, and a -- number of elements to copy, copy the elements from the source array -- to the destination array. Both arrays must fully contain the -- specified ranges, but this is not checked. The two arrays must not -- be the same array in different states, but this is not checked -- either. -- -- __/Warning:/__ this can fail with an unchecked exception. copySmallArray# :: SmallArray# a -> Int# -> SmallMutableArray# s a -> Int# -> Int# -> State# s -> State# s copySmallArray# = copySmallArray# -- |Given a source array, an offset into the source array, a -- destination array, an offset into the destination array, and a -- number of elements to copy, copy the elements from the source array -- to the destination array. The source and destination arrays can -- refer to the same array. Both arrays must fully contain the -- specified ranges, but this is not checked. -- The regions are allowed to overlap, although this is only possible when the same -- array is provided as both the source and the destination. -- -- __/Warning:/__ this can fail with an unchecked exception. copySmallMutableArray# :: SmallMutableArray# s a -> Int# -> SmallMutableArray# s a -> Int# -> Int# -> State# s -> State# s copySmallMutableArray# = copySmallMutableArray# -- |Given a source array, an offset into the source array, and a number -- of elements to copy, create a new array with the elements from the -- source array. The provided array must fully contain the specified -- range, but this is not checked. -- -- __/Warning:/__ this can fail with an unchecked exception. cloneSmallArray# :: SmallArray# a -> Int# -> Int# -> SmallArray# a cloneSmallArray# = cloneSmallArray# -- |Given a source array, an offset into the source array, and a number -- of elements to copy, create a new array with the elements from the -- source array. The provided array must fully contain the specified -- range, but this is not checked. -- -- __/Warning:/__ this can fail with an unchecked exception. cloneSmallMutableArray# :: SmallMutableArray# s a -> Int# -> Int# -> State# s -> (# State# s,SmallMutableArray# s a #) cloneSmallMutableArray# = cloneSmallMutableArray# -- |Given a source array, an offset into the source array, and a number -- of elements to copy, create a new array with the elements from the -- source array. The provided array must fully contain the specified -- range, but this is not checked. -- -- __/Warning:/__ this can fail with an unchecked exception. freezeSmallArray# :: SmallMutableArray# s a -> Int# -> Int# -> State# s -> (# State# s,SmallArray# a #) freezeSmallArray# = freezeSmallArray# -- |Given a source array, an offset into the source array, and a number -- of elements to copy, create a new array with the elements from the -- source array. The provided array must fully contain the specified -- range, but this is not checked. -- -- __/Warning:/__ this can fail with an unchecked exception. thawSmallArray# :: SmallArray# a -> Int# -> Int# -> State# s -> (# State# s,SmallMutableArray# s a #) thawSmallArray# = thawSmallArray# -- |Unsafe, machine-level atomic compare and swap on an element within an array. -- See the documentation of @casArray\#@. casSmallArray# :: SmallMutableArray# s a -> Int# -> a -> a -> State# s -> (# State# s,Int#,a #) casSmallArray# = casSmallArray# data ByteArray# data MutableByteArray# s -- |Create a new mutable byte array of specified size (in bytes), in -- the specified state thread. newByteArray# :: Int# -> State# s -> (# State# s,MutableByteArray# s #) newByteArray# = newByteArray# -- |Create a mutable byte array that the GC guarantees not to move. newPinnedByteArray# :: Int# -> State# s -> (# State# s,MutableByteArray# s #) newPinnedByteArray# = newPinnedByteArray# -- |Create a mutable byte array, aligned by the specified amount, that the GC guarantees not to move. newAlignedPinnedByteArray# :: Int# -> Int# -> State# s -> (# State# s,MutableByteArray# s #) newAlignedPinnedByteArray# = newAlignedPinnedByteArray# -- |Determine whether a @MutableByteArray\#@ is guaranteed not to move -- during GC. isMutableByteArrayPinned# :: MutableByteArray# s -> Int# isMutableByteArrayPinned# = isMutableByteArrayPinned# -- |Determine whether a @ByteArray\#@ is guaranteed not to move during GC. isByteArrayPinned# :: ByteArray# -> Int# isByteArrayPinned# = isByteArrayPinned# -- |Intended for use with pinned arrays; otherwise very unsafe! byteArrayContents# :: ByteArray# -> Addr# byteArrayContents# = byteArrayContents# sameMutableByteArray# :: MutableByteArray# s -> MutableByteArray# s -> Int# sameMutableByteArray# = sameMutableByteArray# -- |Shrink mutable byte array to new specified size (in bytes), in -- the specified state thread. The new size argument must be less than or -- equal to the current size as reported by @sizeofMutableByteArray\#@. shrinkMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> State# s shrinkMutableByteArray# = shrinkMutableByteArray# -- |Resize (unpinned) mutable byte array to new specified size (in bytes). -- The returned @MutableByteArray\#@ is either the original -- @MutableByteArray\#@ resized in-place or, if not possible, a newly -- allocated (unpinned) @MutableByteArray\#@ (with the original content -- copied over). -- -- To avoid undefined behaviour, the original @MutableByteArray\#@ shall -- not be accessed anymore after a @resizeMutableByteArray\#@ has been -- performed. Moreover, no reference to the old one should be kept in order -- to allow garbage collection of the original @MutableByteArray\#@ in -- case a new @MutableByteArray\#@ had to be allocated. resizeMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,MutableByteArray# s #) resizeMutableByteArray# = resizeMutableByteArray# -- |Make a mutable byte array immutable, without copying. unsafeFreezeByteArray# :: MutableByteArray# s -> State# s -> (# State# s,ByteArray# #) unsafeFreezeByteArray# = unsafeFreezeByteArray# -- |Return the size of the array in bytes. sizeofByteArray# :: ByteArray# -> Int# sizeofByteArray# = sizeofByteArray# -- |Return the size of the array in bytes. Note that this is deprecated as it is -- unsafe in the presence of resize operations on the same byte -- array. {-# DEPRECATED sizeofMutableByteArray# " Use 'getSizeofMutableByteArray#' instead " #-} sizeofMutableByteArray# :: MutableByteArray# s -> Int# sizeofMutableByteArray# = sizeofMutableByteArray# -- |Return the number of elements in the array. getSizeofMutableByteArray# :: MutableByteArray# s -> State# s -> (# State# s,Int# #) getSizeofMutableByteArray# = getSizeofMutableByteArray# -- |Read 8-bit character; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexCharArray# :: ByteArray# -> Int# -> Char# indexCharArray# = indexCharArray# -- |Read 31-bit character; offset in 4-byte words. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWideCharArray# :: ByteArray# -> Int# -> Char# indexWideCharArray# = indexWideCharArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexIntArray# :: ByteArray# -> Int# -> Int# indexIntArray# = indexIntArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexWordArray# :: ByteArray# -> Int# -> Word# indexWordArray# = indexWordArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexAddrArray# :: ByteArray# -> Int# -> Addr# indexAddrArray# = indexAddrArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexFloatArray# :: ByteArray# -> Int# -> Float# indexFloatArray# = indexFloatArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexDoubleArray# :: ByteArray# -> Int# -> Double# indexDoubleArray# = indexDoubleArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a indexStablePtrArray# = indexStablePtrArray# -- |Read 8-bit integer; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexInt8Array# :: ByteArray# -> Int# -> Int# indexInt8Array# = indexInt8Array# -- |Read 16-bit integer; offset in 16-bit words. -- -- __/Warning:/__ this can fail with an unchecked exception. indexInt16Array# :: ByteArray# -> Int# -> Int# indexInt16Array# = indexInt16Array# -- |Read 32-bit integer; offset in 32-bit words. -- -- __/Warning:/__ this can fail with an unchecked exception. indexInt32Array# :: ByteArray# -> Int# -> Int# indexInt32Array# = indexInt32Array# -- |Read 64-bit integer; offset in 64-bit words. -- -- __/Warning:/__ this can fail with an unchecked exception. indexInt64Array# :: ByteArray# -> Int# -> Int# indexInt64Array# = indexInt64Array# -- |Read 8-bit word; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8Array# :: ByteArray# -> Int# -> Word# indexWord8Array# = indexWord8Array# -- |Read 16-bit word; offset in 16-bit words. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord16Array# :: ByteArray# -> Int# -> Word# indexWord16Array# = indexWord16Array# -- |Read 32-bit word; offset in 32-bit words. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord32Array# :: ByteArray# -> Int# -> Word# indexWord32Array# = indexWord32Array# -- |Read 64-bit word; offset in 64-bit words. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord64Array# :: ByteArray# -> Int# -> Word# indexWord64Array# = indexWord64Array# -- |Read 8-bit character; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char# indexWord8ArrayAsChar# = indexWord8ArrayAsChar# -- |Read 31-bit character; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char# indexWord8ArrayAsWideChar# = indexWord8ArrayAsWideChar# -- |Read address; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr# indexWord8ArrayAsAddr# = indexWord8ArrayAsAddr# -- |Read float; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float# indexWord8ArrayAsFloat# = indexWord8ArrayAsFloat# -- |Read double; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double# indexWord8ArrayAsDouble# = indexWord8ArrayAsDouble# -- |Read stable pointer; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a indexWord8ArrayAsStablePtr# = indexWord8ArrayAsStablePtr# -- |Read 16-bit int; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int# indexWord8ArrayAsInt16# = indexWord8ArrayAsInt16# -- |Read 32-bit int; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int# indexWord8ArrayAsInt32# = indexWord8ArrayAsInt32# -- |Read 64-bit int; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int# indexWord8ArrayAsInt64# = indexWord8ArrayAsInt64# -- |Read int; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int# indexWord8ArrayAsInt# = indexWord8ArrayAsInt# -- |Read 16-bit word; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word# indexWord8ArrayAsWord16# = indexWord8ArrayAsWord16# -- |Read 32-bit word; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word# indexWord8ArrayAsWord32# = indexWord8ArrayAsWord32# -- |Read 64-bit word; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word# indexWord8ArrayAsWord64# = indexWord8ArrayAsWord64# -- |Read word; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word# indexWord8ArrayAsWord# = indexWord8ArrayAsWord# -- |Read 8-bit character; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. readCharArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Char# #) readCharArray# = readCharArray# -- |Read 31-bit character; offset in 4-byte words. -- -- __/Warning:/__ this can fail with an unchecked exception. readWideCharArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Char# #) readWideCharArray# = readWideCharArray# -- |Read integer; offset in machine words. -- -- __/Warning:/__ this can fail with an unchecked exception. readIntArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #) readIntArray# = readIntArray# -- |Read word; offset in machine words. -- -- __/Warning:/__ this can fail with an unchecked exception. readWordArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #) readWordArray# = readWordArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readAddrArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Addr# #) readAddrArray# = readAddrArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readFloatArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Float# #) readFloatArray# = readFloatArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readDoubleArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Double# #) readDoubleArray# = readDoubleArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readStablePtrArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,StablePtr# a #) readStablePtrArray# = readStablePtrArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readInt8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #) readInt8Array# = readInt8Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readInt16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #) readInt16Array# = readInt16Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readInt32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #) readInt32Array# = readInt32Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readInt64Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #) readInt64Array# = readInt64Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #) readWord8Array# = readWord8Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #) readWord16Array# = readWord16Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #) readWord32Array# = readWord32Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord64Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #) readWord64Array# = readWord64Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsChar# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Char# #) readWord8ArrayAsChar# = readWord8ArrayAsChar# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsWideChar# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Char# #) readWord8ArrayAsWideChar# = readWord8ArrayAsWideChar# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsAddr# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Addr# #) readWord8ArrayAsAddr# = readWord8ArrayAsAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsFloat# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Float# #) readWord8ArrayAsFloat# = readWord8ArrayAsFloat# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsDouble# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Double# #) readWord8ArrayAsDouble# = readWord8ArrayAsDouble# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsStablePtr# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,StablePtr# a #) readWord8ArrayAsStablePtr# = readWord8ArrayAsStablePtr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsInt16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #) readWord8ArrayAsInt16# = readWord8ArrayAsInt16# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsInt32# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #) readWord8ArrayAsInt32# = readWord8ArrayAsInt32# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsInt64# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #) readWord8ArrayAsInt64# = readWord8ArrayAsInt64# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsInt# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #) readWord8ArrayAsInt# = readWord8ArrayAsInt# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsWord16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #) readWord8ArrayAsWord16# = readWord8ArrayAsWord16# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsWord32# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #) readWord8ArrayAsWord32# = readWord8ArrayAsWord32# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsWord64# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #) readWord8ArrayAsWord64# = readWord8ArrayAsWord64# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8ArrayAsWord# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #) readWord8ArrayAsWord# = readWord8ArrayAsWord# -- |Write 8-bit character; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. writeCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s writeCharArray# = writeCharArray# -- |Write 31-bit character; offset in 4-byte words. -- -- __/Warning:/__ this can fail with an unchecked exception. writeWideCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s writeWideCharArray# = writeWideCharArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s writeIntArray# = writeIntArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWordArray# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s writeWordArray# = writeWordArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeAddrArray# :: MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s writeAddrArray# = writeAddrArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeFloatArray# :: MutableByteArray# s -> Int# -> Float# -> State# s -> State# s writeFloatArray# = writeFloatArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeDoubleArray# :: MutableByteArray# s -> Int# -> Double# -> State# s -> State# s writeDoubleArray# = writeDoubleArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeStablePtrArray# :: MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s writeStablePtrArray# = writeStablePtrArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeInt8Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s writeInt8Array# = writeInt8Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeInt16Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s writeInt16Array# = writeInt16Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeInt32Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s writeInt32Array# = writeInt32Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeInt64Array# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s writeInt64Array# = writeInt64Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s writeWord8Array# = writeWord8Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord16Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s writeWord16Array# = writeWord16Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord32Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s writeWord32Array# = writeWord32Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord64Array# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s writeWord64Array# = writeWord64Array# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsChar# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s writeWord8ArrayAsChar# = writeWord8ArrayAsChar# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsWideChar# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s writeWord8ArrayAsWideChar# = writeWord8ArrayAsWideChar# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsAddr# :: MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s writeWord8ArrayAsAddr# = writeWord8ArrayAsAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsFloat# :: MutableByteArray# s -> Int# -> Float# -> State# s -> State# s writeWord8ArrayAsFloat# = writeWord8ArrayAsFloat# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsDouble# :: MutableByteArray# s -> Int# -> Double# -> State# s -> State# s writeWord8ArrayAsDouble# = writeWord8ArrayAsDouble# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsStablePtr# :: MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s writeWord8ArrayAsStablePtr# = writeWord8ArrayAsStablePtr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsInt16# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s writeWord8ArrayAsInt16# = writeWord8ArrayAsInt16# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsInt32# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s writeWord8ArrayAsInt32# = writeWord8ArrayAsInt32# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsInt64# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s writeWord8ArrayAsInt64# = writeWord8ArrayAsInt64# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsInt# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s writeWord8ArrayAsInt# = writeWord8ArrayAsInt# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsWord16# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s writeWord8ArrayAsWord16# = writeWord8ArrayAsWord16# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsWord32# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s writeWord8ArrayAsWord32# = writeWord8ArrayAsWord32# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsWord64# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s writeWord8ArrayAsWord64# = writeWord8ArrayAsWord64# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8ArrayAsWord# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s writeWord8ArrayAsWord# = writeWord8ArrayAsWord# -- |@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. compareByteArrays# :: ByteArray# -> Int# -> ByteArray# -> Int# -> Int# -> Int# compareByteArrays# = compareByteArrays# -- |@copyByteArray# src src_ofs dst dst_ofs n@ copies the range -- starting at offset @src_ofs@ of length @n@ from the -- @ByteArray#@ @src@ to the @MutableByteArray#@ @dst@ -- starting at offset @dst_ofs@. Both arrays must fully contain -- the specified ranges, but this is not checked. The two arrays must -- not be the same array in different states, but this is not checked -- either. -- -- __/Warning:/__ this can fail with an unchecked exception. copyByteArray# :: ByteArray# -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s copyByteArray# = copyByteArray# -- |Copy a range of the first MutableByteArray\# to the specified region in the second MutableByteArray\#. -- Both arrays must fully contain the specified ranges, but this is not checked. The regions are -- allowed to overlap, although this is only possible when the same array is provided -- as both the source and the destination. -- -- __/Warning:/__ this can fail with an unchecked exception. copyMutableByteArray# :: MutableByteArray# s -> Int# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s copyMutableByteArray# = copyMutableByteArray# -- |Copy a range of the ByteArray\# to the memory range starting at the Addr\#. -- The ByteArray\# and the memory region at Addr\# must fully contain the -- specified ranges, but this is not checked. The Addr\# must not point into the -- ByteArray\# (e.g. if the ByteArray\# were pinned), but this is not checked -- either. -- -- __/Warning:/__ this can fail with an unchecked exception. copyByteArrayToAddr# :: ByteArray# -> Int# -> Addr# -> Int# -> State# s -> State# s copyByteArrayToAddr# = copyByteArrayToAddr# -- |Copy a range of the MutableByteArray\# to the memory range starting at the -- Addr\#. The MutableByteArray\# and the memory region at Addr\# must fully -- contain the specified ranges, but this is not checked. The Addr\# must not -- point into the MutableByteArray\# (e.g. if the MutableByteArray\# were -- pinned), but this is not checked either. -- -- __/Warning:/__ this can fail with an unchecked exception. copyMutableByteArrayToAddr# :: MutableByteArray# s -> Int# -> Addr# -> Int# -> State# s -> State# s copyMutableByteArrayToAddr# = copyMutableByteArrayToAddr# -- |Copy a memory range starting at the Addr\# to the specified range in the -- MutableByteArray\#. The memory region at Addr\# and the ByteArray\# must fully -- contain the specified ranges, but this is not checked. The Addr\# must not -- point into the MutableByteArray\# (e.g. if the MutableByteArray\# were pinned), -- but this is not checked either. -- -- __/Warning:/__ this can fail with an unchecked exception. copyAddrToByteArray# :: Addr# -> MutableByteArray# s -> Int# -> Int# -> State# s -> State# s copyAddrToByteArray# = copyAddrToByteArray# -- |@setByteArray# ba off len c@ sets the byte range @[off, off+len]@ of -- the @MutableByteArray#@ to the byte @c@. -- -- __/Warning:/__ this can fail with an unchecked exception. setByteArray# :: MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> State# s setByteArray# = setByteArray# -- |Given an array and an offset in machine words, read an element. The -- index is assumed to be in bounds. Implies a full memory barrier. -- -- __/Warning:/__ this can fail with an unchecked exception. atomicReadIntArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #) atomicReadIntArray# = atomicReadIntArray# -- |Given an array and an offset in machine words, write an element. The -- index is assumed to be in bounds. Implies a full memory barrier. -- -- __/Warning:/__ this can fail with an unchecked exception. atomicWriteIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s atomicWriteIntArray# = atomicWriteIntArray# -- |Given an array, an offset in machine words, the expected old value, and -- the new value, perform an atomic compare and swap i.e. write the new -- value if the current value matches the provided old value. Returns -- the value of the element before the operation. Implies a full memory -- barrier. -- -- __/Warning:/__ this can fail with an unchecked exception. casIntArray# :: MutableByteArray# s -> Int# -> Int# -> Int# -> State# s -> (# State# s,Int# #) casIntArray# = casIntArray# -- |Given an array, and offset in machine words, and a value to add, -- atomically add the value to the element. Returns the value of the -- element before the operation. Implies a full memory barrier. -- -- __/Warning:/__ this can fail with an unchecked exception. fetchAddIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s,Int# #) fetchAddIntArray# = fetchAddIntArray# -- |Given an array, and offset in machine words, and a value to subtract, -- atomically substract the value to the element. Returns the value of -- the element before the operation. Implies a full memory barrier. -- -- __/Warning:/__ this can fail with an unchecked exception. fetchSubIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s,Int# #) fetchSubIntArray# = fetchSubIntArray# -- |Given an array, and offset in machine words, and a value to AND, -- atomically AND the value to the element. Returns the value of the -- element before the operation. Implies a full memory barrier. -- -- __/Warning:/__ this can fail with an unchecked exception. fetchAndIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s,Int# #) fetchAndIntArray# = fetchAndIntArray# -- |Given an array, and offset in machine words, and a value to NAND, -- atomically NAND the value to the element. Returns the value of the -- element before the operation. Implies a full memory barrier. -- -- __/Warning:/__ this can fail with an unchecked exception. fetchNandIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s,Int# #) fetchNandIntArray# = fetchNandIntArray# -- |Given an array, and offset in machine words, and a value to OR, -- atomically OR the value to the element. Returns the value of the -- element before the operation. Implies a full memory barrier. -- -- __/Warning:/__ this can fail with an unchecked exception. fetchOrIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s,Int# #) fetchOrIntArray# = fetchOrIntArray# -- |Given an array, and offset in machine words, and a value to XOR, -- atomically XOR the value to the element. Returns the value of the -- element before the operation. Implies a full memory barrier. -- -- __/Warning:/__ this can fail with an unchecked exception. fetchXorIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> (# State# s,Int# #) fetchXorIntArray# = fetchXorIntArray# data ArrayArray# data MutableArrayArray# s -- |Create a new mutable array of arrays with the specified number of elements, -- in the specified state thread, with each element recursively referring to the -- newly created array. newArrayArray# :: Int# -> State# s -> (# State# s,MutableArrayArray# s #) newArrayArray# = newArrayArray# sameMutableArrayArray# :: MutableArrayArray# s -> MutableArrayArray# s -> Int# sameMutableArrayArray# = sameMutableArrayArray# -- |Make a mutable array of arrays immutable, without copying. unsafeFreezeArrayArray# :: MutableArrayArray# s -> State# s -> (# State# s,ArrayArray# #) unsafeFreezeArrayArray# = unsafeFreezeArrayArray# -- |Return the number of elements in the array. sizeofArrayArray# :: ArrayArray# -> Int# sizeofArrayArray# = sizeofArrayArray# -- |Return the number of elements in the array. sizeofMutableArrayArray# :: MutableArrayArray# s -> Int# sizeofMutableArrayArray# = sizeofMutableArrayArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexByteArrayArray# :: ArrayArray# -> Int# -> ByteArray# indexByteArrayArray# = indexByteArrayArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexArrayArrayArray# :: ArrayArray# -> Int# -> ArrayArray# indexArrayArrayArray# = indexArrayArrayArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readByteArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s,ByteArray# #) readByteArrayArray# = readByteArrayArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readMutableByteArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s,MutableByteArray# s #) readMutableByteArrayArray# = readMutableByteArrayArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readArrayArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s,ArrayArray# #) readArrayArrayArray# = readArrayArrayArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readMutableArrayArrayArray# :: MutableArrayArray# s -> Int# -> State# s -> (# State# s,MutableArrayArray# s #) readMutableArrayArrayArray# = readMutableArrayArrayArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeByteArrayArray# :: MutableArrayArray# s -> Int# -> ByteArray# -> State# s -> State# s writeByteArrayArray# = writeByteArrayArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeMutableByteArrayArray# :: MutableArrayArray# s -> Int# -> MutableByteArray# s -> State# s -> State# s writeMutableByteArrayArray# = writeMutableByteArrayArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeArrayArrayArray# :: MutableArrayArray# s -> Int# -> ArrayArray# -> State# s -> State# s writeArrayArrayArray# = writeArrayArrayArray# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeMutableArrayArrayArray# :: MutableArrayArray# s -> Int# -> MutableArrayArray# s -> State# s -> State# s writeMutableArrayArrayArray# = writeMutableArrayArrayArray# -- |Copy a range of the ArrayArray\# to the specified region in the MutableArrayArray\#. -- Both arrays must fully contain the specified ranges, but this is not checked. -- The two arrays must not be the same array in different states, but this is not checked either. -- -- __/Warning:/__ this can fail with an unchecked exception. copyArrayArray# :: ArrayArray# -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s copyArrayArray# = copyArrayArray# -- |Copy a range of the first MutableArrayArray# to the specified region in the second -- MutableArrayArray#. -- Both arrays must fully contain the specified ranges, but this is not checked. -- The regions are allowed to overlap, although this is only possible when the same -- array is provided as both the source and the destination. -- -- -- __/Warning:/__ this can fail with an unchecked exception. copyMutableArrayArray# :: MutableArrayArray# s -> Int# -> MutableArrayArray# s -> Int# -> Int# -> State# s -> State# s copyMutableArrayArray# = copyMutableArrayArray# -- | An arbitrary machine address assumed to point outside -- the garbage-collected heap. data Addr# -- | The null address. nullAddr# :: Addr# nullAddr# = nullAddr# plusAddr# :: Addr# -> Int# -> Addr# plusAddr# = plusAddr# -- |Result is meaningless if two @Addr\#@s are so far apart that their -- difference doesn\'t fit in an @Int\#@. minusAddr# :: Addr# -> Addr# -> Int# minusAddr# = minusAddr# -- |Return the remainder when the @Addr\#@ arg, treated like an @Int\#@, -- is divided by the @Int\#@ arg. remAddr# :: Addr# -> Int# -> Int# remAddr# = remAddr# -- |Coerce directly from address to int. {-# DEPRECATED addr2Int# " This operation is strongly deprecated. " #-} addr2Int# :: Addr# -> Int# addr2Int# = addr2Int# -- |Coerce directly from int to address. {-# DEPRECATED int2Addr# " This operation is strongly deprecated. " #-} int2Addr# :: Int# -> Addr# int2Addr# = int2Addr# gtAddr# :: Addr# -> Addr# -> Int# gtAddr# = gtAddr# geAddr# :: Addr# -> Addr# -> Int# geAddr# = geAddr# eqAddr# :: Addr# -> Addr# -> Int# eqAddr# = eqAddr# neAddr# :: Addr# -> Addr# -> Int# neAddr# = neAddr# ltAddr# :: Addr# -> Addr# -> Int# ltAddr# = ltAddr# leAddr# :: Addr# -> Addr# -> Int# leAddr# = leAddr# -- |Reads 8-bit character; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. indexCharOffAddr# :: Addr# -> Int# -> Char# indexCharOffAddr# = indexCharOffAddr# -- |Reads 31-bit character; offset in 4-byte words. -- -- __/Warning:/__ this can fail with an unchecked exception. indexWideCharOffAddr# :: Addr# -> Int# -> Char# indexWideCharOffAddr# = indexWideCharOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexIntOffAddr# :: Addr# -> Int# -> Int# indexIntOffAddr# = indexIntOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexWordOffAddr# :: Addr# -> Int# -> Word# indexWordOffAddr# = indexWordOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexAddrOffAddr# :: Addr# -> Int# -> Addr# indexAddrOffAddr# = indexAddrOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexFloatOffAddr# :: Addr# -> Int# -> Float# indexFloatOffAddr# = indexFloatOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexDoubleOffAddr# :: Addr# -> Int# -> Double# indexDoubleOffAddr# = indexDoubleOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a indexStablePtrOffAddr# = indexStablePtrOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexInt8OffAddr# :: Addr# -> Int# -> Int# indexInt8OffAddr# = indexInt8OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexInt16OffAddr# :: Addr# -> Int# -> Int# indexInt16OffAddr# = indexInt16OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexInt32OffAddr# :: Addr# -> Int# -> Int# indexInt32OffAddr# = indexInt32OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexInt64OffAddr# :: Addr# -> Int# -> Int# indexInt64OffAddr# = indexInt64OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord8OffAddr# :: Addr# -> Int# -> Word# indexWord8OffAddr# = indexWord8OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord16OffAddr# :: Addr# -> Int# -> Word# indexWord16OffAddr# = indexWord16OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord32OffAddr# :: Addr# -> Int# -> Word# indexWord32OffAddr# = indexWord32OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. indexWord64OffAddr# :: Addr# -> Int# -> Word# indexWord64OffAddr# = indexWord64OffAddr# -- |Reads 8-bit character; offset in bytes. -- -- __/Warning:/__ this can fail with an unchecked exception. readCharOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Char# #) readCharOffAddr# = readCharOffAddr# -- |Reads 31-bit character; offset in 4-byte words. -- -- __/Warning:/__ this can fail with an unchecked exception. readWideCharOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Char# #) readWideCharOffAddr# = readWideCharOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readIntOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int# #) readIntOffAddr# = readIntOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWordOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word# #) readWordOffAddr# = readWordOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readAddrOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Addr# #) readAddrOffAddr# = readAddrOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readFloatOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Float# #) readFloatOffAddr# = readFloatOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readDoubleOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Double# #) readDoubleOffAddr# = readDoubleOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readStablePtrOffAddr# :: Addr# -> Int# -> State# s -> (# State# s,StablePtr# a #) readStablePtrOffAddr# = readStablePtrOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readInt8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int# #) readInt8OffAddr# = readInt8OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readInt16OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int# #) readInt16OffAddr# = readInt16OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readInt32OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int# #) readInt32OffAddr# = readInt32OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readInt64OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int# #) readInt64OffAddr# = readInt64OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word# #) readWord8OffAddr# = readWord8OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord16OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word# #) readWord16OffAddr# = readWord16OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord32OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word# #) readWord32OffAddr# = readWord32OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. readWord64OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word# #) readWord64OffAddr# = readWord64OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeCharOffAddr# :: Addr# -> Int# -> Char# -> State# s -> State# s writeCharOffAddr# = writeCharOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWideCharOffAddr# :: Addr# -> Int# -> Char# -> State# s -> State# s writeWideCharOffAddr# = writeWideCharOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeIntOffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s writeIntOffAddr# = writeIntOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWordOffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s writeWordOffAddr# = writeWordOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeAddrOffAddr# :: Addr# -> Int# -> Addr# -> State# s -> State# s writeAddrOffAddr# = writeAddrOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeFloatOffAddr# :: Addr# -> Int# -> Float# -> State# s -> State# s writeFloatOffAddr# = writeFloatOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeDoubleOffAddr# :: Addr# -> Int# -> Double# -> State# s -> State# s writeDoubleOffAddr# = writeDoubleOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeStablePtrOffAddr# :: Addr# -> Int# -> StablePtr# a -> State# s -> State# s writeStablePtrOffAddr# = writeStablePtrOffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeInt8OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s writeInt8OffAddr# = writeInt8OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeInt16OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s writeInt16OffAddr# = writeInt16OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeInt32OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s writeInt32OffAddr# = writeInt32OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeInt64OffAddr# :: Addr# -> Int# -> Int# -> State# s -> State# s writeInt64OffAddr# = writeInt64OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord8OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s writeWord8OffAddr# = writeWord8OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord16OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s writeWord16OffAddr# = writeWord16OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord32OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s writeWord32OffAddr# = writeWord32OffAddr# -- | -- -- __/Warning:/__ this can fail with an unchecked exception. writeWord64OffAddr# :: Addr# -> Int# -> Word# -> State# s -> State# s writeWord64OffAddr# = writeWord64OffAddr# -- |A @MutVar\#@ behaves like a single-element mutable array. data MutVar# s a -- |Create @MutVar\#@ with specified initial value in specified state thread. newMutVar# :: a -> State# s -> (# State# s,MutVar# s a #) newMutVar# = newMutVar# -- |Read contents of @MutVar\#@. Result is not yet evaluated. readMutVar# :: MutVar# s a -> State# s -> (# State# s,a #) readMutVar# = readMutVar# -- |Write contents of @MutVar\#@. writeMutVar# :: MutVar# s a -> a -> State# s -> State# s writeMutVar# = writeMutVar# sameMutVar# :: MutVar# s a -> MutVar# s a -> Int# sameMutVar# = sameMutVar# -- | 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. atomicModifyMutVar2# :: MutVar# s a -> (a -> c) -> State# s -> (# State# s,a,c #) atomicModifyMutVar2# = atomicModifyMutVar2# -- | 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. atomicModifyMutVar_# :: MutVar# s a -> (a -> a) -> State# s -> (# State# s,a,a #) atomicModifyMutVar_# = atomicModifyMutVar_# casMutVar# :: MutVar# s a -> a -> a -> State# s -> (# State# s,Int#,a #) casMutVar# = casMutVar# catch# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> (b -> State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #) catch# = catch# raise# :: b -> o raise# = raise# raiseIO# :: a -> State# (RealWorld) -> (# State# (RealWorld),b #) raiseIO# = raiseIO# maskAsyncExceptions# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #) maskAsyncExceptions# = maskAsyncExceptions# maskUninterruptible# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #) maskUninterruptible# = maskUninterruptible# unmaskAsyncExceptions# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #) unmaskAsyncExceptions# = unmaskAsyncExceptions# getMaskingState# :: State# (RealWorld) -> (# State# (RealWorld),Int# #) getMaskingState# = getMaskingState# data TVar# s a atomically# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #) atomically# = atomically# retry# :: State# (RealWorld) -> (# State# (RealWorld),a #) retry# = retry# catchRetry# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> (State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #) catchRetry# = catchRetry# catchSTM# :: (State# (RealWorld) -> (# State# (RealWorld),a #)) -> (b -> State# (RealWorld) -> (# State# (RealWorld),a #)) -> State# (RealWorld) -> (# State# (RealWorld),a #) catchSTM# = catchSTM# -- |Create a new @TVar\#@ holding a specified initial value. newTVar# :: a -> State# s -> (# State# s,TVar# s a #) newTVar# = newTVar# -- |Read contents of @TVar\#@. Result is not yet evaluated. readTVar# :: TVar# s a -> State# s -> (# State# s,a #) readTVar# = readTVar# -- |Read contents of @TVar\#@ outside an STM transaction readTVarIO# :: TVar# s a -> State# s -> (# State# s,a #) readTVarIO# = readTVarIO# -- |Write contents of @TVar\#@. writeTVar# :: TVar# s a -> a -> State# s -> State# s writeTVar# = writeTVar# sameTVar# :: TVar# s a -> TVar# s a -> Int# sameTVar# = sameTVar# -- | A shared mutable variable (/not/ the same as a @MutVar\#@!). -- (Note: in a non-concurrent implementation, @(MVar\# a)@ can be -- represented by @(MutVar\# (Maybe a))@.) data MVar# s a -- |Create new @MVar\#@; initially empty. newMVar# :: State# s -> (# State# s,MVar# s a #) newMVar# = newMVar# -- |If @MVar\#@ is empty, block until it becomes full. -- Then remove and return its contents, and set it empty. takeMVar# :: MVar# s a -> State# s -> (# State# s,a #) takeMVar# = takeMVar# -- |If @MVar\#@ is empty, immediately return with integer 0 and value undefined. -- Otherwise, return with integer 1 and contents of @MVar\#@, and set @MVar\#@ empty. tryTakeMVar# :: MVar# s a -> State# s -> (# State# s,Int#,a #) tryTakeMVar# = tryTakeMVar# -- |If @MVar\#@ is full, block until it becomes empty. -- Then store value arg as its new contents. putMVar# :: MVar# s a -> a -> State# s -> State# s putMVar# = putMVar# -- |If @MVar\#@ is full, immediately return with integer 0. -- Otherwise, store value arg as @MVar\#@\'s new contents, and return with integer 1. tryPutMVar# :: MVar# s a -> a -> State# s -> (# State# s,Int# #) tryPutMVar# = tryPutMVar# -- |If @MVar\#@ is empty, block until it becomes full. -- Then read its contents without modifying the MVar, without possibility -- of intervention from other threads. readMVar# :: MVar# s a -> State# s -> (# State# s,a #) readMVar# = readMVar# -- |If @MVar\#@ is empty, immediately return with integer 0 and value undefined. -- Otherwise, return with integer 1 and contents of @MVar\#@. tryReadMVar# :: MVar# s a -> State# s -> (# State# s,Int#,a #) tryReadMVar# = tryReadMVar# sameMVar# :: MVar# s a -> MVar# s a -> Int# sameMVar# = sameMVar# -- |Return 1 if @MVar\#@ is empty; 0 otherwise. isEmptyMVar# :: MVar# s a -> State# s -> (# State# s,Int# #) isEmptyMVar# = isEmptyMVar# -- |Sleep specified number of microseconds. delay# :: Int# -> State# s -> State# s delay# = delay# -- |Block until input is available on specified file descriptor. waitRead# :: Int# -> State# s -> State# s waitRead# = waitRead# -- |Block until output is possible on specified file descriptor. waitWrite# :: Int# -> State# s -> State# s waitWrite# = waitWrite# -- | @State\#@ is the primitive, unlifted type of states. It has -- one type parameter, thus @State\# RealWorld@, or @State\# s@, -- where s is a type variable. The only purpose of the type parameter -- is to keep different state threads separate. It is represented by -- nothing at all. data State# s -- | @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\#@. data RealWorld -- |(In a non-concurrent implementation, this can be a singleton -- type, whose (unique) value is returned by @myThreadId\#@. The -- other operations can be omitted.) data ThreadId# fork# :: a -> State# (RealWorld) -> (# State# (RealWorld),ThreadId# #) fork# = fork# forkOn# :: Int# -> a -> State# (RealWorld) -> (# State# (RealWorld),ThreadId# #) forkOn# = forkOn# killThread# :: ThreadId# -> a -> State# (RealWorld) -> State# (RealWorld) killThread# = killThread# yield# :: State# (RealWorld) -> State# (RealWorld) yield# = yield# myThreadId# :: State# (RealWorld) -> (# State# (RealWorld),ThreadId# #) myThreadId# = myThreadId# labelThread# :: ThreadId# -> Addr# -> State# (RealWorld) -> State# (RealWorld) labelThread# = labelThread# isCurrentThreadBound# :: State# (RealWorld) -> (# State# (RealWorld),Int# #) isCurrentThreadBound# = isCurrentThreadBound# noDuplicate# :: State# s -> State# s noDuplicate# = noDuplicate# threadStatus# :: ThreadId# -> State# (RealWorld) -> (# State# (RealWorld),Int#,Int#,Int# #) threadStatus# = threadStatus# data Weak# b -- | @mkWeak# k v finalizer s@ creates a weak reference to value @k@, -- with an associated reference to some value @v@. If @k@ is still -- alive then @v@ can be retrieved using @deRefWeak#@. Note that -- the type of @k@ must be represented by a pointer (i.e. of kind @TYPE \'LiftedRep@ or @TYPE \'UnliftedRep@). mkWeak# :: o -> b -> (State# (RealWorld) -> (# State# (RealWorld),c #)) -> State# (RealWorld) -> (# State# (RealWorld),Weak# b #) mkWeak# = mkWeak# mkWeakNoFinalizer# :: o -> b -> State# (RealWorld) -> (# State# (RealWorld),Weak# b #) mkWeakNoFinalizer# = mkWeakNoFinalizer# -- | @addCFinalizerToWeak# fptr ptr flag eptr w@ attaches a C -- function pointer @fptr@ to a weak pointer @w@ as a finalizer. If -- @flag@ is zero, @fptr@ will be called with one argument, -- @ptr@. Otherwise, it will be called with two arguments, -- @eptr@ and @ptr@. @addCFinalizerToWeak#@ returns -- 1 on success, or 0 if @w@ is already dead. addCFinalizerToWeak# :: Addr# -> Addr# -> Int# -> Addr# -> Weak# b -> State# (RealWorld) -> (# State# (RealWorld),Int# #) addCFinalizerToWeak# = addCFinalizerToWeak# deRefWeak# :: Weak# a -> State# (RealWorld) -> (# State# (RealWorld),Int#,a #) deRefWeak# = deRefWeak# -- | Finalize a weak pointer. The return value is an unboxed tuple -- containing the new state of the world and an \"unboxed Maybe\", -- represented by an @Int#@ and a (possibly invalid) finalization -- action. An @Int#@ of @1@ indicates that the finalizer is valid. The -- return value @b@ from the finalizer should be ignored. finalizeWeak# :: Weak# a -> State# (RealWorld) -> (# State# (RealWorld),Int#,State# (RealWorld) -> (# State# (RealWorld),b #) #) finalizeWeak# = finalizeWeak# touch# :: o -> State# (RealWorld) -> State# (RealWorld) touch# = touch# data StablePtr# a data StableName# a makeStablePtr# :: a -> State# (RealWorld) -> (# State# (RealWorld),StablePtr# a #) makeStablePtr# = makeStablePtr# deRefStablePtr# :: StablePtr# a -> State# (RealWorld) -> (# State# (RealWorld),a #) deRefStablePtr# = deRefStablePtr# eqStablePtr# :: StablePtr# a -> StablePtr# a -> Int# eqStablePtr# = eqStablePtr# makeStableName# :: a -> State# (RealWorld) -> (# State# (RealWorld),StableName# a #) makeStableName# = makeStableName# eqStableName# :: StableName# a -> StableName# b -> Int# eqStableName# = eqStableName# stableNameToInt# :: StableName# a -> Int# stableNameToInt# = stableNameToInt# data Compact# -- | Create a new CNF with a single compact block. The argument is -- the capacity of the compact block (in bytes, not words). -- The capacity is rounded up to a multiple of the allocator block size -- and is capped to one mega block. compactNew# :: Word# -> State# (RealWorld) -> (# State# (RealWorld),Compact# #) compactNew# = compactNew# -- | Set the new allocation size of the CNF. This value (in bytes) -- determines the capacity of each compact block in the CNF. It -- does not retroactively affect existing compact blocks in the CNF. compactResize# :: Compact# -> Word# -> State# (RealWorld) -> State# (RealWorld) compactResize# = compactResize# -- | Returns 1\# if the object is contained in the CNF, 0\# otherwise. compactContains# :: Compact# -> a -> State# (RealWorld) -> (# State# (RealWorld),Int# #) compactContains# = compactContains# -- | Returns 1\# if the object is in any CNF at all, 0\# otherwise. compactContainsAny# :: a -> State# (RealWorld) -> (# State# (RealWorld),Int# #) compactContainsAny# = compactContainsAny# -- | Returns the address and the utilized size (in bytes) of the -- first compact block of a CNF. compactGetFirstBlock# :: Compact# -> State# (RealWorld) -> (# State# (RealWorld),Addr#,Word# #) compactGetFirstBlock# = compactGetFirstBlock# -- | Given a CNF and the address of one its compact blocks, returns the -- next compact block and its utilized size, or @nullAddr\#@ if the -- argument was the last compact block in the CNF. compactGetNextBlock# :: Compact# -> Addr# -> State# (RealWorld) -> (# State# (RealWorld),Addr#,Word# #) compactGetNextBlock# = compactGetNextBlock# -- | Attempt to allocate a compact block with the capacity (in -- bytes) given by the first argument. The @Addr\#@ is a pointer -- to previous compact block of the CNF or @nullAddr\#@ to create a -- new CNF with a single compact block. -- -- The resulting block is not known to the GC until -- @compactFixupPointers\#@ is called on it, and care must be taken -- so that the address does not escape or memory will be leaked. -- compactAllocateBlock# :: Word# -> Addr# -> State# (RealWorld) -> (# State# (RealWorld),Addr# #) compactAllocateBlock# = compactAllocateBlock# -- | Given the pointer to the first block of a CNF and the -- address of the root object in the old address space, fix up -- the internal pointers inside the CNF to account for -- a different position in memory than when it was serialized. -- This method must be called exactly once after importing -- a serialized CNF. It returns the new CNF and the new adjusted -- root address. compactFixupPointers# :: Addr# -> Addr# -> State# (RealWorld) -> (# State# (RealWorld),Compact#,Addr# #) compactFixupPointers# = compactFixupPointers# -- | Recursively add a closure and its transitive closure to a -- @Compact\#@ (a CNF), evaluating any unevaluated components -- at the same time. Note: @compactAdd\#@ is not thread-safe, so -- only one thread may call @compactAdd\#@ with a particular -- @Compact\#@ at any given time. The primop does not -- enforce any mutual exclusion; the caller is expected to -- arrange this. compactAdd# :: Compact# -> a -> State# (RealWorld) -> (# State# (RealWorld),a #) compactAdd# = compactAdd# -- | Like @compactAdd\#@, but retains sharing and cycles -- during compaction. compactAddWithSharing# :: Compact# -> a -> State# (RealWorld) -> (# State# (RealWorld),a #) compactAddWithSharing# = compactAddWithSharing# -- | Return the total capacity (in bytes) of all the compact blocks -- in the CNF. compactSize# :: Compact# -> State# (RealWorld) -> (# State# (RealWorld),Word# #) compactSize# = compactSize# -- | Returns @1\#@ if the given pointers are equal and @0\#@ otherwise. -- -- __/Warning:/__ this can fail with an unchecked exception. reallyUnsafePtrEquality# :: a -> a -> Int# reallyUnsafePtrEquality# = reallyUnsafePtrEquality# {-# DEPRECATED par# " Use 'spark#' instead " #-} par# :: a -> Int# par# = par# spark# :: a -> State# s -> (# State# s,a #) spark# = spark# seq# :: a -> State# s -> (# State# s,a #) seq# = seq# getSpark# :: State# s -> (# State# s,Int#,a #) getSpark# = getSpark# -- | Returns the number of sparks in the local spark pool. numSparks# :: State# s -> (# State# s,Int# #) numSparks# = numSparks# dataToTag# :: a -> Int# dataToTag# = dataToTag# tagToEnum# :: Int# -> a tagToEnum# = let x = x in x -- | Primitive bytecode type. data BCO# -- | Convert an @Addr\#@ to a followable Any type. addrToAny# :: Addr# -> (# a #) addrToAny# = addrToAny# -- | Retrieve the address of any Haskell value. This is -- essentially an @unsafeCoerce\#@, but if implemented as such -- the core lint pass complains and fails to compile. -- As a primop, it is opaque to core\/stg, and only appears -- in cmm (where the copy propagation pass will get rid of it). -- Note that \"a\" must be a value, not a thunk! It\'s too late -- for strictness analysis to enforce this, so you\'re on your -- own to guarantee this. Also note that @Addr\#@ is not a GC -- pointer - up to you to guarantee that it does not become -- a dangling pointer immediately after you get it. anyToAddr# :: a -> State# (RealWorld) -> (# State# (RealWorld),Addr# #) anyToAddr# = anyToAddr# -- | Wrap a BCO in a @AP_UPD@ thunk which will be updated with the value of -- the BCO when evaluated. mkApUpd0# :: BCO# -> (# a #) mkApUpd0# = mkApUpd0# -- | @newBCO\# instrs lits ptrs arity bitmap@ creates a new bytecode object. The -- resulting object encodes a function of the given arity with the instructions -- encoded in @instrs@, and a static reference table usage bitmap given by -- @bitmap@. newBCO# :: ByteArray# -> ByteArray# -> Array# a -> Int# -> ByteArray# -> State# s -> (# State# s,BCO# #) newBCO# = newBCO# -- | @unpackClosure\# closure@ copies the closure and pointers in the -- payload of the given closure into two new arrays, and returns a pointer to -- the first word of the closure\'s info table, a non-pointer array for the raw -- bytes of the closure, and a pointer array for the pointers in the payload. unpackClosure# :: a -> (# Addr#,ByteArray#,Array# b #) unpackClosure# = unpackClosure# -- | @closureSize\# closure@ returns the size of the given closure in -- machine words. closureSize# :: a -> Int# closureSize# = closureSize# getApStackVal# :: a -> Int# -> (# Int#,b #) getApStackVal# = getApStackVal# getCCSOf# :: a -> State# s -> (# State# s,Addr# #) getCCSOf# = getCCSOf# -- | Returns the current @CostCentreStack@ (value is @NULL@ if -- not profiling). Takes a dummy argument which can be used to -- avoid the call to @getCurrentCCS\#@ being floated out by the -- simplifier, which would result in an uninformative stack -- (\"CAF\"). getCurrentCCS# :: a -> State# s -> (# State# s,Addr# #) getCurrentCCS# = getCurrentCCS# -- | Run the supplied IO action with an empty CCS. For example, this -- is used by the interpreter to run an interpreted computation -- without the call stack showing that it was invoked from GHC. clearCCS# :: (State# s -> (# State# s,a #)) -> State# s -> (# State# s,a #) clearCCS# = clearCCS# -- | The type constructor @Proxy#@ is used to bear witness to some -- type variable. It\'s used when you want to pass around proxy values -- for doing things like modelling type applications. A @Proxy#@ -- is not only unboxed, it also has a polymorphic kind, and has no -- runtime representation, being totally free. data Proxy# a -- | Witness for an unboxed @Proxy#@ value, which has no runtime -- representation. proxy# :: Proxy# a proxy# = proxy# -- | The value of @seq a b@ is bottom if @a@ is bottom, and -- otherwise equal to @b@. In other words, it evaluates the first -- argument @a@ to weak head normal form (WHNF). @seq@ is usually -- introduced to improve performance by avoiding unneeded laziness. -- -- A note on evaluation order: the expression @seq a b@ does -- /not/ guarantee that @a@ will be evaluated before @b@. -- The only guarantee given by @seq@ is that the both @a@ -- and @b@ will be evaluated before @seq@ returns a value. -- In particular, this means that @b@ may be evaluated before -- @a@. If you need to guarantee a specific order of evaluation, -- you must use the function @pseq@ from the \"parallel\" package. infixr 0 `seq` seq :: a -> b -> b seq = seq -- | The function @unsafeCoerce\#@ allows you to side-step the typechecker entirely. That -- is, it allows you to coerce any type into any other type. If you use this function, -- you had better get it right, otherwise segmentation faults await. It is generally -- used when you want to write a program that you know is well-typed, but where Haskell\'s -- type system is not expressive enough to prove that it is well typed. -- -- The following uses of @unsafeCoerce\#@ are supposed to work (i.e. not lead to -- spurious compile-time or run-time crashes): -- -- * Casting any lifted type to @Any@ -- -- * Casting @Any@ back to the real type -- -- * Casting an unboxed type to another unboxed type of the same size. -- (Casting between floating-point and integral types does not work. -- See the @GHC.Float@ module for functions to do work.) -- -- * Casting between two types that have the same runtime representation. One case is when -- the two types differ only in \"phantom\" type parameters, for example -- @Ptr Int@ to @Ptr Float@, or @[Int]@ to @[Float]@ when the list is -- known to be empty. Also, a @newtype@ of a type @T@ has the same representation -- at runtime as @T@. -- -- Other uses of @unsafeCoerce\#@ are undefined. In particular, you should not use -- @unsafeCoerce\#@ to cast a T to an algebraic data type D, unless T is also -- an algebraic data type. For example, do not cast @Int->Int@ to @Bool@, even if -- you later cast that @Bool@ back to @Int->Int@ before applying it. The reasons -- have to do with GHC\'s internal representation details (for the cognoscenti, data values -- can be entered but function closures cannot). If you want a safe type to cast things -- to, use @Any@, which is not an algebraic data type. -- -- -- -- __/Warning:/__ this can fail with an unchecked exception. unsafeCoerce# :: a -> b unsafeCoerce# = unsafeCoerce# -- | Emits an event via the RTS tracing framework. The contents -- of the event is the zero-terminated byte string passed as the first -- argument. The event will be emitted either to the @.eventlog@ file, -- or to stderr, depending on the runtime RTS flags. traceEvent# :: Addr# -> State# s -> State# s traceEvent# = traceEvent# -- | Emits an event via the RTS tracing framework. The contents -- of the event is the binary object passed as the first argument with -- the the given length passed as the second argument. The event will be -- emitted to the @.eventlog@ file. traceBinaryEvent# :: Addr# -> Int# -> State# s -> State# s traceBinaryEvent# = traceBinaryEvent# -- | Emits a marker event via the RTS tracing framework. The contents -- of the event is the zero-terminated byte string passed as the first -- argument. The event will be emitted either to the @.eventlog@ file, -- or to stderr, depending on the runtime RTS flags. traceMarker# :: Addr# -> State# s -> State# s traceMarker# = traceMarker# -- | Sets the allocation counter for the current thread to the given value. setThreadAllocationCounter# :: Int# -> State# (RealWorld) -> State# (RealWorld) setThreadAllocationCounter# = setThreadAllocationCounter# -- | The function @coerce@ allows you to safely convert between values of -- types that have the same representation with no run-time overhead. In the -- simplest case you can use it instead of a newtype constructor, to go from -- the newtype\'s concrete type to the abstract type. But it also works in -- more complicated settings, e.g. converting a list of newtypes to a list of -- concrete types. -- -- This function is runtime-representation polymorphic, but the -- @RuntimeRep@ type argument is marked as @Inferred@, meaning -- that it is not available for visible type application. This means -- the typechecker will accept @coerce \@Int \@Age 42@. -- coerce :: Coercible a b => a -> b coerce = coerce -- | -- -- __/Warning:/__ this is only available on LLVM. data Int8X16# -- | -- -- __/Warning:/__ this is only available on LLVM. data Int16X8# -- | -- -- __/Warning:/__ this is only available on LLVM. data Int32X4# -- | -- -- __/Warning:/__ this is only available on LLVM. data Int64X2# -- | -- -- __/Warning:/__ this is only available on LLVM. data Int8X32# -- | -- -- __/Warning:/__ this is only available on LLVM. data Int16X16# -- | -- -- __/Warning:/__ this is only available on LLVM. data Int32X8# -- | -- -- __/Warning:/__ this is only available on LLVM. data Int64X4# -- | -- -- __/Warning:/__ this is only available on LLVM. data Int8X64# -- | -- -- __/Warning:/__ this is only available on LLVM. data Int16X32# -- | -- -- __/Warning:/__ this is only available on LLVM. data Int32X16# -- | -- -- __/Warning:/__ this is only available on LLVM. data Int64X8# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word8X16# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word16X8# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word32X4# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word64X2# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word8X32# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word16X16# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word32X8# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word64X4# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word8X64# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word16X32# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word32X16# -- | -- -- __/Warning:/__ this is only available on LLVM. data Word64X8# -- | -- -- __/Warning:/__ this is only available on LLVM. data FloatX4# -- | -- -- __/Warning:/__ this is only available on LLVM. data DoubleX2# -- | -- -- __/Warning:/__ this is only available on LLVM. data FloatX8# -- | -- -- __/Warning:/__ this is only available on LLVM. data DoubleX4# -- | -- -- __/Warning:/__ this is only available on LLVM. data FloatX16# -- | -- -- __/Warning:/__ this is only available on LLVM. data DoubleX8# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt8X16# :: Int# -> Int8X16# broadcastInt8X16# = broadcastInt8X16# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt16X8# :: Int# -> Int16X8# broadcastInt16X8# = broadcastInt16X8# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt32X4# :: Int# -> Int32X4# broadcastInt32X4# = broadcastInt32X4# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt64X2# :: Int# -> Int64X2# broadcastInt64X2# = broadcastInt64X2# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt8X32# :: Int# -> Int8X32# broadcastInt8X32# = broadcastInt8X32# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt16X16# :: Int# -> Int16X16# broadcastInt16X16# = broadcastInt16X16# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt32X8# :: Int# -> Int32X8# broadcastInt32X8# = broadcastInt32X8# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt64X4# :: Int# -> Int64X4# broadcastInt64X4# = broadcastInt64X4# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt8X64# :: Int# -> Int8X64# broadcastInt8X64# = broadcastInt8X64# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt16X32# :: Int# -> Int16X32# broadcastInt16X32# = broadcastInt16X32# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt32X16# :: Int# -> Int32X16# broadcastInt32X16# = broadcastInt32X16# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastInt64X8# :: Int# -> Int64X8# broadcastInt64X8# = broadcastInt64X8# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord8X16# :: Word# -> Word8X16# broadcastWord8X16# = broadcastWord8X16# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord16X8# :: Word# -> Word16X8# broadcastWord16X8# = broadcastWord16X8# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord32X4# :: Word# -> Word32X4# broadcastWord32X4# = broadcastWord32X4# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord64X2# :: Word# -> Word64X2# broadcastWord64X2# = broadcastWord64X2# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord8X32# :: Word# -> Word8X32# broadcastWord8X32# = broadcastWord8X32# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord16X16# :: Word# -> Word16X16# broadcastWord16X16# = broadcastWord16X16# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord32X8# :: Word# -> Word32X8# broadcastWord32X8# = broadcastWord32X8# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord64X4# :: Word# -> Word64X4# broadcastWord64X4# = broadcastWord64X4# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord8X64# :: Word# -> Word8X64# broadcastWord8X64# = broadcastWord8X64# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord16X32# :: Word# -> Word16X32# broadcastWord16X32# = broadcastWord16X32# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord32X16# :: Word# -> Word32X16# broadcastWord32X16# = broadcastWord32X16# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastWord64X8# :: Word# -> Word64X8# broadcastWord64X8# = broadcastWord64X8# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastFloatX4# :: Float# -> FloatX4# broadcastFloatX4# = broadcastFloatX4# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastDoubleX2# :: Double# -> DoubleX2# broadcastDoubleX2# = broadcastDoubleX2# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastFloatX8# :: Float# -> FloatX8# broadcastFloatX8# = broadcastFloatX8# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastDoubleX4# :: Double# -> DoubleX4# broadcastDoubleX4# = broadcastDoubleX4# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastFloatX16# :: Float# -> FloatX16# broadcastFloatX16# = broadcastFloatX16# -- | Broadcast a scalar to all elements of a vector. -- -- __/Warning:/__ this is only available on LLVM. broadcastDoubleX8# :: Double# -> DoubleX8# broadcastDoubleX8# = broadcastDoubleX8# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt8X16# :: (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) -> Int8X16# packInt8X16# = packInt8X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt16X8# :: (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) -> Int16X8# packInt16X8# = packInt16X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt32X4# :: (# Int#,Int#,Int#,Int# #) -> Int32X4# packInt32X4# = packInt32X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt64X2# :: (# Int#,Int# #) -> Int64X2# packInt64X2# = packInt64X2# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt8X32# :: (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) -> Int8X32# packInt8X32# = packInt8X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt16X16# :: (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) -> Int16X16# packInt16X16# = packInt16X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt32X8# :: (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) -> Int32X8# packInt32X8# = packInt32X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt64X4# :: (# Int#,Int#,Int#,Int# #) -> Int64X4# packInt64X4# = packInt64X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt8X64# :: (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) -> Int8X64# packInt8X64# = packInt8X64# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt16X32# :: (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) -> Int16X32# packInt16X32# = packInt16X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt32X16# :: (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) -> Int32X16# packInt32X16# = packInt32X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packInt64X8# :: (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) -> Int64X8# packInt64X8# = packInt64X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord8X16# :: (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) -> Word8X16# packWord8X16# = packWord8X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord16X8# :: (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) -> Word16X8# packWord16X8# = packWord16X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord32X4# :: (# Word#,Word#,Word#,Word# #) -> Word32X4# packWord32X4# = packWord32X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord64X2# :: (# Word#,Word# #) -> Word64X2# packWord64X2# = packWord64X2# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord8X32# :: (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) -> Word8X32# packWord8X32# = packWord8X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord16X16# :: (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) -> Word16X16# packWord16X16# = packWord16X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord32X8# :: (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) -> Word32X8# packWord32X8# = packWord32X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord64X4# :: (# Word#,Word#,Word#,Word# #) -> Word64X4# packWord64X4# = packWord64X4# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord8X64# :: (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) -> Word8X64# packWord8X64# = packWord8X64# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord16X32# :: (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) -> Word16X32# packWord16X32# = packWord16X32# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord32X16# :: (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) -> Word32X16# packWord32X16# = packWord32X16# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packWord64X8# :: (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) -> Word64X8# packWord64X8# = packWord64X8# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packFloatX4# :: (# Float#,Float#,Float#,Float# #) -> FloatX4# packFloatX4# = packFloatX4# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packDoubleX2# :: (# Double#,Double# #) -> DoubleX2# packDoubleX2# = packDoubleX2# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packFloatX8# :: (# Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float# #) -> FloatX8# packFloatX8# = packFloatX8# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packDoubleX4# :: (# Double#,Double#,Double#,Double# #) -> DoubleX4# packDoubleX4# = packDoubleX4# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packFloatX16# :: (# Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float# #) -> FloatX16# packFloatX16# = packFloatX16# -- | Pack the elements of an unboxed tuple into a vector. -- -- __/Warning:/__ this is only available on LLVM. packDoubleX8# :: (# Double#,Double#,Double#,Double#,Double#,Double#,Double#,Double# #) -> DoubleX8# packDoubleX8# = packDoubleX8# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt8X16# :: Int8X16# -> (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) unpackInt8X16# = unpackInt8X16# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt16X8# :: Int16X8# -> (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) unpackInt16X8# = unpackInt16X8# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt32X4# :: Int32X4# -> (# Int#,Int#,Int#,Int# #) unpackInt32X4# = unpackInt32X4# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt64X2# :: Int64X2# -> (# Int#,Int# #) unpackInt64X2# = unpackInt64X2# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt8X32# :: Int8X32# -> (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) unpackInt8X32# = unpackInt8X32# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt16X16# :: Int16X16# -> (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) unpackInt16X16# = unpackInt16X16# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt32X8# :: Int32X8# -> (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) unpackInt32X8# = unpackInt32X8# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt64X4# :: Int64X4# -> (# Int#,Int#,Int#,Int# #) unpackInt64X4# = unpackInt64X4# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt8X64# :: Int8X64# -> (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) unpackInt8X64# = unpackInt8X64# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt16X32# :: Int16X32# -> (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) unpackInt16X32# = unpackInt16X32# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt32X16# :: Int32X16# -> (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) unpackInt32X16# = unpackInt32X16# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackInt64X8# :: Int64X8# -> (# Int#,Int#,Int#,Int#,Int#,Int#,Int#,Int# #) unpackInt64X8# = unpackInt64X8# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord8X16# :: Word8X16# -> (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) unpackWord8X16# = unpackWord8X16# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord16X8# :: Word16X8# -> (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) unpackWord16X8# = unpackWord16X8# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord32X4# :: Word32X4# -> (# Word#,Word#,Word#,Word# #) unpackWord32X4# = unpackWord32X4# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord64X2# :: Word64X2# -> (# Word#,Word# #) unpackWord64X2# = unpackWord64X2# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord8X32# :: Word8X32# -> (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) unpackWord8X32# = unpackWord8X32# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord16X16# :: Word16X16# -> (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) unpackWord16X16# = unpackWord16X16# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord32X8# :: Word32X8# -> (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) unpackWord32X8# = unpackWord32X8# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord64X4# :: Word64X4# -> (# Word#,Word#,Word#,Word# #) unpackWord64X4# = unpackWord64X4# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord8X64# :: Word8X64# -> (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) unpackWord8X64# = unpackWord8X64# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord16X32# :: Word16X32# -> (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) unpackWord16X32# = unpackWord16X32# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord32X16# :: Word32X16# -> (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) unpackWord32X16# = unpackWord32X16# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackWord64X8# :: Word64X8# -> (# Word#,Word#,Word#,Word#,Word#,Word#,Word#,Word# #) unpackWord64X8# = unpackWord64X8# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackFloatX4# :: FloatX4# -> (# Float#,Float#,Float#,Float# #) unpackFloatX4# = unpackFloatX4# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackDoubleX2# :: DoubleX2# -> (# Double#,Double# #) unpackDoubleX2# = unpackDoubleX2# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackFloatX8# :: FloatX8# -> (# Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float# #) unpackFloatX8# = unpackFloatX8# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackDoubleX4# :: DoubleX4# -> (# Double#,Double#,Double#,Double# #) unpackDoubleX4# = unpackDoubleX4# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackFloatX16# :: FloatX16# -> (# Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float#,Float# #) unpackFloatX16# = unpackFloatX16# -- | Unpack the elements of a vector into an unboxed tuple. # -- -- __/Warning:/__ this is only available on LLVM. unpackDoubleX8# :: DoubleX8# -> (# Double#,Double#,Double#,Double#,Double#,Double#,Double#,Double# #) unpackDoubleX8# = unpackDoubleX8# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt8X16# :: Int8X16# -> Int# -> Int# -> Int8X16# insertInt8X16# = insertInt8X16# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt16X8# :: Int16X8# -> Int# -> Int# -> Int16X8# insertInt16X8# = insertInt16X8# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt32X4# :: Int32X4# -> Int# -> Int# -> Int32X4# insertInt32X4# = insertInt32X4# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt64X2# :: Int64X2# -> Int# -> Int# -> Int64X2# insertInt64X2# = insertInt64X2# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt8X32# :: Int8X32# -> Int# -> Int# -> Int8X32# insertInt8X32# = insertInt8X32# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt16X16# :: Int16X16# -> Int# -> Int# -> Int16X16# insertInt16X16# = insertInt16X16# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt32X8# :: Int32X8# -> Int# -> Int# -> Int32X8# insertInt32X8# = insertInt32X8# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt64X4# :: Int64X4# -> Int# -> Int# -> Int64X4# insertInt64X4# = insertInt64X4# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt8X64# :: Int8X64# -> Int# -> Int# -> Int8X64# insertInt8X64# = insertInt8X64# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt16X32# :: Int16X32# -> Int# -> Int# -> Int16X32# insertInt16X32# = insertInt16X32# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt32X16# :: Int32X16# -> Int# -> Int# -> Int32X16# insertInt32X16# = insertInt32X16# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertInt64X8# :: Int64X8# -> Int# -> Int# -> Int64X8# insertInt64X8# = insertInt64X8# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord8X16# :: Word8X16# -> Word# -> Int# -> Word8X16# insertWord8X16# = insertWord8X16# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord16X8# :: Word16X8# -> Word# -> Int# -> Word16X8# insertWord16X8# = insertWord16X8# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord32X4# :: Word32X4# -> Word# -> Int# -> Word32X4# insertWord32X4# = insertWord32X4# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord64X2# :: Word64X2# -> Word# -> Int# -> Word64X2# insertWord64X2# = insertWord64X2# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord8X32# :: Word8X32# -> Word# -> Int# -> Word8X32# insertWord8X32# = insertWord8X32# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord16X16# :: Word16X16# -> Word# -> Int# -> Word16X16# insertWord16X16# = insertWord16X16# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord32X8# :: Word32X8# -> Word# -> Int# -> Word32X8# insertWord32X8# = insertWord32X8# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord64X4# :: Word64X4# -> Word# -> Int# -> Word64X4# insertWord64X4# = insertWord64X4# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord8X64# :: Word8X64# -> Word# -> Int# -> Word8X64# insertWord8X64# = insertWord8X64# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord16X32# :: Word16X32# -> Word# -> Int# -> Word16X32# insertWord16X32# = insertWord16X32# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord32X16# :: Word32X16# -> Word# -> Int# -> Word32X16# insertWord32X16# = insertWord32X16# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertWord64X8# :: Word64X8# -> Word# -> Int# -> Word64X8# insertWord64X8# = insertWord64X8# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertFloatX4# :: FloatX4# -> Float# -> Int# -> FloatX4# insertFloatX4# = insertFloatX4# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertDoubleX2# :: DoubleX2# -> Double# -> Int# -> DoubleX2# insertDoubleX2# = insertDoubleX2# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertFloatX8# :: FloatX8# -> Float# -> Int# -> FloatX8# insertFloatX8# = insertFloatX8# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertDoubleX4# :: DoubleX4# -> Double# -> Int# -> DoubleX4# insertDoubleX4# = insertDoubleX4# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertFloatX16# :: FloatX16# -> Float# -> Int# -> FloatX16# insertFloatX16# = insertFloatX16# -- | Insert a scalar at the given position in a vector. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. insertDoubleX8# :: DoubleX8# -> Double# -> Int# -> DoubleX8# insertDoubleX8# = insertDoubleX8# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# plusInt8X16# = plusInt8X16# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# plusInt16X8# = plusInt16X8# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# plusInt32X4# = plusInt32X4# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# plusInt64X2# = plusInt64X2# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# plusInt8X32# = plusInt8X32# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# plusInt16X16# = plusInt16X16# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# plusInt32X8# = plusInt32X8# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# plusInt64X4# = plusInt64X4# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# plusInt8X64# = plusInt8X64# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# plusInt16X32# = plusInt16X32# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# plusInt32X16# = plusInt32X16# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# plusInt64X8# = plusInt64X8# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# plusWord8X16# = plusWord8X16# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# plusWord16X8# = plusWord16X8# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# plusWord32X4# = plusWord32X4# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# plusWord64X2# = plusWord64X2# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# plusWord8X32# = plusWord8X32# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# plusWord16X16# = plusWord16X16# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# plusWord32X8# = plusWord32X8# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# plusWord64X4# = plusWord64X4# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# plusWord8X64# = plusWord8X64# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# plusWord16X32# = plusWord16X32# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# plusWord32X16# = plusWord32X16# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# plusWord64X8# = plusWord64X8# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# plusFloatX4# = plusFloatX4# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# plusDoubleX2# = plusDoubleX2# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# plusFloatX8# = plusFloatX8# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# plusDoubleX4# = plusDoubleX4# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# plusFloatX16# = plusFloatX16# -- | Add two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. plusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# plusDoubleX8# = plusDoubleX8# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# minusInt8X16# = minusInt8X16# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# minusInt16X8# = minusInt16X8# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# minusInt32X4# = minusInt32X4# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# minusInt64X2# = minusInt64X2# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# minusInt8X32# = minusInt8X32# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# minusInt16X16# = minusInt16X16# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# minusInt32X8# = minusInt32X8# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# minusInt64X4# = minusInt64X4# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# minusInt8X64# = minusInt8X64# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# minusInt16X32# = minusInt16X32# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# minusInt32X16# = minusInt32X16# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# minusInt64X8# = minusInt64X8# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# minusWord8X16# = minusWord8X16# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# minusWord16X8# = minusWord16X8# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# minusWord32X4# = minusWord32X4# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# minusWord64X2# = minusWord64X2# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# minusWord8X32# = minusWord8X32# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# minusWord16X16# = minusWord16X16# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# minusWord32X8# = minusWord32X8# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# minusWord64X4# = minusWord64X4# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# minusWord8X64# = minusWord8X64# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# minusWord16X32# = minusWord16X32# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# minusWord32X16# = minusWord32X16# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# minusWord64X8# = minusWord64X8# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# minusFloatX4# = minusFloatX4# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# minusDoubleX2# = minusDoubleX2# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# minusFloatX8# = minusFloatX8# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# minusDoubleX4# = minusDoubleX4# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# minusFloatX16# = minusFloatX16# -- | Subtract two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. minusDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# minusDoubleX8# = minusDoubleX8# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# timesInt8X16# = timesInt8X16# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# timesInt16X8# = timesInt16X8# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# timesInt32X4# = timesInt32X4# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# timesInt64X2# = timesInt64X2# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# timesInt8X32# = timesInt8X32# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# timesInt16X16# = timesInt16X16# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# timesInt32X8# = timesInt32X8# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# timesInt64X4# = timesInt64X4# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# timesInt8X64# = timesInt8X64# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# timesInt16X32# = timesInt16X32# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# timesInt32X16# = timesInt32X16# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# timesInt64X8# = timesInt64X8# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# timesWord8X16# = timesWord8X16# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# timesWord16X8# = timesWord16X8# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# timesWord32X4# = timesWord32X4# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# timesWord64X2# = timesWord64X2# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# timesWord8X32# = timesWord8X32# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# timesWord16X16# = timesWord16X16# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# timesWord32X8# = timesWord32X8# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# timesWord64X4# = timesWord64X4# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# timesWord8X64# = timesWord8X64# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# timesWord16X32# = timesWord16X32# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# timesWord32X16# = timesWord32X16# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# timesWord64X8# = timesWord64X8# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# timesFloatX4# = timesFloatX4# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# timesDoubleX2# = timesDoubleX2# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# timesFloatX8# = timesFloatX8# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# timesDoubleX4# = timesDoubleX4# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# timesFloatX16# = timesFloatX16# -- | Multiply two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM. timesDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# timesDoubleX8# = timesDoubleX8# -- | Divide two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. divideFloatX4# :: FloatX4# -> FloatX4# -> FloatX4# divideFloatX4# = divideFloatX4# -- | Divide two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. divideDoubleX2# :: DoubleX2# -> DoubleX2# -> DoubleX2# divideDoubleX2# = divideDoubleX2# -- | Divide two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. divideFloatX8# :: FloatX8# -> FloatX8# -> FloatX8# divideFloatX8# = divideFloatX8# -- | Divide two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. divideDoubleX4# :: DoubleX4# -> DoubleX4# -> DoubleX4# divideDoubleX4# = divideDoubleX4# -- | Divide two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. divideFloatX16# :: FloatX16# -> FloatX16# -> FloatX16# divideFloatX16# = divideFloatX16# -- | Divide two vectors element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. divideDoubleX8# :: DoubleX8# -> DoubleX8# -> DoubleX8# divideDoubleX8# = divideDoubleX8# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# quotInt8X16# = quotInt8X16# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# quotInt16X8# = quotInt16X8# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# quotInt32X4# = quotInt32X4# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# quotInt64X2# = quotInt64X2# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# quotInt8X32# = quotInt8X32# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# quotInt16X16# = quotInt16X16# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# quotInt32X8# = quotInt32X8# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# quotInt64X4# = quotInt64X4# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# quotInt8X64# = quotInt8X64# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# quotInt16X32# = quotInt16X32# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# quotInt32X16# = quotInt32X16# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# quotInt64X8# = quotInt64X8# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# quotWord8X16# = quotWord8X16# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# quotWord16X8# = quotWord16X8# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# quotWord32X4# = quotWord32X4# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# quotWord64X2# = quotWord64X2# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# quotWord8X32# = quotWord8X32# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# quotWord16X16# = quotWord16X16# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# quotWord32X8# = quotWord32X8# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# quotWord64X4# = quotWord64X4# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# quotWord8X64# = quotWord8X64# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# quotWord16X32# = quotWord16X32# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# quotWord32X16# = quotWord32X16# -- | Rounds towards zero element-wise. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. quotWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# quotWord64X8# = quotWord64X8# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt8X16# :: Int8X16# -> Int8X16# -> Int8X16# remInt8X16# = remInt8X16# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt16X8# :: Int16X8# -> Int16X8# -> Int16X8# remInt16X8# = remInt16X8# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt32X4# :: Int32X4# -> Int32X4# -> Int32X4# remInt32X4# = remInt32X4# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt64X2# :: Int64X2# -> Int64X2# -> Int64X2# remInt64X2# = remInt64X2# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt8X32# :: Int8X32# -> Int8X32# -> Int8X32# remInt8X32# = remInt8X32# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt16X16# :: Int16X16# -> Int16X16# -> Int16X16# remInt16X16# = remInt16X16# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt32X8# :: Int32X8# -> Int32X8# -> Int32X8# remInt32X8# = remInt32X8# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt64X4# :: Int64X4# -> Int64X4# -> Int64X4# remInt64X4# = remInt64X4# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt8X64# :: Int8X64# -> Int8X64# -> Int8X64# remInt8X64# = remInt8X64# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt16X32# :: Int16X32# -> Int16X32# -> Int16X32# remInt16X32# = remInt16X32# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt32X16# :: Int32X16# -> Int32X16# -> Int32X16# remInt32X16# = remInt32X16# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remInt64X8# :: Int64X8# -> Int64X8# -> Int64X8# remInt64X8# = remInt64X8# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord8X16# :: Word8X16# -> Word8X16# -> Word8X16# remWord8X16# = remWord8X16# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord16X8# :: Word16X8# -> Word16X8# -> Word16X8# remWord16X8# = remWord16X8# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord32X4# :: Word32X4# -> Word32X4# -> Word32X4# remWord32X4# = remWord32X4# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord64X2# :: Word64X2# -> Word64X2# -> Word64X2# remWord64X2# = remWord64X2# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord8X32# :: Word8X32# -> Word8X32# -> Word8X32# remWord8X32# = remWord8X32# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord16X16# :: Word16X16# -> Word16X16# -> Word16X16# remWord16X16# = remWord16X16# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord32X8# :: Word32X8# -> Word32X8# -> Word32X8# remWord32X8# = remWord32X8# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord64X4# :: Word64X4# -> Word64X4# -> Word64X4# remWord64X4# = remWord64X4# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord8X64# :: Word8X64# -> Word8X64# -> Word8X64# remWord8X64# = remWord8X64# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord16X32# :: Word16X32# -> Word16X32# -> Word16X32# remWord16X32# = remWord16X32# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord32X16# :: Word32X16# -> Word32X16# -> Word32X16# remWord32X16# = remWord32X16# -- | Satisfies @(quot\# x y) times\# y plus\# (rem\# x y) == x@. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. remWord64X8# :: Word64X8# -> Word64X8# -> Word64X8# remWord64X8# = remWord64X8# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt8X16# :: Int8X16# -> Int8X16# negateInt8X16# = negateInt8X16# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt16X8# :: Int16X8# -> Int16X8# negateInt16X8# = negateInt16X8# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt32X4# :: Int32X4# -> Int32X4# negateInt32X4# = negateInt32X4# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt64X2# :: Int64X2# -> Int64X2# negateInt64X2# = negateInt64X2# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt8X32# :: Int8X32# -> Int8X32# negateInt8X32# = negateInt8X32# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt16X16# :: Int16X16# -> Int16X16# negateInt16X16# = negateInt16X16# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt32X8# :: Int32X8# -> Int32X8# negateInt32X8# = negateInt32X8# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt64X4# :: Int64X4# -> Int64X4# negateInt64X4# = negateInt64X4# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt8X64# :: Int8X64# -> Int8X64# negateInt8X64# = negateInt8X64# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt16X32# :: Int16X32# -> Int16X32# negateInt16X32# = negateInt16X32# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt32X16# :: Int32X16# -> Int32X16# negateInt32X16# = negateInt32X16# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateInt64X8# :: Int64X8# -> Int64X8# negateInt64X8# = negateInt64X8# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateFloatX4# :: FloatX4# -> FloatX4# negateFloatX4# = negateFloatX4# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateDoubleX2# :: DoubleX2# -> DoubleX2# negateDoubleX2# = negateDoubleX2# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateFloatX8# :: FloatX8# -> FloatX8# negateFloatX8# = negateFloatX8# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateDoubleX4# :: DoubleX4# -> DoubleX4# negateDoubleX4# = negateDoubleX4# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateFloatX16# :: FloatX16# -> FloatX16# negateFloatX16# = negateFloatX16# -- | Negate element-wise. -- -- __/Warning:/__ this is only available on LLVM. negateDoubleX8# :: DoubleX8# -> DoubleX8# negateDoubleX8# = negateDoubleX8# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8X16Array# :: ByteArray# -> Int# -> Int8X16# indexInt8X16Array# = indexInt8X16Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16X8Array# :: ByteArray# -> Int# -> Int16X8# indexInt16X8Array# = indexInt16X8Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32X4Array# :: ByteArray# -> Int# -> Int32X4# indexInt32X4Array# = indexInt32X4Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64X2Array# :: ByteArray# -> Int# -> Int64X2# indexInt64X2Array# = indexInt64X2Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8X32Array# :: ByteArray# -> Int# -> Int8X32# indexInt8X32Array# = indexInt8X32Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16X16Array# :: ByteArray# -> Int# -> Int16X16# indexInt16X16Array# = indexInt16X16Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32X8Array# :: ByteArray# -> Int# -> Int32X8# indexInt32X8Array# = indexInt32X8Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64X4Array# :: ByteArray# -> Int# -> Int64X4# indexInt64X4Array# = indexInt64X4Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8X64Array# :: ByteArray# -> Int# -> Int8X64# indexInt8X64Array# = indexInt8X64Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16X32Array# :: ByteArray# -> Int# -> Int16X32# indexInt16X32Array# = indexInt16X32Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32X16Array# :: ByteArray# -> Int# -> Int32X16# indexInt32X16Array# = indexInt32X16Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64X8Array# :: ByteArray# -> Int# -> Int64X8# indexInt64X8Array# = indexInt64X8Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8X16Array# :: ByteArray# -> Int# -> Word8X16# indexWord8X16Array# = indexWord8X16Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16X8Array# :: ByteArray# -> Int# -> Word16X8# indexWord16X8Array# = indexWord16X8Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32X4Array# :: ByteArray# -> Int# -> Word32X4# indexWord32X4Array# = indexWord32X4Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64X2Array# :: ByteArray# -> Int# -> Word64X2# indexWord64X2Array# = indexWord64X2Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8X32Array# :: ByteArray# -> Int# -> Word8X32# indexWord8X32Array# = indexWord8X32Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16X16Array# :: ByteArray# -> Int# -> Word16X16# indexWord16X16Array# = indexWord16X16Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32X8Array# :: ByteArray# -> Int# -> Word32X8# indexWord32X8Array# = indexWord32X8Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64X4Array# :: ByteArray# -> Int# -> Word64X4# indexWord64X4Array# = indexWord64X4Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8X64Array# :: ByteArray# -> Int# -> Word8X64# indexWord8X64Array# = indexWord8X64Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16X32Array# :: ByteArray# -> Int# -> Word16X32# indexWord16X32Array# = indexWord16X32Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32X16Array# :: ByteArray# -> Int# -> Word32X16# indexWord32X16Array# = indexWord32X16Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64X8Array# :: ByteArray# -> Int# -> Word64X8# indexWord64X8Array# = indexWord64X8Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatX4Array# :: ByteArray# -> Int# -> FloatX4# indexFloatX4Array# = indexFloatX4Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleX2Array# :: ByteArray# -> Int# -> DoubleX2# indexDoubleX2Array# = indexDoubleX2Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatX8Array# :: ByteArray# -> Int# -> FloatX8# indexFloatX8Array# = indexFloatX8Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleX4Array# :: ByteArray# -> Int# -> DoubleX4# indexDoubleX4Array# = indexDoubleX4Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatX16Array# :: ByteArray# -> Int# -> FloatX16# indexFloatX16Array# = indexFloatX16Array# -- | Read a vector from specified index of immutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleX8Array# :: ByteArray# -> Int# -> DoubleX8# indexDoubleX8Array# = indexDoubleX8Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8X16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int8X16# #) readInt8X16Array# = readInt8X16Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16X8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int16X8# #) readInt16X8Array# = readInt16X8Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32X4Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int32X4# #) readInt32X4Array# = readInt32X4Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64X2Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int64X2# #) readInt64X2Array# = readInt64X2Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8X32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int8X32# #) readInt8X32Array# = readInt8X32Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16X16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int16X16# #) readInt16X16Array# = readInt16X16Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32X8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int32X8# #) readInt32X8Array# = readInt32X8Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64X4Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int64X4# #) readInt64X4Array# = readInt64X4Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8X64Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int8X64# #) readInt8X64Array# = readInt8X64Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16X32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int16X32# #) readInt16X32Array# = readInt16X32Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32X16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int32X16# #) readInt32X16Array# = readInt32X16Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64X8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int64X8# #) readInt64X8Array# = readInt64X8Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8X16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word8X16# #) readWord8X16Array# = readWord8X16Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16X8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word16X8# #) readWord16X8Array# = readWord16X8Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32X4Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word32X4# #) readWord32X4Array# = readWord32X4Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64X2Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word64X2# #) readWord64X2Array# = readWord64X2Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8X32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word8X32# #) readWord8X32Array# = readWord8X32Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16X16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word16X16# #) readWord16X16Array# = readWord16X16Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32X8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word32X8# #) readWord32X8Array# = readWord32X8Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64X4Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word64X4# #) readWord64X4Array# = readWord64X4Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8X64Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word8X64# #) readWord8X64Array# = readWord8X64Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16X32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word16X32# #) readWord16X32Array# = readWord16X32Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32X16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word32X16# #) readWord32X16Array# = readWord32X16Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64X8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word64X8# #) readWord64X8Array# = readWord64X8Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatX4Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,FloatX4# #) readFloatX4Array# = readFloatX4Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleX2Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,DoubleX2# #) readDoubleX2Array# = readDoubleX2Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatX8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,FloatX8# #) readFloatX8Array# = readFloatX8Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleX4Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,DoubleX4# #) readDoubleX4Array# = readDoubleX4Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatX16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,FloatX16# #) readFloatX16Array# = readFloatX16Array# -- | Read a vector from specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleX8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,DoubleX8# #) readDoubleX8Array# = readDoubleX8Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8X16Array# :: MutableByteArray# s -> Int# -> Int8X16# -> State# s -> State# s writeInt8X16Array# = writeInt8X16Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16X8Array# :: MutableByteArray# s -> Int# -> Int16X8# -> State# s -> State# s writeInt16X8Array# = writeInt16X8Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32X4Array# :: MutableByteArray# s -> Int# -> Int32X4# -> State# s -> State# s writeInt32X4Array# = writeInt32X4Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64X2Array# :: MutableByteArray# s -> Int# -> Int64X2# -> State# s -> State# s writeInt64X2Array# = writeInt64X2Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8X32Array# :: MutableByteArray# s -> Int# -> Int8X32# -> State# s -> State# s writeInt8X32Array# = writeInt8X32Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16X16Array# :: MutableByteArray# s -> Int# -> Int16X16# -> State# s -> State# s writeInt16X16Array# = writeInt16X16Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32X8Array# :: MutableByteArray# s -> Int# -> Int32X8# -> State# s -> State# s writeInt32X8Array# = writeInt32X8Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64X4Array# :: MutableByteArray# s -> Int# -> Int64X4# -> State# s -> State# s writeInt64X4Array# = writeInt64X4Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8X64Array# :: MutableByteArray# s -> Int# -> Int8X64# -> State# s -> State# s writeInt8X64Array# = writeInt8X64Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16X32Array# :: MutableByteArray# s -> Int# -> Int16X32# -> State# s -> State# s writeInt16X32Array# = writeInt16X32Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32X16Array# :: MutableByteArray# s -> Int# -> Int32X16# -> State# s -> State# s writeInt32X16Array# = writeInt32X16Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64X8Array# :: MutableByteArray# s -> Int# -> Int64X8# -> State# s -> State# s writeInt64X8Array# = writeInt64X8Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8X16Array# :: MutableByteArray# s -> Int# -> Word8X16# -> State# s -> State# s writeWord8X16Array# = writeWord8X16Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16X8Array# :: MutableByteArray# s -> Int# -> Word16X8# -> State# s -> State# s writeWord16X8Array# = writeWord16X8Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32X4Array# :: MutableByteArray# s -> Int# -> Word32X4# -> State# s -> State# s writeWord32X4Array# = writeWord32X4Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64X2Array# :: MutableByteArray# s -> Int# -> Word64X2# -> State# s -> State# s writeWord64X2Array# = writeWord64X2Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8X32Array# :: MutableByteArray# s -> Int# -> Word8X32# -> State# s -> State# s writeWord8X32Array# = writeWord8X32Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16X16Array# :: MutableByteArray# s -> Int# -> Word16X16# -> State# s -> State# s writeWord16X16Array# = writeWord16X16Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32X8Array# :: MutableByteArray# s -> Int# -> Word32X8# -> State# s -> State# s writeWord32X8Array# = writeWord32X8Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64X4Array# :: MutableByteArray# s -> Int# -> Word64X4# -> State# s -> State# s writeWord64X4Array# = writeWord64X4Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8X64Array# :: MutableByteArray# s -> Int# -> Word8X64# -> State# s -> State# s writeWord8X64Array# = writeWord8X64Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16X32Array# :: MutableByteArray# s -> Int# -> Word16X32# -> State# s -> State# s writeWord16X32Array# = writeWord16X32Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32X16Array# :: MutableByteArray# s -> Int# -> Word32X16# -> State# s -> State# s writeWord32X16Array# = writeWord32X16Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64X8Array# :: MutableByteArray# s -> Int# -> Word64X8# -> State# s -> State# s writeWord64X8Array# = writeWord64X8Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatX4Array# :: MutableByteArray# s -> Int# -> FloatX4# -> State# s -> State# s writeFloatX4Array# = writeFloatX4Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleX2Array# :: MutableByteArray# s -> Int# -> DoubleX2# -> State# s -> State# s writeDoubleX2Array# = writeDoubleX2Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatX8Array# :: MutableByteArray# s -> Int# -> FloatX8# -> State# s -> State# s writeFloatX8Array# = writeFloatX8Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleX4Array# :: MutableByteArray# s -> Int# -> DoubleX4# -> State# s -> State# s writeDoubleX4Array# = writeDoubleX4Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatX16Array# :: MutableByteArray# s -> Int# -> FloatX16# -> State# s -> State# s writeFloatX16Array# = writeFloatX16Array# -- | Write a vector to specified index of mutable array. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleX8Array# :: MutableByteArray# s -> Int# -> DoubleX8# -> State# s -> State# s writeDoubleX8Array# = writeDoubleX8Array# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# indexInt8X16OffAddr# = indexInt8X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# indexInt16X8OffAddr# = indexInt16X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# indexInt32X4OffAddr# = indexInt32X4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# indexInt64X2OffAddr# = indexInt64X2OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# indexInt8X32OffAddr# = indexInt8X32OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# indexInt16X16OffAddr# = indexInt16X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# indexInt32X8OffAddr# = indexInt32X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# indexInt64X4OffAddr# = indexInt64X4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# indexInt8X64OffAddr# = indexInt8X64OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# indexInt16X32OffAddr# = indexInt16X32OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# indexInt32X16OffAddr# = indexInt32X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# indexInt64X8OffAddr# = indexInt64X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# indexWord8X16OffAddr# = indexWord8X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# indexWord16X8OffAddr# = indexWord16X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# indexWord32X4OffAddr# = indexWord32X4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# indexWord64X2OffAddr# = indexWord64X2OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# indexWord8X32OffAddr# = indexWord8X32OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# indexWord16X16OffAddr# = indexWord16X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# indexWord32X8OffAddr# = indexWord32X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# indexWord64X4OffAddr# = indexWord64X4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# indexWord8X64OffAddr# = indexWord8X64OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# indexWord16X32OffAddr# = indexWord16X32OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# indexWord32X16OffAddr# = indexWord32X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# indexWord64X8OffAddr# = indexWord64X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# indexFloatX4OffAddr# = indexFloatX4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# indexDoubleX2OffAddr# = indexDoubleX2OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# indexFloatX8OffAddr# = indexFloatX8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# indexDoubleX4OffAddr# = indexDoubleX4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# indexFloatX16OffAddr# = indexFloatX16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# indexDoubleX8OffAddr# = indexDoubleX8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8X16OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int8X16# #) readInt8X16OffAddr# = readInt8X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16X8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int16X8# #) readInt16X8OffAddr# = readInt16X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32X4OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int32X4# #) readInt32X4OffAddr# = readInt32X4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64X2OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int64X2# #) readInt64X2OffAddr# = readInt64X2OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8X32OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int8X32# #) readInt8X32OffAddr# = readInt8X32OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16X16OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int16X16# #) readInt16X16OffAddr# = readInt16X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32X8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int32X8# #) readInt32X8OffAddr# = readInt32X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64X4OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int64X4# #) readInt64X4OffAddr# = readInt64X4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8X64OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int8X64# #) readInt8X64OffAddr# = readInt8X64OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16X32OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int16X32# #) readInt16X32OffAddr# = readInt16X32OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32X16OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int32X16# #) readInt32X16OffAddr# = readInt32X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64X8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Int64X8# #) readInt64X8OffAddr# = readInt64X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8X16OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word8X16# #) readWord8X16OffAddr# = readWord8X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16X8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word16X8# #) readWord16X8OffAddr# = readWord16X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32X4OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word32X4# #) readWord32X4OffAddr# = readWord32X4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64X2OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word64X2# #) readWord64X2OffAddr# = readWord64X2OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8X32OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word8X32# #) readWord8X32OffAddr# = readWord8X32OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16X16OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word16X16# #) readWord16X16OffAddr# = readWord16X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32X8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word32X8# #) readWord32X8OffAddr# = readWord32X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64X4OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word64X4# #) readWord64X4OffAddr# = readWord64X4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8X64OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word8X64# #) readWord8X64OffAddr# = readWord8X64OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16X32OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word16X32# #) readWord16X32OffAddr# = readWord16X32OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32X16OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word32X16# #) readWord32X16OffAddr# = readWord32X16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64X8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,Word64X8# #) readWord64X8OffAddr# = readWord64X8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatX4OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,FloatX4# #) readFloatX4OffAddr# = readFloatX4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleX2OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,DoubleX2# #) readDoubleX2OffAddr# = readDoubleX2OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatX8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,FloatX8# #) readFloatX8OffAddr# = readFloatX8OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleX4OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,DoubleX4# #) readDoubleX4OffAddr# = readDoubleX4OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatX16OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,FloatX16# #) readFloatX16OffAddr# = readFloatX16OffAddr# -- | Reads vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleX8OffAddr# :: Addr# -> Int# -> State# s -> (# State# s,DoubleX8# #) readDoubleX8OffAddr# = readDoubleX8OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8X16OffAddr# :: Addr# -> Int# -> Int8X16# -> State# s -> State# s writeInt8X16OffAddr# = writeInt8X16OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16X8OffAddr# :: Addr# -> Int# -> Int16X8# -> State# s -> State# s writeInt16X8OffAddr# = writeInt16X8OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32X4OffAddr# :: Addr# -> Int# -> Int32X4# -> State# s -> State# s writeInt32X4OffAddr# = writeInt32X4OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64X2OffAddr# :: Addr# -> Int# -> Int64X2# -> State# s -> State# s writeInt64X2OffAddr# = writeInt64X2OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8X32OffAddr# :: Addr# -> Int# -> Int8X32# -> State# s -> State# s writeInt8X32OffAddr# = writeInt8X32OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16X16OffAddr# :: Addr# -> Int# -> Int16X16# -> State# s -> State# s writeInt16X16OffAddr# = writeInt16X16OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32X8OffAddr# :: Addr# -> Int# -> Int32X8# -> State# s -> State# s writeInt32X8OffAddr# = writeInt32X8OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64X4OffAddr# :: Addr# -> Int# -> Int64X4# -> State# s -> State# s writeInt64X4OffAddr# = writeInt64X4OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8X64OffAddr# :: Addr# -> Int# -> Int8X64# -> State# s -> State# s writeInt8X64OffAddr# = writeInt8X64OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16X32OffAddr# :: Addr# -> Int# -> Int16X32# -> State# s -> State# s writeInt16X32OffAddr# = writeInt16X32OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32X16OffAddr# :: Addr# -> Int# -> Int32X16# -> State# s -> State# s writeInt32X16OffAddr# = writeInt32X16OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64X8OffAddr# :: Addr# -> Int# -> Int64X8# -> State# s -> State# s writeInt64X8OffAddr# = writeInt64X8OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8X16OffAddr# :: Addr# -> Int# -> Word8X16# -> State# s -> State# s writeWord8X16OffAddr# = writeWord8X16OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16X8OffAddr# :: Addr# -> Int# -> Word16X8# -> State# s -> State# s writeWord16X8OffAddr# = writeWord16X8OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32X4OffAddr# :: Addr# -> Int# -> Word32X4# -> State# s -> State# s writeWord32X4OffAddr# = writeWord32X4OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64X2OffAddr# :: Addr# -> Int# -> Word64X2# -> State# s -> State# s writeWord64X2OffAddr# = writeWord64X2OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8X32OffAddr# :: Addr# -> Int# -> Word8X32# -> State# s -> State# s writeWord8X32OffAddr# = writeWord8X32OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16X16OffAddr# :: Addr# -> Int# -> Word16X16# -> State# s -> State# s writeWord16X16OffAddr# = writeWord16X16OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32X8OffAddr# :: Addr# -> Int# -> Word32X8# -> State# s -> State# s writeWord32X8OffAddr# = writeWord32X8OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64X4OffAddr# :: Addr# -> Int# -> Word64X4# -> State# s -> State# s writeWord64X4OffAddr# = writeWord64X4OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8X64OffAddr# :: Addr# -> Int# -> Word8X64# -> State# s -> State# s writeWord8X64OffAddr# = writeWord8X64OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16X32OffAddr# :: Addr# -> Int# -> Word16X32# -> State# s -> State# s writeWord16X32OffAddr# = writeWord16X32OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32X16OffAddr# :: Addr# -> Int# -> Word32X16# -> State# s -> State# s writeWord32X16OffAddr# = writeWord32X16OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64X8OffAddr# :: Addr# -> Int# -> Word64X8# -> State# s -> State# s writeWord64X8OffAddr# = writeWord64X8OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatX4OffAddr# :: Addr# -> Int# -> FloatX4# -> State# s -> State# s writeFloatX4OffAddr# = writeFloatX4OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleX2OffAddr# :: Addr# -> Int# -> DoubleX2# -> State# s -> State# s writeDoubleX2OffAddr# = writeDoubleX2OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatX8OffAddr# :: Addr# -> Int# -> FloatX8# -> State# s -> State# s writeFloatX8OffAddr# = writeFloatX8OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleX4OffAddr# :: Addr# -> Int# -> DoubleX4# -> State# s -> State# s writeDoubleX4OffAddr# = writeDoubleX4OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatX16OffAddr# :: Addr# -> Int# -> FloatX16# -> State# s -> State# s writeFloatX16OffAddr# = writeFloatX16OffAddr# -- | Write vector; offset in bytes. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleX8OffAddr# :: Addr# -> Int# -> DoubleX8# -> State# s -> State# s writeDoubleX8OffAddr# = writeDoubleX8OffAddr# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8ArrayAsInt8X16# :: ByteArray# -> Int# -> Int8X16# indexInt8ArrayAsInt8X16# = indexInt8ArrayAsInt8X16# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16ArrayAsInt16X8# :: ByteArray# -> Int# -> Int16X8# indexInt16ArrayAsInt16X8# = indexInt16ArrayAsInt16X8# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32ArrayAsInt32X4# :: ByteArray# -> Int# -> Int32X4# indexInt32ArrayAsInt32X4# = indexInt32ArrayAsInt32X4# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64ArrayAsInt64X2# :: ByteArray# -> Int# -> Int64X2# indexInt64ArrayAsInt64X2# = indexInt64ArrayAsInt64X2# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8ArrayAsInt8X32# :: ByteArray# -> Int# -> Int8X32# indexInt8ArrayAsInt8X32# = indexInt8ArrayAsInt8X32# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16ArrayAsInt16X16# :: ByteArray# -> Int# -> Int16X16# indexInt16ArrayAsInt16X16# = indexInt16ArrayAsInt16X16# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32ArrayAsInt32X8# :: ByteArray# -> Int# -> Int32X8# indexInt32ArrayAsInt32X8# = indexInt32ArrayAsInt32X8# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64ArrayAsInt64X4# :: ByteArray# -> Int# -> Int64X4# indexInt64ArrayAsInt64X4# = indexInt64ArrayAsInt64X4# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8ArrayAsInt8X64# :: ByteArray# -> Int# -> Int8X64# indexInt8ArrayAsInt8X64# = indexInt8ArrayAsInt8X64# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16ArrayAsInt16X32# :: ByteArray# -> Int# -> Int16X32# indexInt16ArrayAsInt16X32# = indexInt16ArrayAsInt16X32# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32ArrayAsInt32X16# :: ByteArray# -> Int# -> Int32X16# indexInt32ArrayAsInt32X16# = indexInt32ArrayAsInt32X16# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64ArrayAsInt64X8# :: ByteArray# -> Int# -> Int64X8# indexInt64ArrayAsInt64X8# = indexInt64ArrayAsInt64X8# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8ArrayAsWord8X16# :: ByteArray# -> Int# -> Word8X16# indexWord8ArrayAsWord8X16# = indexWord8ArrayAsWord8X16# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16ArrayAsWord16X8# :: ByteArray# -> Int# -> Word16X8# indexWord16ArrayAsWord16X8# = indexWord16ArrayAsWord16X8# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32ArrayAsWord32X4# :: ByteArray# -> Int# -> Word32X4# indexWord32ArrayAsWord32X4# = indexWord32ArrayAsWord32X4# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64ArrayAsWord64X2# :: ByteArray# -> Int# -> Word64X2# indexWord64ArrayAsWord64X2# = indexWord64ArrayAsWord64X2# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8ArrayAsWord8X32# :: ByteArray# -> Int# -> Word8X32# indexWord8ArrayAsWord8X32# = indexWord8ArrayAsWord8X32# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16ArrayAsWord16X16# :: ByteArray# -> Int# -> Word16X16# indexWord16ArrayAsWord16X16# = indexWord16ArrayAsWord16X16# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32ArrayAsWord32X8# :: ByteArray# -> Int# -> Word32X8# indexWord32ArrayAsWord32X8# = indexWord32ArrayAsWord32X8# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64ArrayAsWord64X4# :: ByteArray# -> Int# -> Word64X4# indexWord64ArrayAsWord64X4# = indexWord64ArrayAsWord64X4# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8ArrayAsWord8X64# :: ByteArray# -> Int# -> Word8X64# indexWord8ArrayAsWord8X64# = indexWord8ArrayAsWord8X64# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16ArrayAsWord16X32# :: ByteArray# -> Int# -> Word16X32# indexWord16ArrayAsWord16X32# = indexWord16ArrayAsWord16X32# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32ArrayAsWord32X16# :: ByteArray# -> Int# -> Word32X16# indexWord32ArrayAsWord32X16# = indexWord32ArrayAsWord32X16# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64ArrayAsWord64X8# :: ByteArray# -> Int# -> Word64X8# indexWord64ArrayAsWord64X8# = indexWord64ArrayAsWord64X8# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatArrayAsFloatX4# :: ByteArray# -> Int# -> FloatX4# indexFloatArrayAsFloatX4# = indexFloatArrayAsFloatX4# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleArrayAsDoubleX2# :: ByteArray# -> Int# -> DoubleX2# indexDoubleArrayAsDoubleX2# = indexDoubleArrayAsDoubleX2# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatArrayAsFloatX8# :: ByteArray# -> Int# -> FloatX8# indexFloatArrayAsFloatX8# = indexFloatArrayAsFloatX8# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleArrayAsDoubleX4# :: ByteArray# -> Int# -> DoubleX4# indexDoubleArrayAsDoubleX4# = indexDoubleArrayAsDoubleX4# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatArrayAsFloatX16# :: ByteArray# -> Int# -> FloatX16# indexFloatArrayAsFloatX16# = indexFloatArrayAsFloatX16# -- | Read a vector from specified index of immutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleArrayAsDoubleX8# :: ByteArray# -> Int# -> DoubleX8# indexDoubleArrayAsDoubleX8# = indexDoubleArrayAsDoubleX8# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8ArrayAsInt8X16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int8X16# #) readInt8ArrayAsInt8X16# = readInt8ArrayAsInt8X16# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16ArrayAsInt16X8# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int16X8# #) readInt16ArrayAsInt16X8# = readInt16ArrayAsInt16X8# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32ArrayAsInt32X4# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int32X4# #) readInt32ArrayAsInt32X4# = readInt32ArrayAsInt32X4# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64ArrayAsInt64X2# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int64X2# #) readInt64ArrayAsInt64X2# = readInt64ArrayAsInt64X2# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8ArrayAsInt8X32# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int8X32# #) readInt8ArrayAsInt8X32# = readInt8ArrayAsInt8X32# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16ArrayAsInt16X16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int16X16# #) readInt16ArrayAsInt16X16# = readInt16ArrayAsInt16X16# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32ArrayAsInt32X8# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int32X8# #) readInt32ArrayAsInt32X8# = readInt32ArrayAsInt32X8# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64ArrayAsInt64X4# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int64X4# #) readInt64ArrayAsInt64X4# = readInt64ArrayAsInt64X4# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8ArrayAsInt8X64# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int8X64# #) readInt8ArrayAsInt8X64# = readInt8ArrayAsInt8X64# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16ArrayAsInt16X32# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int16X32# #) readInt16ArrayAsInt16X32# = readInt16ArrayAsInt16X32# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32ArrayAsInt32X16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int32X16# #) readInt32ArrayAsInt32X16# = readInt32ArrayAsInt32X16# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64ArrayAsInt64X8# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int64X8# #) readInt64ArrayAsInt64X8# = readInt64ArrayAsInt64X8# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8ArrayAsWord8X16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word8X16# #) readWord8ArrayAsWord8X16# = readWord8ArrayAsWord8X16# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16ArrayAsWord16X8# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word16X8# #) readWord16ArrayAsWord16X8# = readWord16ArrayAsWord16X8# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32ArrayAsWord32X4# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word32X4# #) readWord32ArrayAsWord32X4# = readWord32ArrayAsWord32X4# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64ArrayAsWord64X2# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word64X2# #) readWord64ArrayAsWord64X2# = readWord64ArrayAsWord64X2# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8ArrayAsWord8X32# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word8X32# #) readWord8ArrayAsWord8X32# = readWord8ArrayAsWord8X32# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16ArrayAsWord16X16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word16X16# #) readWord16ArrayAsWord16X16# = readWord16ArrayAsWord16X16# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32ArrayAsWord32X8# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word32X8# #) readWord32ArrayAsWord32X8# = readWord32ArrayAsWord32X8# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64ArrayAsWord64X4# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word64X4# #) readWord64ArrayAsWord64X4# = readWord64ArrayAsWord64X4# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8ArrayAsWord8X64# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word8X64# #) readWord8ArrayAsWord8X64# = readWord8ArrayAsWord8X64# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16ArrayAsWord16X32# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word16X32# #) readWord16ArrayAsWord16X32# = readWord16ArrayAsWord16X32# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32ArrayAsWord32X16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word32X16# #) readWord32ArrayAsWord32X16# = readWord32ArrayAsWord32X16# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64ArrayAsWord64X8# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word64X8# #) readWord64ArrayAsWord64X8# = readWord64ArrayAsWord64X8# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatArrayAsFloatX4# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,FloatX4# #) readFloatArrayAsFloatX4# = readFloatArrayAsFloatX4# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleArrayAsDoubleX2# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,DoubleX2# #) readDoubleArrayAsDoubleX2# = readDoubleArrayAsDoubleX2# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatArrayAsFloatX8# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,FloatX8# #) readFloatArrayAsFloatX8# = readFloatArrayAsFloatX8# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleArrayAsDoubleX4# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,DoubleX4# #) readDoubleArrayAsDoubleX4# = readDoubleArrayAsDoubleX4# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatArrayAsFloatX16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,FloatX16# #) readFloatArrayAsFloatX16# = readFloatArrayAsFloatX16# -- | Read a vector from specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleArrayAsDoubleX8# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,DoubleX8# #) readDoubleArrayAsDoubleX8# = readDoubleArrayAsDoubleX8# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8ArrayAsInt8X16# :: MutableByteArray# s -> Int# -> Int8X16# -> State# s -> State# s writeInt8ArrayAsInt8X16# = writeInt8ArrayAsInt8X16# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16ArrayAsInt16X8# :: MutableByteArray# s -> Int# -> Int16X8# -> State# s -> State# s writeInt16ArrayAsInt16X8# = writeInt16ArrayAsInt16X8# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32ArrayAsInt32X4# :: MutableByteArray# s -> Int# -> Int32X4# -> State# s -> State# s writeInt32ArrayAsInt32X4# = writeInt32ArrayAsInt32X4# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64ArrayAsInt64X2# :: MutableByteArray# s -> Int# -> Int64X2# -> State# s -> State# s writeInt64ArrayAsInt64X2# = writeInt64ArrayAsInt64X2# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8ArrayAsInt8X32# :: MutableByteArray# s -> Int# -> Int8X32# -> State# s -> State# s writeInt8ArrayAsInt8X32# = writeInt8ArrayAsInt8X32# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16ArrayAsInt16X16# :: MutableByteArray# s -> Int# -> Int16X16# -> State# s -> State# s writeInt16ArrayAsInt16X16# = writeInt16ArrayAsInt16X16# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32ArrayAsInt32X8# :: MutableByteArray# s -> Int# -> Int32X8# -> State# s -> State# s writeInt32ArrayAsInt32X8# = writeInt32ArrayAsInt32X8# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64ArrayAsInt64X4# :: MutableByteArray# s -> Int# -> Int64X4# -> State# s -> State# s writeInt64ArrayAsInt64X4# = writeInt64ArrayAsInt64X4# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8ArrayAsInt8X64# :: MutableByteArray# s -> Int# -> Int8X64# -> State# s -> State# s writeInt8ArrayAsInt8X64# = writeInt8ArrayAsInt8X64# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16ArrayAsInt16X32# :: MutableByteArray# s -> Int# -> Int16X32# -> State# s -> State# s writeInt16ArrayAsInt16X32# = writeInt16ArrayAsInt16X32# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32ArrayAsInt32X16# :: MutableByteArray# s -> Int# -> Int32X16# -> State# s -> State# s writeInt32ArrayAsInt32X16# = writeInt32ArrayAsInt32X16# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64ArrayAsInt64X8# :: MutableByteArray# s -> Int# -> Int64X8# -> State# s -> State# s writeInt64ArrayAsInt64X8# = writeInt64ArrayAsInt64X8# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8ArrayAsWord8X16# :: MutableByteArray# s -> Int# -> Word8X16# -> State# s -> State# s writeWord8ArrayAsWord8X16# = writeWord8ArrayAsWord8X16# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16ArrayAsWord16X8# :: MutableByteArray# s -> Int# -> Word16X8# -> State# s -> State# s writeWord16ArrayAsWord16X8# = writeWord16ArrayAsWord16X8# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32ArrayAsWord32X4# :: MutableByteArray# s -> Int# -> Word32X4# -> State# s -> State# s writeWord32ArrayAsWord32X4# = writeWord32ArrayAsWord32X4# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64ArrayAsWord64X2# :: MutableByteArray# s -> Int# -> Word64X2# -> State# s -> State# s writeWord64ArrayAsWord64X2# = writeWord64ArrayAsWord64X2# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8ArrayAsWord8X32# :: MutableByteArray# s -> Int# -> Word8X32# -> State# s -> State# s writeWord8ArrayAsWord8X32# = writeWord8ArrayAsWord8X32# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16ArrayAsWord16X16# :: MutableByteArray# s -> Int# -> Word16X16# -> State# s -> State# s writeWord16ArrayAsWord16X16# = writeWord16ArrayAsWord16X16# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32ArrayAsWord32X8# :: MutableByteArray# s -> Int# -> Word32X8# -> State# s -> State# s writeWord32ArrayAsWord32X8# = writeWord32ArrayAsWord32X8# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64ArrayAsWord64X4# :: MutableByteArray# s -> Int# -> Word64X4# -> State# s -> State# s writeWord64ArrayAsWord64X4# = writeWord64ArrayAsWord64X4# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8ArrayAsWord8X64# :: MutableByteArray# s -> Int# -> Word8X64# -> State# s -> State# s writeWord8ArrayAsWord8X64# = writeWord8ArrayAsWord8X64# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16ArrayAsWord16X32# :: MutableByteArray# s -> Int# -> Word16X32# -> State# s -> State# s writeWord16ArrayAsWord16X32# = writeWord16ArrayAsWord16X32# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32ArrayAsWord32X16# :: MutableByteArray# s -> Int# -> Word32X16# -> State# s -> State# s writeWord32ArrayAsWord32X16# = writeWord32ArrayAsWord32X16# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64ArrayAsWord64X8# :: MutableByteArray# s -> Int# -> Word64X8# -> State# s -> State# s writeWord64ArrayAsWord64X8# = writeWord64ArrayAsWord64X8# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatArrayAsFloatX4# :: MutableByteArray# s -> Int# -> FloatX4# -> State# s -> State# s writeFloatArrayAsFloatX4# = writeFloatArrayAsFloatX4# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleArrayAsDoubleX2# :: MutableByteArray# s -> Int# -> DoubleX2# -> State# s -> State# s writeDoubleArrayAsDoubleX2# = writeDoubleArrayAsDoubleX2# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatArrayAsFloatX8# :: MutableByteArray# s -> Int# -> FloatX8# -> State# s -> State# s writeFloatArrayAsFloatX8# = writeFloatArrayAsFloatX8# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleArrayAsDoubleX4# :: MutableByteArray# s -> Int# -> DoubleX4# -> State# s -> State# s writeDoubleArrayAsDoubleX4# = writeDoubleArrayAsDoubleX4# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatArrayAsFloatX16# :: MutableByteArray# s -> Int# -> FloatX16# -> State# s -> State# s writeFloatArrayAsFloatX16# = writeFloatArrayAsFloatX16# -- | Write a vector to specified index of mutable array of scalars; offset is in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleArrayAsDoubleX8# :: MutableByteArray# s -> Int# -> DoubleX8# -> State# s -> State# s writeDoubleArrayAsDoubleX8# = writeDoubleArrayAsDoubleX8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# indexInt8OffAddrAsInt8X16# = indexInt8OffAddrAsInt8X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# indexInt16OffAddrAsInt16X8# = indexInt16OffAddrAsInt16X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# indexInt32OffAddrAsInt32X4# = indexInt32OffAddrAsInt32X4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# indexInt64OffAddrAsInt64X2# = indexInt64OffAddrAsInt64X2# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# indexInt8OffAddrAsInt8X32# = indexInt8OffAddrAsInt8X32# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# indexInt16OffAddrAsInt16X16# = indexInt16OffAddrAsInt16X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# indexInt32OffAddrAsInt32X8# = indexInt32OffAddrAsInt32X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# indexInt64OffAddrAsInt64X4# = indexInt64OffAddrAsInt64X4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# indexInt8OffAddrAsInt8X64# = indexInt8OffAddrAsInt8X64# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# indexInt16OffAddrAsInt16X32# = indexInt16OffAddrAsInt16X32# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# indexInt32OffAddrAsInt32X16# = indexInt32OffAddrAsInt32X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# indexInt64OffAddrAsInt64X8# = indexInt64OffAddrAsInt64X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# indexWord8OffAddrAsWord8X16# = indexWord8OffAddrAsWord8X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# indexWord16OffAddrAsWord16X8# = indexWord16OffAddrAsWord16X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# indexWord32OffAddrAsWord32X4# = indexWord32OffAddrAsWord32X4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# indexWord64OffAddrAsWord64X2# = indexWord64OffAddrAsWord64X2# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# indexWord8OffAddrAsWord8X32# = indexWord8OffAddrAsWord8X32# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# indexWord16OffAddrAsWord16X16# = indexWord16OffAddrAsWord16X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# indexWord32OffAddrAsWord32X8# = indexWord32OffAddrAsWord32X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# indexWord64OffAddrAsWord64X4# = indexWord64OffAddrAsWord64X4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# indexWord8OffAddrAsWord8X64# = indexWord8OffAddrAsWord8X64# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# indexWord16OffAddrAsWord16X32# = indexWord16OffAddrAsWord16X32# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# indexWord32OffAddrAsWord32X16# = indexWord32OffAddrAsWord32X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# indexWord64OffAddrAsWord64X8# = indexWord64OffAddrAsWord64X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# indexFloatOffAddrAsFloatX4# = indexFloatOffAddrAsFloatX4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# indexDoubleOffAddrAsDoubleX2# = indexDoubleOffAddrAsDoubleX2# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# indexFloatOffAddrAsFloatX8# = indexFloatOffAddrAsFloatX8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# indexDoubleOffAddrAsDoubleX4# = indexDoubleOffAddrAsDoubleX4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# indexFloatOffAddrAsFloatX16# = indexFloatOffAddrAsFloatX16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. indexDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# indexDoubleOffAddrAsDoubleX8# = indexDoubleOffAddrAsDoubleX8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8OffAddrAsInt8X16# :: Addr# -> Int# -> State# s -> (# State# s,Int8X16# #) readInt8OffAddrAsInt8X16# = readInt8OffAddrAsInt8X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16OffAddrAsInt16X8# :: Addr# -> Int# -> State# s -> (# State# s,Int16X8# #) readInt16OffAddrAsInt16X8# = readInt16OffAddrAsInt16X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32OffAddrAsInt32X4# :: Addr# -> Int# -> State# s -> (# State# s,Int32X4# #) readInt32OffAddrAsInt32X4# = readInt32OffAddrAsInt32X4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64OffAddrAsInt64X2# :: Addr# -> Int# -> State# s -> (# State# s,Int64X2# #) readInt64OffAddrAsInt64X2# = readInt64OffAddrAsInt64X2# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8OffAddrAsInt8X32# :: Addr# -> Int# -> State# s -> (# State# s,Int8X32# #) readInt8OffAddrAsInt8X32# = readInt8OffAddrAsInt8X32# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16OffAddrAsInt16X16# :: Addr# -> Int# -> State# s -> (# State# s,Int16X16# #) readInt16OffAddrAsInt16X16# = readInt16OffAddrAsInt16X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32OffAddrAsInt32X8# :: Addr# -> Int# -> State# s -> (# State# s,Int32X8# #) readInt32OffAddrAsInt32X8# = readInt32OffAddrAsInt32X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64OffAddrAsInt64X4# :: Addr# -> Int# -> State# s -> (# State# s,Int64X4# #) readInt64OffAddrAsInt64X4# = readInt64OffAddrAsInt64X4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt8OffAddrAsInt8X64# :: Addr# -> Int# -> State# s -> (# State# s,Int8X64# #) readInt8OffAddrAsInt8X64# = readInt8OffAddrAsInt8X64# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt16OffAddrAsInt16X32# :: Addr# -> Int# -> State# s -> (# State# s,Int16X32# #) readInt16OffAddrAsInt16X32# = readInt16OffAddrAsInt16X32# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt32OffAddrAsInt32X16# :: Addr# -> Int# -> State# s -> (# State# s,Int32X16# #) readInt32OffAddrAsInt32X16# = readInt32OffAddrAsInt32X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readInt64OffAddrAsInt64X8# :: Addr# -> Int# -> State# s -> (# State# s,Int64X8# #) readInt64OffAddrAsInt64X8# = readInt64OffAddrAsInt64X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8OffAddrAsWord8X16# :: Addr# -> Int# -> State# s -> (# State# s,Word8X16# #) readWord8OffAddrAsWord8X16# = readWord8OffAddrAsWord8X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16OffAddrAsWord16X8# :: Addr# -> Int# -> State# s -> (# State# s,Word16X8# #) readWord16OffAddrAsWord16X8# = readWord16OffAddrAsWord16X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32OffAddrAsWord32X4# :: Addr# -> Int# -> State# s -> (# State# s,Word32X4# #) readWord32OffAddrAsWord32X4# = readWord32OffAddrAsWord32X4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64OffAddrAsWord64X2# :: Addr# -> Int# -> State# s -> (# State# s,Word64X2# #) readWord64OffAddrAsWord64X2# = readWord64OffAddrAsWord64X2# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8OffAddrAsWord8X32# :: Addr# -> Int# -> State# s -> (# State# s,Word8X32# #) readWord8OffAddrAsWord8X32# = readWord8OffAddrAsWord8X32# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16OffAddrAsWord16X16# :: Addr# -> Int# -> State# s -> (# State# s,Word16X16# #) readWord16OffAddrAsWord16X16# = readWord16OffAddrAsWord16X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32OffAddrAsWord32X8# :: Addr# -> Int# -> State# s -> (# State# s,Word32X8# #) readWord32OffAddrAsWord32X8# = readWord32OffAddrAsWord32X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64OffAddrAsWord64X4# :: Addr# -> Int# -> State# s -> (# State# s,Word64X4# #) readWord64OffAddrAsWord64X4# = readWord64OffAddrAsWord64X4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord8OffAddrAsWord8X64# :: Addr# -> Int# -> State# s -> (# State# s,Word8X64# #) readWord8OffAddrAsWord8X64# = readWord8OffAddrAsWord8X64# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord16OffAddrAsWord16X32# :: Addr# -> Int# -> State# s -> (# State# s,Word16X32# #) readWord16OffAddrAsWord16X32# = readWord16OffAddrAsWord16X32# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord32OffAddrAsWord32X16# :: Addr# -> Int# -> State# s -> (# State# s,Word32X16# #) readWord32OffAddrAsWord32X16# = readWord32OffAddrAsWord32X16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readWord64OffAddrAsWord64X8# :: Addr# -> Int# -> State# s -> (# State# s,Word64X8# #) readWord64OffAddrAsWord64X8# = readWord64OffAddrAsWord64X8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatOffAddrAsFloatX4# :: Addr# -> Int# -> State# s -> (# State# s,FloatX4# #) readFloatOffAddrAsFloatX4# = readFloatOffAddrAsFloatX4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> State# s -> (# State# s,DoubleX2# #) readDoubleOffAddrAsDoubleX2# = readDoubleOffAddrAsDoubleX2# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatOffAddrAsFloatX8# :: Addr# -> Int# -> State# s -> (# State# s,FloatX8# #) readFloatOffAddrAsFloatX8# = readFloatOffAddrAsFloatX8# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> State# s -> (# State# s,DoubleX4# #) readDoubleOffAddrAsDoubleX4# = readDoubleOffAddrAsDoubleX4# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readFloatOffAddrAsFloatX16# :: Addr# -> Int# -> State# s -> (# State# s,FloatX16# #) readFloatOffAddrAsFloatX16# = readFloatOffAddrAsFloatX16# -- | Reads vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. readDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> State# s -> (# State# s,DoubleX8# #) readDoubleOffAddrAsDoubleX8# = readDoubleOffAddrAsDoubleX8# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8OffAddrAsInt8X16# :: Addr# -> Int# -> Int8X16# -> State# s -> State# s writeInt8OffAddrAsInt8X16# = writeInt8OffAddrAsInt8X16# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16OffAddrAsInt16X8# :: Addr# -> Int# -> Int16X8# -> State# s -> State# s writeInt16OffAddrAsInt16X8# = writeInt16OffAddrAsInt16X8# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32OffAddrAsInt32X4# :: Addr# -> Int# -> Int32X4# -> State# s -> State# s writeInt32OffAddrAsInt32X4# = writeInt32OffAddrAsInt32X4# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64OffAddrAsInt64X2# :: Addr# -> Int# -> Int64X2# -> State# s -> State# s writeInt64OffAddrAsInt64X2# = writeInt64OffAddrAsInt64X2# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8OffAddrAsInt8X32# :: Addr# -> Int# -> Int8X32# -> State# s -> State# s writeInt8OffAddrAsInt8X32# = writeInt8OffAddrAsInt8X32# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16OffAddrAsInt16X16# :: Addr# -> Int# -> Int16X16# -> State# s -> State# s writeInt16OffAddrAsInt16X16# = writeInt16OffAddrAsInt16X16# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32OffAddrAsInt32X8# :: Addr# -> Int# -> Int32X8# -> State# s -> State# s writeInt32OffAddrAsInt32X8# = writeInt32OffAddrAsInt32X8# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64OffAddrAsInt64X4# :: Addr# -> Int# -> Int64X4# -> State# s -> State# s writeInt64OffAddrAsInt64X4# = writeInt64OffAddrAsInt64X4# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt8OffAddrAsInt8X64# :: Addr# -> Int# -> Int8X64# -> State# s -> State# s writeInt8OffAddrAsInt8X64# = writeInt8OffAddrAsInt8X64# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt16OffAddrAsInt16X32# :: Addr# -> Int# -> Int16X32# -> State# s -> State# s writeInt16OffAddrAsInt16X32# = writeInt16OffAddrAsInt16X32# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt32OffAddrAsInt32X16# :: Addr# -> Int# -> Int32X16# -> State# s -> State# s writeInt32OffAddrAsInt32X16# = writeInt32OffAddrAsInt32X16# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeInt64OffAddrAsInt64X8# :: Addr# -> Int# -> Int64X8# -> State# s -> State# s writeInt64OffAddrAsInt64X8# = writeInt64OffAddrAsInt64X8# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8OffAddrAsWord8X16# :: Addr# -> Int# -> Word8X16# -> State# s -> State# s writeWord8OffAddrAsWord8X16# = writeWord8OffAddrAsWord8X16# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16OffAddrAsWord16X8# :: Addr# -> Int# -> Word16X8# -> State# s -> State# s writeWord16OffAddrAsWord16X8# = writeWord16OffAddrAsWord16X8# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32OffAddrAsWord32X4# :: Addr# -> Int# -> Word32X4# -> State# s -> State# s writeWord32OffAddrAsWord32X4# = writeWord32OffAddrAsWord32X4# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64OffAddrAsWord64X2# :: Addr# -> Int# -> Word64X2# -> State# s -> State# s writeWord64OffAddrAsWord64X2# = writeWord64OffAddrAsWord64X2# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8OffAddrAsWord8X32# :: Addr# -> Int# -> Word8X32# -> State# s -> State# s writeWord8OffAddrAsWord8X32# = writeWord8OffAddrAsWord8X32# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16OffAddrAsWord16X16# :: Addr# -> Int# -> Word16X16# -> State# s -> State# s writeWord16OffAddrAsWord16X16# = writeWord16OffAddrAsWord16X16# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32OffAddrAsWord32X8# :: Addr# -> Int# -> Word32X8# -> State# s -> State# s writeWord32OffAddrAsWord32X8# = writeWord32OffAddrAsWord32X8# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64OffAddrAsWord64X4# :: Addr# -> Int# -> Word64X4# -> State# s -> State# s writeWord64OffAddrAsWord64X4# = writeWord64OffAddrAsWord64X4# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord8OffAddrAsWord8X64# :: Addr# -> Int# -> Word8X64# -> State# s -> State# s writeWord8OffAddrAsWord8X64# = writeWord8OffAddrAsWord8X64# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord16OffAddrAsWord16X32# :: Addr# -> Int# -> Word16X32# -> State# s -> State# s writeWord16OffAddrAsWord16X32# = writeWord16OffAddrAsWord16X32# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord32OffAddrAsWord32X16# :: Addr# -> Int# -> Word32X16# -> State# s -> State# s writeWord32OffAddrAsWord32X16# = writeWord32OffAddrAsWord32X16# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeWord64OffAddrAsWord64X8# :: Addr# -> Int# -> Word64X8# -> State# s -> State# s writeWord64OffAddrAsWord64X8# = writeWord64OffAddrAsWord64X8# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatOffAddrAsFloatX4# :: Addr# -> Int# -> FloatX4# -> State# s -> State# s writeFloatOffAddrAsFloatX4# = writeFloatOffAddrAsFloatX4# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleOffAddrAsDoubleX2# :: Addr# -> Int# -> DoubleX2# -> State# s -> State# s writeDoubleOffAddrAsDoubleX2# = writeDoubleOffAddrAsDoubleX2# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatOffAddrAsFloatX8# :: Addr# -> Int# -> FloatX8# -> State# s -> State# s writeFloatOffAddrAsFloatX8# = writeFloatOffAddrAsFloatX8# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleOffAddrAsDoubleX4# :: Addr# -> Int# -> DoubleX4# -> State# s -> State# s writeDoubleOffAddrAsDoubleX4# = writeDoubleOffAddrAsDoubleX4# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeFloatOffAddrAsFloatX16# :: Addr# -> Int# -> FloatX16# -> State# s -> State# s writeFloatOffAddrAsFloatX16# = writeFloatOffAddrAsFloatX16# -- | Write vector; offset in scalar elements. -- -- __/Warning:/__ this is only available on LLVM and can fail with an unchecked exception. writeDoubleOffAddrAsDoubleX8# :: Addr# -> Int# -> DoubleX8# -> State# s -> State# s writeDoubleOffAddrAsDoubleX8# = writeDoubleOffAddrAsDoubleX8# prefetchByteArray3# :: ByteArray# -> Int# -> State# s -> State# s prefetchByteArray3# = prefetchByteArray3# prefetchMutableByteArray3# :: MutableByteArray# s -> Int# -> State# s -> State# s prefetchMutableByteArray3# = prefetchMutableByteArray3# prefetchAddr3# :: Addr# -> Int# -> State# s -> State# s prefetchAddr3# = prefetchAddr3# prefetchValue3# :: a -> State# s -> State# s prefetchValue3# = prefetchValue3# prefetchByteArray2# :: ByteArray# -> Int# -> State# s -> State# s prefetchByteArray2# = prefetchByteArray2# prefetchMutableByteArray2# :: MutableByteArray# s -> Int# -> State# s -> State# s prefetchMutableByteArray2# = prefetchMutableByteArray2# prefetchAddr2# :: Addr# -> Int# -> State# s -> State# s prefetchAddr2# = prefetchAddr2# prefetchValue2# :: a -> State# s -> State# s prefetchValue2# = prefetchValue2# prefetchByteArray1# :: ByteArray# -> Int# -> State# s -> State# s prefetchByteArray1# = prefetchByteArray1# prefetchMutableByteArray1# :: MutableByteArray# s -> Int# -> State# s -> State# s prefetchMutableByteArray1# = prefetchMutableByteArray1# prefetchAddr1# :: Addr# -> Int# -> State# s -> State# s prefetchAddr1# = prefetchAddr1# prefetchValue1# :: a -> State# s -> State# s prefetchValue1# = prefetchValue1# prefetchByteArray0# :: ByteArray# -> Int# -> State# s -> State# s prefetchByteArray0# = prefetchByteArray0# prefetchMutableByteArray0# :: MutableByteArray# s -> Int# -> State# s -> State# s prefetchMutableByteArray0# = prefetchMutableByteArray0# prefetchAddr0# :: Addr# -> Int# -> State# s -> State# s prefetchAddr0# = prefetchAddr0# prefetchValue0# :: a -> State# s -> State# s prefetchValue0# = prefetchValue0#