{-
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 #-}
{-# OPTIONS_HADDOCK print-explicit-runtime-reps #-}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.
-- 
--          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.
-- 
--          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#,
        
-- * Int8#
-- |Operations on 8-bit integers.

        Int8#,
        int8ToInt#,
        intToInt8#,
        negateInt8#,
        plusInt8#,
        subInt8#,
        timesInt8#,
        quotInt8#,
        remInt8#,
        quotRemInt8#,
        uncheckedShiftLInt8#,
        uncheckedShiftRAInt8#,
        uncheckedShiftRLInt8#,
        int8ToWord8#,
        eqInt8#,
        geInt8#,
        gtInt8#,
        leInt8#,
        ltInt8#,
        neInt8#,
        
-- * Word8#
-- |Operations on 8-bit unsigned words.

        Word8#,
        word8ToWord#,
        wordToWord8#,
        plusWord8#,
        subWord8#,
        timesWord8#,
        quotWord8#,
        remWord8#,
        quotRemWord8#,
        andWord8#,
        orWord8#,
        xorWord8#,
        notWord8#,
        uncheckedShiftLWord8#,
        uncheckedShiftRLWord8#,
        word8ToInt8#,
        eqWord8#,
        geWord8#,
        gtWord8#,
        leWord8#,
        ltWord8#,
        neWord8#,
        
-- * Int16#
-- |Operations on 16-bit integers.

        Int16#,
        int16ToInt#,
        intToInt16#,
        negateInt16#,
        plusInt16#,
        subInt16#,
        timesInt16#,
        quotInt16#,
        remInt16#,
        quotRemInt16#,
        uncheckedShiftLInt16#,
        uncheckedShiftRAInt16#,
        uncheckedShiftRLInt16#,
        int16ToWord16#,
        eqInt16#,
        geInt16#,
        gtInt16#,
        leInt16#,
        ltInt16#,
        neInt16#,
        
-- * Word16#
-- |Operations on 16-bit unsigned words.

        Word16#,
        word16ToWord#,
        wordToWord16#,
        plusWord16#,
        subWord16#,
        timesWord16#,
        quotWord16#,
        remWord16#,
        quotRemWord16#,
        andWord16#,
        orWord16#,
        xorWord16#,
        notWord16#,
        uncheckedShiftLWord16#,
        uncheckedShiftRLWord16#,
        word16ToInt16#,
        eqWord16#,
        geWord16#,
        gtWord16#,
        leWord16#,
        ltWord16#,
        neWord16#,
        
-- * Int32#
-- |Operations on 32-bit integers.

        Int32#,
        int32ToInt#,
        intToInt32#,
        negateInt32#,
        plusInt32#,
        subInt32#,
        timesInt32#,
        quotInt32#,
        remInt32#,
        quotRemInt32#,
        uncheckedShiftLInt32#,
        uncheckedShiftRAInt32#,
        uncheckedShiftRLInt32#,
        int32ToWord32#,
        eqInt32#,
        geInt32#,
        gtInt32#,
        leInt32#,
        ltInt32#,
        neInt32#,
        
-- * Word32#
-- |Operations on 32-bit unsigned words.

        Word32#,
        word32ToWord#,
        wordToWord32#,
        plusWord32#,
        subWord32#,
        timesWord32#,
        quotWord32#,
        remWord32#,
        quotRemWord32#,
        andWord32#,
        orWord32#,
        xorWord32#,
        notWord32#,
        uncheckedShiftLWord32#,
        uncheckedShiftRLWord32#,
        word32ToInt32#,
        eqWord32#,
        geWord32#,
        gtWord32#,
        leWord32#,
        ltWord32#,
        neWord32#,
        
-- * Int64#
-- |Operations on 64-bit signed words.

        Int64#,
        int64ToInt#,
        intToInt64#,
        negateInt64#,
        plusInt64#,
        subInt64#,
        timesInt64#,
        quotInt64#,
        remInt64#,
        uncheckedIShiftL64#,
        uncheckedIShiftRA64#,
        uncheckedIShiftRL64#,
        int64ToWord64#,
        eqInt64#,
        geInt64#,
        gtInt64#,
        leInt64#,
        ltInt64#,
        neInt64#,
        
-- * Word64#
-- |Operations on 64-bit unsigned words.

        Word64#,
        word64ToWord#,
        wordToWord64#,
        plusWord64#,
        subWord64#,
        timesWord64#,
        quotWord64#,
        remWord64#,
        and64#,
        or64#,
        xor64#,
        not64#,
        uncheckedShiftL64#,
        uncheckedShiftRL64#,
        word64ToInt64#,
        eqWord64#,
        geWord64#,
        gtWord64#,
        leWord64#,
        ltWord64#,
        neWord64#,
        
-- * Int#
-- |Operations on native-size integers (32+ bits).

        Int#,
        (+#),
        (-#),
        (*#),
        timesInt2#,
        mulIntMayOflo#,
        quotInt#,
        remInt#,
        quotRemInt#,
        andI#,
        orI#,
        xorI#,
        notI#,
        negateInt#,
        addIntC#,
        subIntC#,
        (>#),
        (>=#),
        (==#),
        (/=#),
        (<#),
        (<=#),
        chr#,
        int2Word#,
        int2Float#,
        int2Double#,
        word2Float#,
        word2Double#,
        uncheckedIShiftL#,
        uncheckedIShiftRA#,
        uncheckedIShiftRL#,
        
-- * 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#,
        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#,
        shrinkSmallMutableArray#,
        readSmallArray#,
        writeSmallArray#,
        sizeofSmallArray#,
        sizeofSmallMutableArray#,
        getSizeofSmallMutableArray#,
        indexSmallArray#,
        unsafeFreezeSmallArray#,
        unsafeThawSmallArray#,
        copySmallArray#,
        copySmallMutableArray#,
        cloneSmallArray#,
        cloneSmallMutableArray#,
        freezeSmallArray#,
        thawSmallArray#,
        casSmallArray#,
        
-- * Byte Arrays
-- |A @ByteArray\#@ is a region of
--          raw memory in the garbage-collected heap, which is not
--          scanned for pointers. 
--          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#,
        mutableByteArrayContents#,
        shrinkMutableByteArray#,
        resizeMutableByteArray#,
        unsafeFreezeByteArray#,
        sizeofByteArray#,
        sizeofMutableByteArray#,
        getSizeofMutableByteArray#,
        indexCharArray#,
        indexWideCharArray#,
        indexIntArray#,
        indexWordArray#,
        indexAddrArray#,
        indexFloatArray#,
        indexDoubleArray#,
        indexStablePtrArray#,
        indexInt8Array#,
        indexInt16Array#,
        indexInt32Array#,
        indexInt64Array#,
        indexWord8Array#,
        indexWord16Array#,
        indexWord32Array#,
        indexWord64Array#,
        indexWord8ArrayAsChar#,
        indexWord8ArrayAsWideChar#,
        indexWord8ArrayAsInt#,
        indexWord8ArrayAsWord#,
        indexWord8ArrayAsAddr#,
        indexWord8ArrayAsFloat#,
        indexWord8ArrayAsDouble#,
        indexWord8ArrayAsStablePtr#,
        indexWord8ArrayAsInt16#,
        indexWord8ArrayAsInt32#,
        indexWord8ArrayAsInt64#,
        indexWord8ArrayAsWord16#,
        indexWord8ArrayAsWord32#,
        indexWord8ArrayAsWord64#,
        readCharArray#,
        readWideCharArray#,
        readIntArray#,
        readWordArray#,
        readAddrArray#,
        readFloatArray#,
        readDoubleArray#,
        readStablePtrArray#,
        readInt8Array#,
        readInt16Array#,
        readInt32Array#,
        readInt64Array#,
        readWord8Array#,
        readWord16Array#,
        readWord32Array#,
        readWord64Array#,
        readWord8ArrayAsChar#,
        readWord8ArrayAsWideChar#,
        readWord8ArrayAsInt#,
        readWord8ArrayAsWord#,
        readWord8ArrayAsAddr#,
        readWord8ArrayAsFloat#,
        readWord8ArrayAsDouble#,
        readWord8ArrayAsStablePtr#,
        readWord8ArrayAsInt16#,
        readWord8ArrayAsInt32#,
        readWord8ArrayAsInt64#,
        readWord8ArrayAsWord16#,
        readWord8ArrayAsWord32#,
        readWord8ArrayAsWord64#,
        writeCharArray#,
        writeWideCharArray#,
        writeIntArray#,
        writeWordArray#,
        writeAddrArray#,
        writeFloatArray#,
        writeDoubleArray#,
        writeStablePtrArray#,
        writeInt8Array#,
        writeInt16Array#,
        writeInt32Array#,
        writeInt64Array#,
        writeWord8Array#,
        writeWord16Array#,
        writeWord32Array#,
        writeWord64Array#,
        writeWord8ArrayAsChar#,
        writeWord8ArrayAsWideChar#,
        writeWord8ArrayAsInt#,
        writeWord8ArrayAsWord#,
        writeWord8ArrayAsAddr#,
        writeWord8ArrayAsFloat#,
        writeWord8ArrayAsDouble#,
        writeWord8ArrayAsStablePtr#,
        writeWord8ArrayAsInt16#,
        writeWord8ArrayAsInt32#,
        writeWord8ArrayAsInt64#,
        writeWord8ArrayAsWord16#,
        writeWord8ArrayAsWord32#,
        writeWord8ArrayAsWord64#,
        compareByteArrays#,
        copyByteArray#,
        copyMutableByteArray#,
        copyByteArrayToAddr#,
        copyMutableByteArrayToAddr#,
        copyAddrToByteArray#,
        setByteArray#,
        atomicReadIntArray#,
        atomicWriteIntArray#,
        casIntArray#,
        casInt8Array#,
        casInt16Array#,
        casInt32Array#,
        casInt64Array#,
        fetchAddIntArray#,
        fetchSubIntArray#,
        fetchAndIntArray#,
        fetchNandIntArray#,
        fetchOrIntArray#,
        fetchXorIntArray#,
        
-- * 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#,
        atomicExchangeAddrAddr#,
        atomicExchangeWordAddr#,
        atomicCasAddrAddr#,
        atomicCasWordAddr#,
        atomicCasWord8Addr#,
        atomicCasWord16Addr#,
        atomicCasWord32Addr#,
        atomicCasWord64Addr#,
        fetchAddWordAddr#,
        fetchSubWordAddr#,
        fetchAndWordAddr#,
        fetchNandWordAddr#,
        fetchOrWordAddr#,
        fetchXorWordAddr#,
        atomicReadWordAddr#,
        atomicWriteWordAddr#,
        
-- * Mutable variables
-- |Operations on MutVar\#s.

        MutVar#,
        newMutVar#,
        readMutVar#,
        writeMutVar#,
        atomicModifyMutVar2#,
        atomicModifyMutVar_#,
        casMutVar#,
        
-- * Exceptions
-- |

        catch#,
        raise#,
        raiseIO#,
        maskAsyncExceptions#,
        maskUninterruptible#,
        unmaskAsyncExceptions#,
        getMaskingState#,
        
-- * STM-accessible Mutable Variables
-- |

        TVar#,
        atomically#,
        retry#,
        catchRetry#,
        catchSTM#,
        newTVar#,
        readTVar#,
        readTVarIO#,
        writeTVar#,
        
-- * Synchronized Mutable Variables
-- |Operations on @MVar\#@s. 

        MVar#,
        newMVar#,
        takeMVar#,
        tryTakeMVar#,
        putMVar#,
        tryPutMVar#,
        readMVar#,
        tryReadMVar#,
        isEmptyMVar#,
        
-- * Synchronized I\/O Ports
-- |Operations on @IOPort\#@s. 

        IOPort#,
        newIOPort#,
        readIOPort#,
        writeIOPort#,
        
-- * 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#,
        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#,
        
-- * Controlling object lifetime
-- |Ensuring that objects don\'t die a premature death.

        keepAlive#,
        
-- * 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#,
        
-- * Info Table Origin
-- |

        whereFrom#,
        
-- * Etc
-- |Miscellaneous built-ins

        FUN,
        realWorld#,
        void#,
        Proxy#,
        proxy#,
        seq,
        unsafeCoerce#,
        traceEvent#,
        traceBinaryEvent#,
        traceMarker#,
        setThreadAllocationCounter#,
        StackSnapshot#,
        
-- * 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 PPC native backend, 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 -> mkClosedDmdSig (replicate arity topDmd) topDiv }
fixity = Nothing
llvm_only = False

deprecated_msg = { }
-}
import GHC.Types (Coercible)
default ()

data Char#

gtChar# :: Char# -> Char# -> Int#
gtChar# :: Char# -> Char# -> Int#
gtChar# = Char# -> Char# -> Int#
gtChar#

geChar# :: Char# -> Char# -> Int#
geChar# :: Char# -> Char# -> Int#
geChar# = Char# -> Char# -> Int#
geChar#

eqChar# :: Char# -> Char# -> Int#
eqChar# :: Char# -> Char# -> Int#
eqChar# = Char# -> Char# -> Int#
eqChar#

neChar# :: Char# -> Char# -> Int#
neChar# :: Char# -> Char# -> Int#
neChar# = Char# -> Char# -> Int#
neChar#

ltChar# :: Char# -> Char# -> Int#
ltChar# :: Char# -> Char# -> Int#
ltChar# = Char# -> Char# -> Int#
ltChar#

leChar# :: Char# -> Char# -> Int#
leChar# :: Char# -> Char# -> Int#
leChar# = Char# -> Char# -> Int#
leChar#

ord# :: Char# -> Int#
ord# :: Char# -> Int#
ord# = Char# -> Int#
ord#

data Int8#

int8ToInt# :: Int8# -> Int#
int8ToInt# :: Int8# -> Int#
int8ToInt# = Int8# -> Int#
int8ToInt#

intToInt8# :: Int# -> Int8#
intToInt8# :: Int# -> Int8#
intToInt8# = Int# -> Int8#
intToInt8#

negateInt8# :: Int8# -> Int8#
negateInt8# :: Int8# -> Int8#
negateInt8# = Int8# -> Int8#
negateInt8#

plusInt8# :: Int8# -> Int8# -> Int8#
plusInt8# :: Int8# -> Int8# -> Int8#
plusInt8# = Int8# -> Int8# -> Int8#
plusInt8#

subInt8# :: Int8# -> Int8# -> Int8#
subInt8# :: Int8# -> Int8# -> Int8#
subInt8# = Int8# -> Int8# -> Int8#
subInt8#

timesInt8# :: Int8# -> Int8# -> Int8#
timesInt8# :: Int8# -> Int8# -> Int8#
timesInt8# = Int8# -> Int8# -> Int8#
timesInt8#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotInt8# :: Int8# -> Int8# -> Int8#
quotInt8# :: Int8# -> Int8# -> Int8#
quotInt8# = Int8# -> Int8# -> Int8#
quotInt8#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
remInt8# :: Int8# -> Int8# -> Int8#
remInt8# :: Int8# -> Int8# -> Int8#
remInt8# = Int8# -> Int8# -> Int8#
remInt8#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotRemInt8# :: Int8# -> Int8# -> (# Int8#,Int8# #)
quotRemInt8# :: Int8# -> Int8# -> (# Int8#, Int8# #)
quotRemInt8# = Int8# -> Int8# -> (# Int8#, Int8# #)
quotRemInt8#

uncheckedShiftLInt8# :: Int8# -> Int# -> Int8#
uncheckedShiftLInt8# :: Int8# -> Int# -> Int8#
uncheckedShiftLInt8# = Int8# -> Int# -> Int8#
uncheckedShiftLInt8#

uncheckedShiftRAInt8# :: Int8# -> Int# -> Int8#
uncheckedShiftRAInt8# :: Int8# -> Int# -> Int8#
uncheckedShiftRAInt8# = Int8# -> Int# -> Int8#
uncheckedShiftRAInt8#

uncheckedShiftRLInt8# :: Int8# -> Int# -> Int8#
uncheckedShiftRLInt8# :: Int8# -> Int# -> Int8#
uncheckedShiftRLInt8# = Int8# -> Int# -> Int8#
uncheckedShiftRLInt8#

int8ToWord8# :: Int8# -> Word8#
int8ToWord8# :: Int8# -> Word8#
int8ToWord8# = Int8# -> Word8#
int8ToWord8#

eqInt8# :: Int8# -> Int8# -> Int#
eqInt8# :: Int8# -> Int8# -> Int#
eqInt8# = Int8# -> Int8# -> Int#
eqInt8#

geInt8# :: Int8# -> Int8# -> Int#
geInt8# :: Int8# -> Int8# -> Int#
geInt8# = Int8# -> Int8# -> Int#
geInt8#

gtInt8# :: Int8# -> Int8# -> Int#
gtInt8# :: Int8# -> Int8# -> Int#
gtInt8# = Int8# -> Int8# -> Int#
gtInt8#

leInt8# :: Int8# -> Int8# -> Int#
leInt8# :: Int8# -> Int8# -> Int#
leInt8# = Int8# -> Int8# -> Int#
leInt8#

ltInt8# :: Int8# -> Int8# -> Int#
ltInt8# :: Int8# -> Int8# -> Int#
ltInt8# = Int8# -> Int8# -> Int#
ltInt8#

neInt8# :: Int8# -> Int8# -> Int#
neInt8# :: Int8# -> Int8# -> Int#
neInt8# = Int8# -> Int8# -> Int#
neInt8#

data Word8#

word8ToWord# :: Word8# -> Word#
word8ToWord# :: Word8# -> Word#
word8ToWord# = Word8# -> Word#
word8ToWord#

wordToWord8# :: Word# -> Word8#
wordToWord8# :: Word# -> Word8#
wordToWord8# = Word# -> Word8#
wordToWord8#

plusWord8# :: Word8# -> Word8# -> Word8#
plusWord8# :: Word8# -> Word8# -> Word8#
plusWord8# = Word8# -> Word8# -> Word8#
plusWord8#

subWord8# :: Word8# -> Word8# -> Word8#
subWord8# :: Word8# -> Word8# -> Word8#
subWord8# = Word8# -> Word8# -> Word8#
subWord8#

timesWord8# :: Word8# -> Word8# -> Word8#
timesWord8# :: Word8# -> Word8# -> Word8#
timesWord8# = Word8# -> Word8# -> Word8#
timesWord8#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotWord8# :: Word8# -> Word8# -> Word8#
quotWord8# :: Word8# -> Word8# -> Word8#
quotWord8# = Word8# -> Word8# -> Word8#
quotWord8#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
remWord8# :: Word8# -> Word8# -> Word8#
remWord8# :: Word8# -> Word8# -> Word8#
remWord8# = Word8# -> Word8# -> Word8#
remWord8#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotRemWord8# :: Word8# -> Word8# -> (# Word8#,Word8# #)
quotRemWord8# :: Word8# -> Word8# -> (# Word8#, Word8# #)
quotRemWord8# = Word8# -> Word8# -> (# Word8#, Word8# #)
quotRemWord8#

andWord8# :: Word8# -> Word8# -> Word8#
andWord8# :: Word8# -> Word8# -> Word8#
andWord8# = Word8# -> Word8# -> Word8#
andWord8#

orWord8# :: Word8# -> Word8# -> Word8#
orWord8# :: Word8# -> Word8# -> Word8#
orWord8# = Word8# -> Word8# -> Word8#
orWord8#

xorWord8# :: Word8# -> Word8# -> Word8#
xorWord8# :: Word8# -> Word8# -> Word8#
xorWord8# = Word8# -> Word8# -> Word8#
xorWord8#

notWord8# :: Word8# -> Word8#
notWord8# :: Word8# -> Word8#
notWord8# = Word8# -> Word8#
notWord8#

uncheckedShiftLWord8# :: Word8# -> Int# -> Word8#
uncheckedShiftLWord8# :: Word8# -> Int# -> Word8#
uncheckedShiftLWord8# = Word8# -> Int# -> Word8#
uncheckedShiftLWord8#

uncheckedShiftRLWord8# :: Word8# -> Int# -> Word8#
uncheckedShiftRLWord8# :: Word8# -> Int# -> Word8#
uncheckedShiftRLWord8# = Word8# -> Int# -> Word8#
uncheckedShiftRLWord8#

word8ToInt8# :: Word8# -> Int8#
word8ToInt8# :: Word8# -> Int8#
word8ToInt8# = Word8# -> Int8#
word8ToInt8#

eqWord8# :: Word8# -> Word8# -> Int#
eqWord8# :: Word8# -> Word8# -> Int#
eqWord8# = Word8# -> Word8# -> Int#
eqWord8#

geWord8# :: Word8# -> Word8# -> Int#
geWord8# :: Word8# -> Word8# -> Int#
geWord8# = Word8# -> Word8# -> Int#
geWord8#

gtWord8# :: Word8# -> Word8# -> Int#
gtWord8# :: Word8# -> Word8# -> Int#
gtWord8# = Word8# -> Word8# -> Int#
gtWord8#

leWord8# :: Word8# -> Word8# -> Int#
leWord8# :: Word8# -> Word8# -> Int#
leWord8# = Word8# -> Word8# -> Int#
leWord8#

ltWord8# :: Word8# -> Word8# -> Int#
ltWord8# :: Word8# -> Word8# -> Int#
ltWord8# = Word8# -> Word8# -> Int#
ltWord8#

neWord8# :: Word8# -> Word8# -> Int#
neWord8# :: Word8# -> Word8# -> Int#
neWord8# = Word8# -> Word8# -> Int#
neWord8#

data Int16#

int16ToInt# :: Int16# -> Int#
int16ToInt# :: Int16# -> Int#
int16ToInt# = Int16# -> Int#
int16ToInt#

intToInt16# :: Int# -> Int16#
intToInt16# :: Int# -> Int16#
intToInt16# = Int# -> Int16#
intToInt16#

negateInt16# :: Int16# -> Int16#
negateInt16# :: Int16# -> Int16#
negateInt16# = Int16# -> Int16#
negateInt16#

plusInt16# :: Int16# -> Int16# -> Int16#
plusInt16# :: Int16# -> Int16# -> Int16#
plusInt16# = Int16# -> Int16# -> Int16#
plusInt16#

subInt16# :: Int16# -> Int16# -> Int16#
subInt16# :: Int16# -> Int16# -> Int16#
subInt16# = Int16# -> Int16# -> Int16#
subInt16#

timesInt16# :: Int16# -> Int16# -> Int16#
timesInt16# :: Int16# -> Int16# -> Int16#
timesInt16# = Int16# -> Int16# -> Int16#
timesInt16#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotInt16# :: Int16# -> Int16# -> Int16#
quotInt16# :: Int16# -> Int16# -> Int16#
quotInt16# = Int16# -> Int16# -> Int16#
quotInt16#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
remInt16# :: Int16# -> Int16# -> Int16#
remInt16# :: Int16# -> Int16# -> Int16#
remInt16# = Int16# -> Int16# -> Int16#
remInt16#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotRemInt16# :: Int16# -> Int16# -> (# Int16#,Int16# #)
quotRemInt16# :: Int16# -> Int16# -> (# Int16#, Int16# #)
quotRemInt16# = Int16# -> Int16# -> (# Int16#, Int16# #)
quotRemInt16#

uncheckedShiftLInt16# :: Int16# -> Int# -> Int16#
uncheckedShiftLInt16# :: Int16# -> Int# -> Int16#
uncheckedShiftLInt16# = Int16# -> Int# -> Int16#
uncheckedShiftLInt16#

uncheckedShiftRAInt16# :: Int16# -> Int# -> Int16#
uncheckedShiftRAInt16# :: Int16# -> Int# -> Int16#
uncheckedShiftRAInt16# = Int16# -> Int# -> Int16#
uncheckedShiftRAInt16#

uncheckedShiftRLInt16# :: Int16# -> Int# -> Int16#
uncheckedShiftRLInt16# :: Int16# -> Int# -> Int16#
uncheckedShiftRLInt16# = Int16# -> Int# -> Int16#
uncheckedShiftRLInt16#

int16ToWord16# :: Int16# -> Word16#
int16ToWord16# :: Int16# -> Word16#
int16ToWord16# = Int16# -> Word16#
int16ToWord16#

eqInt16# :: Int16# -> Int16# -> Int#
eqInt16# :: Int16# -> Int16# -> Int#
eqInt16# = Int16# -> Int16# -> Int#
eqInt16#

geInt16# :: Int16# -> Int16# -> Int#
geInt16# :: Int16# -> Int16# -> Int#
geInt16# = Int16# -> Int16# -> Int#
geInt16#

gtInt16# :: Int16# -> Int16# -> Int#
gtInt16# :: Int16# -> Int16# -> Int#
gtInt16# = Int16# -> Int16# -> Int#
gtInt16#

leInt16# :: Int16# -> Int16# -> Int#
leInt16# :: Int16# -> Int16# -> Int#
leInt16# = Int16# -> Int16# -> Int#
leInt16#

ltInt16# :: Int16# -> Int16# -> Int#
ltInt16# :: Int16# -> Int16# -> Int#
ltInt16# = Int16# -> Int16# -> Int#
ltInt16#

neInt16# :: Int16# -> Int16# -> Int#
neInt16# :: Int16# -> Int16# -> Int#
neInt16# = Int16# -> Int16# -> Int#
neInt16#

data Word16#

word16ToWord# :: Word16# -> Word#
word16ToWord# :: Word16# -> Word#
word16ToWord# = Word16# -> Word#
word16ToWord#

wordToWord16# :: Word# -> Word16#
wordToWord16# :: Word# -> Word16#
wordToWord16# = Word# -> Word16#
wordToWord16#

plusWord16# :: Word16# -> Word16# -> Word16#
plusWord16# :: Word16# -> Word16# -> Word16#
plusWord16# = Word16# -> Word16# -> Word16#
plusWord16#

subWord16# :: Word16# -> Word16# -> Word16#
subWord16# :: Word16# -> Word16# -> Word16#
subWord16# = Word16# -> Word16# -> Word16#
subWord16#

timesWord16# :: Word16# -> Word16# -> Word16#
timesWord16# :: Word16# -> Word16# -> Word16#
timesWord16# = Word16# -> Word16# -> Word16#
timesWord16#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotWord16# :: Word16# -> Word16# -> Word16#
quotWord16# :: Word16# -> Word16# -> Word16#
quotWord16# = Word16# -> Word16# -> Word16#
quotWord16#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
remWord16# :: Word16# -> Word16# -> Word16#
remWord16# :: Word16# -> Word16# -> Word16#
remWord16# = Word16# -> Word16# -> Word16#
remWord16#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotRemWord16# :: Word16# -> Word16# -> (# Word16#,Word16# #)
quotRemWord16# :: Word16# -> Word16# -> (# Word16#, Word16# #)
quotRemWord16# = Word16# -> Word16# -> (# Word16#, Word16# #)
quotRemWord16#

andWord16# :: Word16# -> Word16# -> Word16#
andWord16# :: Word16# -> Word16# -> Word16#
andWord16# = Word16# -> Word16# -> Word16#
andWord16#

orWord16# :: Word16# -> Word16# -> Word16#
orWord16# :: Word16# -> Word16# -> Word16#
orWord16# = Word16# -> Word16# -> Word16#
orWord16#

xorWord16# :: Word16# -> Word16# -> Word16#
xorWord16# :: Word16# -> Word16# -> Word16#
xorWord16# = Word16# -> Word16# -> Word16#
xorWord16#

notWord16# :: Word16# -> Word16#
notWord16# :: Word16# -> Word16#
notWord16# = Word16# -> Word16#
notWord16#

uncheckedShiftLWord16# :: Word16# -> Int# -> Word16#
uncheckedShiftLWord16# :: Word16# -> Int# -> Word16#
uncheckedShiftLWord16# = Word16# -> Int# -> Word16#
uncheckedShiftLWord16#

uncheckedShiftRLWord16# :: Word16# -> Int# -> Word16#
uncheckedShiftRLWord16# :: Word16# -> Int# -> Word16#
uncheckedShiftRLWord16# = Word16# -> Int# -> Word16#
uncheckedShiftRLWord16#

word16ToInt16# :: Word16# -> Int16#
word16ToInt16# :: Word16# -> Int16#
word16ToInt16# = Word16# -> Int16#
word16ToInt16#

eqWord16# :: Word16# -> Word16# -> Int#
eqWord16# :: Word16# -> Word16# -> Int#
eqWord16# = Word16# -> Word16# -> Int#
eqWord16#

geWord16# :: Word16# -> Word16# -> Int#
geWord16# :: Word16# -> Word16# -> Int#
geWord16# = Word16# -> Word16# -> Int#
geWord16#

gtWord16# :: Word16# -> Word16# -> Int#
gtWord16# :: Word16# -> Word16# -> Int#
gtWord16# = Word16# -> Word16# -> Int#
gtWord16#

leWord16# :: Word16# -> Word16# -> Int#
leWord16# :: Word16# -> Word16# -> Int#
leWord16# = Word16# -> Word16# -> Int#
leWord16#

ltWord16# :: Word16# -> Word16# -> Int#
ltWord16# :: Word16# -> Word16# -> Int#
ltWord16# = Word16# -> Word16# -> Int#
ltWord16#

neWord16# :: Word16# -> Word16# -> Int#
neWord16# :: Word16# -> Word16# -> Int#
neWord16# = Word16# -> Word16# -> Int#
neWord16#

data Int32#

int32ToInt# :: Int32# -> Int#
int32ToInt# :: Int32# -> Int#
int32ToInt# = Int32# -> Int#
int32ToInt#

intToInt32# :: Int# -> Int32#
intToInt32# :: Int# -> Int32#
intToInt32# = Int# -> Int32#
intToInt32#

negateInt32# :: Int32# -> Int32#
negateInt32# :: Int32# -> Int32#
negateInt32# = Int32# -> Int32#
negateInt32#

plusInt32# :: Int32# -> Int32# -> Int32#
plusInt32# :: Int32# -> Int32# -> Int32#
plusInt32# = Int32# -> Int32# -> Int32#
plusInt32#

subInt32# :: Int32# -> Int32# -> Int32#
subInt32# :: Int32# -> Int32# -> Int32#
subInt32# = Int32# -> Int32# -> Int32#
subInt32#

timesInt32# :: Int32# -> Int32# -> Int32#
timesInt32# :: Int32# -> Int32# -> Int32#
timesInt32# = Int32# -> Int32# -> Int32#
timesInt32#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotInt32# :: Int32# -> Int32# -> Int32#
quotInt32# :: Int32# -> Int32# -> Int32#
quotInt32# = Int32# -> Int32# -> Int32#
quotInt32#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
remInt32# :: Int32# -> Int32# -> Int32#
remInt32# :: Int32# -> Int32# -> Int32#
remInt32# = Int32# -> Int32# -> Int32#
remInt32#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotRemInt32# :: Int32# -> Int32# -> (# Int32#,Int32# #)
quotRemInt32# :: Int32# -> Int32# -> (# Int32#, Int32# #)
quotRemInt32# = Int32# -> Int32# -> (# Int32#, Int32# #)
quotRemInt32#

uncheckedShiftLInt32# :: Int32# -> Int# -> Int32#
uncheckedShiftLInt32# :: Int32# -> Int# -> Int32#
uncheckedShiftLInt32# = Int32# -> Int# -> Int32#
uncheckedShiftLInt32#

uncheckedShiftRAInt32# :: Int32# -> Int# -> Int32#
uncheckedShiftRAInt32# :: Int32# -> Int# -> Int32#
uncheckedShiftRAInt32# = Int32# -> Int# -> Int32#
uncheckedShiftRAInt32#

uncheckedShiftRLInt32# :: Int32# -> Int# -> Int32#
uncheckedShiftRLInt32# :: Int32# -> Int# -> Int32#
uncheckedShiftRLInt32# = Int32# -> Int# -> Int32#
uncheckedShiftRLInt32#

int32ToWord32# :: Int32# -> Word32#
int32ToWord32# :: Int32# -> Word32#
int32ToWord32# = Int32# -> Word32#
int32ToWord32#

eqInt32# :: Int32# -> Int32# -> Int#
eqInt32# :: Int32# -> Int32# -> Int#
eqInt32# = Int32# -> Int32# -> Int#
eqInt32#

geInt32# :: Int32# -> Int32# -> Int#
geInt32# :: Int32# -> Int32# -> Int#
geInt32# = Int32# -> Int32# -> Int#
geInt32#

gtInt32# :: Int32# -> Int32# -> Int#
gtInt32# :: Int32# -> Int32# -> Int#
gtInt32# = Int32# -> Int32# -> Int#
gtInt32#

leInt32# :: Int32# -> Int32# -> Int#
leInt32# :: Int32# -> Int32# -> Int#
leInt32# = Int32# -> Int32# -> Int#
leInt32#

ltInt32# :: Int32# -> Int32# -> Int#
ltInt32# :: Int32# -> Int32# -> Int#
ltInt32# = Int32# -> Int32# -> Int#
ltInt32#

neInt32# :: Int32# -> Int32# -> Int#
neInt32# :: Int32# -> Int32# -> Int#
neInt32# = Int32# -> Int32# -> Int#
neInt32#

data Word32#

word32ToWord# :: Word32# -> Word#
word32ToWord# :: Word32# -> Word#
word32ToWord# = Word32# -> Word#
word32ToWord#

wordToWord32# :: Word# -> Word32#
wordToWord32# :: Word# -> Word32#
wordToWord32# = Word# -> Word32#
wordToWord32#

plusWord32# :: Word32# -> Word32# -> Word32#
plusWord32# :: Word32# -> Word32# -> Word32#
plusWord32# = Word32# -> Word32# -> Word32#
plusWord32#

subWord32# :: Word32# -> Word32# -> Word32#
subWord32# :: Word32# -> Word32# -> Word32#
subWord32# = Word32# -> Word32# -> Word32#
subWord32#

timesWord32# :: Word32# -> Word32# -> Word32#
timesWord32# :: Word32# -> Word32# -> Word32#
timesWord32# = Word32# -> Word32# -> Word32#
timesWord32#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotWord32# :: Word32# -> Word32# -> Word32#
quotWord32# :: Word32# -> Word32# -> Word32#
quotWord32# = Word32# -> Word32# -> Word32#
quotWord32#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
remWord32# :: Word32# -> Word32# -> Word32#
remWord32# :: Word32# -> Word32# -> Word32#
remWord32# = Word32# -> Word32# -> Word32#
remWord32#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotRemWord32# :: Word32# -> Word32# -> (# Word32#,Word32# #)
quotRemWord32# :: Word32# -> Word32# -> (# Word32#, Word32# #)
quotRemWord32# = Word32# -> Word32# -> (# Word32#, Word32# #)
quotRemWord32#

andWord32# :: Word32# -> Word32# -> Word32#
andWord32# :: Word32# -> Word32# -> Word32#
andWord32# = Word32# -> Word32# -> Word32#
andWord32#

orWord32# :: Word32# -> Word32# -> Word32#
orWord32# :: Word32# -> Word32# -> Word32#
orWord32# = Word32# -> Word32# -> Word32#
orWord32#

xorWord32# :: Word32# -> Word32# -> Word32#
xorWord32# :: Word32# -> Word32# -> Word32#
xorWord32# = Word32# -> Word32# -> Word32#
xorWord32#

notWord32# :: Word32# -> Word32#
notWord32# :: Word32# -> Word32#
notWord32# = Word32# -> Word32#
notWord32#

uncheckedShiftLWord32# :: Word32# -> Int# -> Word32#
uncheckedShiftLWord32# :: Word32# -> Int# -> Word32#
uncheckedShiftLWord32# = Word32# -> Int# -> Word32#
uncheckedShiftLWord32#

uncheckedShiftRLWord32# :: Word32# -> Int# -> Word32#
uncheckedShiftRLWord32# :: Word32# -> Int# -> Word32#
uncheckedShiftRLWord32# = Word32# -> Int# -> Word32#
uncheckedShiftRLWord32#

word32ToInt32# :: Word32# -> Int32#
word32ToInt32# :: Word32# -> Int32#
word32ToInt32# = Word32# -> Int32#
word32ToInt32#

eqWord32# :: Word32# -> Word32# -> Int#
eqWord32# :: Word32# -> Word32# -> Int#
eqWord32# = Word32# -> Word32# -> Int#
eqWord32#

geWord32# :: Word32# -> Word32# -> Int#
geWord32# :: Word32# -> Word32# -> Int#
geWord32# = Word32# -> Word32# -> Int#
geWord32#

gtWord32# :: Word32# -> Word32# -> Int#
gtWord32# :: Word32# -> Word32# -> Int#
gtWord32# = Word32# -> Word32# -> Int#
gtWord32#

leWord32# :: Word32# -> Word32# -> Int#
leWord32# :: Word32# -> Word32# -> Int#
leWord32# = Word32# -> Word32# -> Int#
leWord32#

ltWord32# :: Word32# -> Word32# -> Int#
ltWord32# :: Word32# -> Word32# -> Int#
ltWord32# = Word32# -> Word32# -> Int#
ltWord32#

neWord32# :: Word32# -> Word32# -> Int#
neWord32# :: Word32# -> Word32# -> Int#
neWord32# = Word32# -> Word32# -> Int#
neWord32#

data Int64#

int64ToInt# :: Int64# -> Int#
int64ToInt# :: Int64# -> Int#
int64ToInt# = Int64# -> Int#
int64ToInt#

intToInt64# :: Int# -> Int64#
intToInt64# :: Int# -> Int64#
intToInt64# = Int# -> Int64#
intToInt64#

negateInt64# :: Int64# -> Int64#
negateInt64# :: Int64# -> Int64#
negateInt64# = Int64# -> Int64#
negateInt64#

plusInt64# :: Int64# -> Int64# -> Int64#
plusInt64# :: Int64# -> Int64# -> Int64#
plusInt64# = Int64# -> Int64# -> Int64#
plusInt64#

subInt64# :: Int64# -> Int64# -> Int64#
subInt64# :: Int64# -> Int64# -> Int64#
subInt64# = Int64# -> Int64# -> Int64#
subInt64#

timesInt64# :: Int64# -> Int64# -> Int64#
timesInt64# :: Int64# -> Int64# -> Int64#
timesInt64# = Int64# -> Int64# -> Int64#
timesInt64#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotInt64# :: Int64# -> Int64# -> Int64#
quotInt64# :: Int64# -> Int64# -> Int64#
quotInt64# = Int64# -> Int64# -> Int64#
quotInt64#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
remInt64# :: Int64# -> Int64# -> Int64#
remInt64# :: Int64# -> Int64# -> Int64#
remInt64# = Int64# -> Int64# -> Int64#
remInt64#

uncheckedIShiftL64# :: Int64# -> Int# -> Int64#
uncheckedIShiftL64# :: Int64# -> Int# -> Int64#
uncheckedIShiftL64# = Int64# -> Int# -> Int64#
uncheckedIShiftL64#

uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#
uncheckedIShiftRA64# :: Int64# -> Int# -> Int64#
uncheckedIShiftRA64# = Int64# -> Int# -> Int64#
uncheckedIShiftRA64#

uncheckedIShiftRL64# :: Int64# -> Int# -> Int64#
uncheckedIShiftRL64# :: Int64# -> Int# -> Int64#
uncheckedIShiftRL64# = Int64# -> Int# -> Int64#
uncheckedIShiftRL64#

int64ToWord64# :: Int64# -> Word64#
int64ToWord64# :: Int64# -> Word64#
int64ToWord64# = Int64# -> Word64#
int64ToWord64#

eqInt64# :: Int64# -> Int64# -> Int#
eqInt64# :: Int64# -> Int64# -> Int#
eqInt64# = Int64# -> Int64# -> Int#
eqInt64#

geInt64# :: Int64# -> Int64# -> Int#
geInt64# :: Int64# -> Int64# -> Int#
geInt64# = Int64# -> Int64# -> Int#
geInt64#

gtInt64# :: Int64# -> Int64# -> Int#
gtInt64# :: Int64# -> Int64# -> Int#
gtInt64# = Int64# -> Int64# -> Int#
gtInt64#

leInt64# :: Int64# -> Int64# -> Int#
leInt64# :: Int64# -> Int64# -> Int#
leInt64# = Int64# -> Int64# -> Int#
leInt64#

ltInt64# :: Int64# -> Int64# -> Int#
ltInt64# :: Int64# -> Int64# -> Int#
ltInt64# = Int64# -> Int64# -> Int#
ltInt64#

neInt64# :: Int64# -> Int64# -> Int#
neInt64# :: Int64# -> Int64# -> Int#
neInt64# = Int64# -> Int64# -> Int#
neInt64#

data Word64#

word64ToWord# :: Word64# -> Word#
word64ToWord# :: Word64# -> Word#
word64ToWord# = Word64# -> Word#
word64ToWord#

wordToWord64# :: Word# -> Word64#
wordToWord64# :: Word# -> Word64#
wordToWord64# = Word# -> Word64#
wordToWord64#

plusWord64# :: Word64# -> Word64# -> Word64#
plusWord64# :: Word64# -> Word64# -> Word64#
plusWord64# = Word64# -> Word64# -> Word64#
plusWord64#

subWord64# :: Word64# -> Word64# -> Word64#
subWord64# :: Word64# -> Word64# -> Word64#
subWord64# = Word64# -> Word64# -> Word64#
subWord64#

timesWord64# :: Word64# -> Word64# -> Word64#
timesWord64# :: Word64# -> Word64# -> Word64#
timesWord64# = Word64# -> Word64# -> Word64#
timesWord64#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotWord64# :: Word64# -> Word64# -> Word64#
quotWord64# :: Word64# -> Word64# -> Word64#
quotWord64# = Word64# -> Word64# -> Word64#
quotWord64#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
remWord64# :: Word64# -> Word64# -> Word64#
remWord64# :: Word64# -> Word64# -> Word64#
remWord64# = Word64# -> Word64# -> Word64#
remWord64#

and64# :: Word64# -> Word64# -> Word64#
and64# :: Word64# -> Word64# -> Word64#
and64# = Word64# -> Word64# -> Word64#
and64#

or64# :: Word64# -> Word64# -> Word64#
or64# :: Word64# -> Word64# -> Word64#
or64# = Word64# -> Word64# -> Word64#
or64#

xor64# :: Word64# -> Word64# -> Word64#
xor64# :: Word64# -> Word64# -> Word64#
xor64# = Word64# -> Word64# -> Word64#
xor64#

not64# :: Word64# -> Word64#
not64# :: Word64# -> Word64#
not64# = Word64# -> Word64#
not64#

uncheckedShiftL64# :: Word64# -> Int# -> Word64#
uncheckedShiftL64# :: Word64# -> Int# -> Word64#
uncheckedShiftL64# = Word64# -> Int# -> Word64#
uncheckedShiftL64#

uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
uncheckedShiftRL64# :: Word64# -> Int# -> Word64#
uncheckedShiftRL64# = Word64# -> Int# -> Word64#
uncheckedShiftRL64#

word64ToInt64# :: Word64# -> Int64#
word64ToInt64# :: Word64# -> Int64#
word64ToInt64# = Word64# -> Int64#
word64ToInt64#

eqWord64# :: Word64# -> Word64# -> Int#
eqWord64# :: Word64# -> Word64# -> Int#
eqWord64# = Word64# -> Word64# -> Int#
eqWord64#

geWord64# :: Word64# -> Word64# -> Int#
geWord64# :: Word64# -> Word64# -> Int#
geWord64# = Word64# -> Word64# -> Int#
geWord64#

gtWord64# :: Word64# -> Word64# -> Int#
gtWord64# :: Word64# -> Word64# -> Int#
gtWord64# = Word64# -> Word64# -> Int#
gtWord64#

leWord64# :: Word64# -> Word64# -> Int#
leWord64# :: Word64# -> Word64# -> Int#
leWord64# = Word64# -> Word64# -> Int#
leWord64#

ltWord64# :: Word64# -> Word64# -> Int#
ltWord64# :: Word64# -> Word64# -> Int#
ltWord64# = Word64# -> Word64# -> Int#
ltWord64#

neWord64# :: Word64# -> Word64# -> Int#
neWord64# :: Word64# -> Word64# -> Int#
neWord64# = Word64# -> Word64# -> Int#
neWord64#

data Int#

infixl 6 +#
(+#) :: Int# -> Int# -> Int#
+# :: Int# -> Int# -> Int#
(+#) = Int# -> Int# -> Int#
(+#)

infixl 6 -#
(-#) :: Int# -> Int# -> Int#
-# :: Int# -> Int# -> Int#
(-#) = Int# -> Int# -> Int#
(-#)

-- |Low word of signed integer multiply.
infixl 7 *#
(*#) :: Int# -> Int# -> Int#
*# :: Int# -> Int# -> Int#
(*#) = Int# -> Int# -> Int#
(*#)

-- |Return a triple (isHighNeeded,high,low) where high and low are respectively
--    the high and low bits of the double-word result. isHighNeeded is a cheap way
--    to test if the high word is a sign-extension of the low word (isHighNeeded =
--    0#) or not (isHighNeeded = 1#).
timesInt2# :: Int# -> Int# -> (# Int#,Int#,Int# #)
timesInt2# :: Int# -> Int# -> (# Int#, Int#, Int# #)
timesInt2# = Int# -> Int# -> (# Int#, Int#, Int# #)
timesInt2#

-- |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# :: Int# -> Int# -> Int#
mulIntMayOflo# = Int# -> Int# -> Int#
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# :: Int# -> Int# -> Int#
quotInt# = Int# -> Int# -> Int#
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# :: Int# -> Int# -> Int#
remInt# = Int# -> Int# -> Int#
remInt#

-- |Rounds towards zero.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotRemInt# :: Int# -> Int# -> (# Int#,Int# #)
quotRemInt# :: Int# -> Int# -> (# Int#, Int# #)
quotRemInt# = Int# -> Int# -> (# Int#, Int# #)
quotRemInt#

-- |Bitwise \"and\".
andI# :: Int# -> Int# -> Int#
andI# :: Int# -> Int# -> Int#
andI# = Int# -> Int# -> Int#
andI#

-- |Bitwise \"or\".
orI# :: Int# -> Int# -> Int#
orI# :: Int# -> Int# -> Int#
orI# = Int# -> Int# -> Int#
orI#

-- |Bitwise \"xor\".
xorI# :: Int# -> Int# -> Int#
xorI# :: Int# -> Int# -> Int#
xorI# = Int# -> Int# -> Int#
xorI#

-- |Bitwise \"not\", also known as the binary complement.
notI# :: Int# -> Int#
notI# :: Int# -> Int#
notI# = Int# -> Int#
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# :: Int# -> Int#
negateInt# = Int# -> Int#
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# :: Int# -> Int# -> (# Int#, Int# #)
addIntC# = Int# -> Int# -> (# Int#, Int# #)
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# :: Int# -> Int# -> (# Int#, Int# #)
subIntC# = Int# -> Int# -> (# Int#, Int# #)
subIntC#

infix 4 >#
(>#) :: Int# -> Int# -> Int#
># :: Int# -> Int# -> Int#
(>#) = Int# -> Int# -> Int#
(>#)

infix 4 >=#
(>=#) :: Int# -> Int# -> Int#
>=# :: Int# -> Int# -> Int#
(>=#) = Int# -> Int# -> Int#
(>=#)

infix 4 ==#
(==#) :: Int# -> Int# -> Int#
==# :: Int# -> Int# -> Int#
(==#) = Int# -> Int# -> Int#
(==#)

infix 4 /=#
(/=#) :: Int# -> Int# -> Int#
/=# :: Int# -> Int# -> Int#
(/=#) = Int# -> Int# -> Int#
(/=#)

infix 4 <#
(<#) :: Int# -> Int# -> Int#
<# :: Int# -> Int# -> Int#
(<#) = Int# -> Int# -> Int#
(<#)

infix 4 <=#
(<=#) :: Int# -> Int# -> Int#
<=# :: Int# -> Int# -> Int#
(<=#) = Int# -> Int# -> Int#
(<=#)

chr# :: Int# -> Char#
chr# :: Int# -> Char#
chr# = Int# -> Char#
chr#

int2Word# :: Int# -> Word#
int2Word# :: Int# -> Word#
int2Word# = Int# -> Word#
int2Word#

-- |Convert an @Int#@ to the corresponding @Float#@ with the same
--     integral value (up to truncation due to floating-point precision). e.g.
--     @int2Float# 1# == 1.0#@
int2Float# :: Int# -> Float#
int2Float# :: Int# -> Float#
int2Float# = Int# -> Float#
int2Float#

-- |Convert an @Int#@ to the corresponding @Double#@ with the same
--     integral value (up to truncation due to floating-point precision). e.g.
--     @int2Double# 1# == 1.0##@
int2Double# :: Int# -> Double#
int2Double# :: Int# -> Double#
int2Double# = Int# -> Double#
int2Double#

-- |Convert an @Word#@ to the corresponding @Float#@ with the same
--     integral value (up to truncation due to floating-point precision). e.g.
--     @word2Float# 1## == 1.0#@
word2Float# :: Word# -> Float#
word2Float# :: Word# -> Float#
word2Float# = Word# -> Float#
word2Float#

-- |Convert an @Word#@ to the corresponding @Double#@ with the same
--     integral value (up to truncation due to floating-point precision). e.g.
--     @word2Double# 1## == 1.0##@
word2Double# :: Word# -> Double#
word2Double# :: Word# -> Double#
word2Double# = Word# -> Double#
word2Double#

-- |Shift left.  Result undefined if shift amount is not
--           in the range 0 to word size - 1 inclusive.
uncheckedIShiftL# :: Int# -> Int# -> Int#
uncheckedIShiftL# :: Int# -> Int# -> Int#
uncheckedIShiftL# = Int# -> Int# -> Int#
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# :: Int# -> Int# -> Int#
uncheckedIShiftRA# = Int# -> Int# -> Int#
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# :: Int# -> Int# -> Int#
uncheckedIShiftRL# = Int# -> Int# -> Int#
uncheckedIShiftRL#

data Word#

plusWord# :: Word# -> Word# -> Word#
plusWord# :: Word# -> Word# -> Word#
plusWord# = Word# -> Word# -> Word#
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# :: Word# -> Word# -> (# Word#, Int# #)
addWordC# = Word# -> Word# -> (# Word#, Int# #)
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# :: Word# -> Word# -> (# Word#, Int# #)
subWordC# = Word# -> Word# -> (# Word#, Int# #)
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# :: Word# -> Word# -> (# Word#, Word# #)
plusWord2# = Word# -> Word# -> (# Word#, Word# #)
plusWord2#

minusWord# :: Word# -> Word# -> Word#
minusWord# :: Word# -> Word# -> Word#
minusWord# = Word# -> Word# -> Word#
minusWord#

timesWord# :: Word# -> Word# -> Word#
timesWord# :: Word# -> Word# -> Word#
timesWord# = Word# -> Word# -> Word#
timesWord#

timesWord2# :: Word# -> Word# -> (# Word#,Word# #)
timesWord2# :: Word# -> Word# -> (# Word#, Word# #)
timesWord2# = Word# -> Word# -> (# Word#, Word# #)
timesWord2#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotWord# :: Word# -> Word# -> Word#
quotWord# :: Word# -> Word# -> Word#
quotWord# = Word# -> Word# -> Word#
quotWord#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
remWord# :: Word# -> Word# -> Word#
remWord# :: Word# -> Word# -> Word#
remWord# = Word# -> Word# -> Word#
remWord#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
quotRemWord# :: Word# -> Word# -> (# Word#,Word# #)
quotRemWord# :: Word# -> Word# -> (# Word#, Word# #)
quotRemWord# = Word# -> Word# -> (# Word#, Word# #)
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# :: Word# -> Word# -> Word# -> (# Word#, Word# #)
quotRemWord2# = Word# -> Word# -> Word# -> (# Word#, Word# #)
quotRemWord2#

and# :: Word# -> Word# -> Word#
and# :: Word# -> Word# -> Word#
and# = Word# -> Word# -> Word#
and#

or# :: Word# -> Word# -> Word#
or# :: Word# -> Word# -> Word#
or# = Word# -> Word# -> Word#
or#

xor# :: Word# -> Word# -> Word#
xor# :: Word# -> Word# -> Word#
xor# = Word# -> Word# -> Word#
xor#

not# :: Word# -> Word#
not# :: Word# -> Word#
not# = Word# -> Word#
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# :: Word# -> Int# -> Word#
uncheckedShiftL# = Word# -> Int# -> Word#
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# :: Word# -> Int# -> Word#
uncheckedShiftRL# = Word# -> Int# -> Word#
uncheckedShiftRL#

word2Int# :: Word# -> Int#
word2Int# :: Word# -> Int#
word2Int# = Word# -> Int#
word2Int#

gtWord# :: Word# -> Word# -> Int#
gtWord# :: Word# -> Word# -> Int#
gtWord# = Word# -> Word# -> Int#
gtWord#

geWord# :: Word# -> Word# -> Int#
geWord# :: Word# -> Word# -> Int#
geWord# = Word# -> Word# -> Int#
geWord#

eqWord# :: Word# -> Word# -> Int#
eqWord# :: Word# -> Word# -> Int#
eqWord# = Word# -> Word# -> Int#
eqWord#

neWord# :: Word# -> Word# -> Int#
neWord# :: Word# -> Word# -> Int#
neWord# = Word# -> Word# -> Int#
neWord#

ltWord# :: Word# -> Word# -> Int#
ltWord# :: Word# -> Word# -> Int#
ltWord# = Word# -> Word# -> Int#
ltWord#

leWord# :: Word# -> Word# -> Int#
leWord# :: Word# -> Word# -> Int#
leWord# = Word# -> Word# -> Int#
leWord#

-- |Count the number of set bits in the lower 8 bits of a word.
popCnt8# :: Word# -> Word#
popCnt8# :: Word# -> Word#
popCnt8# = Word# -> Word#
popCnt8#

-- |Count the number of set bits in the lower 16 bits of a word.
popCnt16# :: Word# -> Word#
popCnt16# :: Word# -> Word#
popCnt16# = Word# -> Word#
popCnt16#

-- |Count the number of set bits in the lower 32 bits of a word.
popCnt32# :: Word# -> Word#
popCnt32# :: Word# -> Word#
popCnt32# = Word# -> Word#
popCnt32#

-- |Count the number of set bits in a 64-bit word.
popCnt64# :: Word64# -> Word#
popCnt64# :: Word64# -> Word#
popCnt64# = Word64# -> Word#
popCnt64#

-- |Count the number of set bits in a word.
popCnt# :: Word# -> Word#
popCnt# :: Word# -> Word#
popCnt# = Word# -> Word#
popCnt#

-- |Deposit bits to lower 8 bits of a word at locations specified by a mask.
pdep8# :: Word# -> Word# -> Word#
pdep8# :: Word# -> Word# -> Word#
pdep8# = Word# -> Word# -> Word#
pdep8#

-- |Deposit bits to lower 16 bits of a word at locations specified by a mask.
pdep16# :: Word# -> Word# -> Word#
pdep16# :: Word# -> Word# -> Word#
pdep16# = Word# -> Word# -> Word#
pdep16#

-- |Deposit bits to lower 32 bits of a word at locations specified by a mask.
pdep32# :: Word# -> Word# -> Word#
pdep32# :: Word# -> Word# -> Word#
pdep32# = Word# -> Word# -> Word#
pdep32#

-- |Deposit bits to a word at locations specified by a mask.
pdep64# :: Word64# -> Word64# -> Word64#
pdep64# :: Word64# -> Word64# -> Word64#
pdep64# = Word64# -> Word64# -> Word64#
pdep64#

-- |Deposit bits to a word at locations specified by a mask.
pdep# :: Word# -> Word# -> Word#
pdep# :: Word# -> Word# -> Word#
pdep# = Word# -> Word# -> Word#
pdep#

-- |Extract bits from lower 8 bits of a word at locations specified by a mask.
pext8# :: Word# -> Word# -> Word#
pext8# :: Word# -> Word# -> Word#
pext8# = Word# -> Word# -> Word#
pext8#

-- |Extract bits from lower 16 bits of a word at locations specified by a mask.
pext16# :: Word# -> Word# -> Word#
pext16# :: Word# -> Word# -> Word#
pext16# = Word# -> Word# -> Word#
pext16#

-- |Extract bits from lower 32 bits of a word at locations specified by a mask.
pext32# :: Word# -> Word# -> Word#
pext32# :: Word# -> Word# -> Word#
pext32# = Word# -> Word# -> Word#
pext32#

-- |Extract bits from a word at locations specified by a mask.
pext64# :: Word64# -> Word64# -> Word64#
pext64# :: Word64# -> Word64# -> Word64#
pext64# = Word64# -> Word64# -> Word64#
pext64#

-- |Extract bits from a word at locations specified by a mask.
pext# :: Word# -> Word# -> Word#
pext# :: Word# -> Word# -> Word#
pext# = Word# -> Word# -> Word#
pext#

-- |Count leading zeros in the lower 8 bits of a word.
clz8# :: Word# -> Word#
clz8# :: Word# -> Word#
clz8# = Word# -> Word#
clz8#

-- |Count leading zeros in the lower 16 bits of a word.
clz16# :: Word# -> Word#
clz16# :: Word# -> Word#
clz16# = Word# -> Word#
clz16#

-- |Count leading zeros in the lower 32 bits of a word.
clz32# :: Word# -> Word#
clz32# :: Word# -> Word#
clz32# = Word# -> Word#
clz32#

-- |Count leading zeros in a 64-bit word.
clz64# :: Word64# -> Word#
clz64# :: Word64# -> Word#
clz64# = Word64# -> Word#
clz64#

-- |Count leading zeros in a word.
clz# :: Word# -> Word#
clz# :: Word# -> Word#
clz# = Word# -> Word#
clz#

-- |Count trailing zeros in the lower 8 bits of a word.
ctz8# :: Word# -> Word#
ctz8# :: Word# -> Word#
ctz8# = Word# -> Word#
ctz8#

-- |Count trailing zeros in the lower 16 bits of a word.
ctz16# :: Word# -> Word#
ctz16# :: Word# -> Word#
ctz16# = Word# -> Word#
ctz16#

-- |Count trailing zeros in the lower 32 bits of a word.
ctz32# :: Word# -> Word#
ctz32# :: Word# -> Word#
ctz32# = Word# -> Word#
ctz32#

-- |Count trailing zeros in a 64-bit word.
ctz64# :: Word64# -> Word#
ctz64# :: Word64# -> Word#
ctz64# = Word64# -> Word#
ctz64#

-- |Count trailing zeros in a word.
ctz# :: Word# -> Word#
ctz# :: Word# -> Word#
ctz# = Word# -> Word#
ctz#

-- |Swap bytes in the lower 16 bits of a word. The higher bytes are undefined. 
byteSwap16# :: Word# -> Word#
byteSwap16# :: Word# -> Word#
byteSwap16# = Word# -> Word#
byteSwap16#

-- |Swap bytes in the lower 32 bits of a word. The higher bytes are undefined. 
byteSwap32# :: Word# -> Word#
byteSwap32# :: Word# -> Word#
byteSwap32# = Word# -> Word#
byteSwap32#

-- |Swap bytes in a 64 bits of a word.
byteSwap64# :: Word64# -> Word64#
byteSwap64# :: Word64# -> Word64#
byteSwap64# = Word64# -> Word64#
byteSwap64#

-- |Swap bytes in a word.
byteSwap# :: Word# -> Word#
byteSwap# :: Word# -> Word#
byteSwap# = Word# -> Word#
byteSwap#

-- |Reverse the order of the bits in a 8-bit word.
bitReverse8# :: Word# -> Word#
bitReverse8# :: Word# -> Word#
bitReverse8# = Word# -> Word#
bitReverse8#

-- |Reverse the order of the bits in a 16-bit word.
bitReverse16# :: Word# -> Word#
bitReverse16# :: Word# -> Word#
bitReverse16# = Word# -> Word#
bitReverse16#

-- |Reverse the order of the bits in a 32-bit word.
bitReverse32# :: Word# -> Word#
bitReverse32# :: Word# -> Word#
bitReverse32# = Word# -> Word#
bitReverse32#

-- |Reverse the order of the bits in a 64-bit word.
bitReverse64# :: Word64# -> Word64#
bitReverse64# :: Word64# -> Word64#
bitReverse64# = Word64# -> Word64#
bitReverse64#

-- |Reverse the order of the bits in a word.
bitReverse# :: Word# -> Word#
bitReverse# :: Word# -> Word#
bitReverse# = Word# -> Word#
bitReverse#

narrow8Int# :: Int# -> Int#
narrow8Int# :: Int# -> Int#
narrow8Int# = Int# -> Int#
narrow8Int#

narrow16Int# :: Int# -> Int#
narrow16Int# :: Int# -> Int#
narrow16Int# = Int# -> Int#
narrow16Int#

narrow32Int# :: Int# -> Int#
narrow32Int# :: Int# -> Int#
narrow32Int# = Int# -> Int#
narrow32Int#

narrow8Word# :: Word# -> Word#
narrow8Word# :: Word# -> Word#
narrow8Word# = Word# -> Word#
narrow8Word#

narrow16Word# :: Word# -> Word#
narrow16Word# :: Word# -> Word#
narrow16Word# = Word# -> Word#
narrow16Word#

narrow32Word# :: Word# -> Word#
narrow32Word# :: Word# -> Word#
narrow32Word# = Word# -> Word#
narrow32Word#

data Double#

infix 4 >##
(>##) :: Double# -> Double# -> Int#
>## :: Double# -> Double# -> Int#
(>##) = Double# -> Double# -> Int#
(>##)

infix 4 >=##
(>=##) :: Double# -> Double# -> Int#
>=## :: Double# -> Double# -> Int#
(>=##) = Double# -> Double# -> Int#
(>=##)

infix 4 ==##
(==##) :: Double# -> Double# -> Int#
==## :: Double# -> Double# -> Int#
(==##) = Double# -> Double# -> Int#
(==##)

infix 4 /=##
(/=##) :: Double# -> Double# -> Int#
/=## :: Double# -> Double# -> Int#
(/=##) = Double# -> Double# -> Int#
(/=##)

infix 4 <##
(<##) :: Double# -> Double# -> Int#
<## :: Double# -> Double# -> Int#
(<##) = Double# -> Double# -> Int#
(<##)

infix 4 <=##
(<=##) :: Double# -> Double# -> Int#
<=## :: Double# -> Double# -> Int#
(<=##) = Double# -> Double# -> Int#
(<=##)

infixl 6 +##
(+##) :: Double# -> Double# -> Double#
+## :: Double# -> Double# -> Double#
(+##) = Double# -> Double# -> Double#
(+##)

infixl 6 -##
(-##) :: Double# -> Double# -> Double#
-## :: Double# -> Double# -> Double#
(-##) = Double# -> Double# -> Double#
(-##)

infixl 7 *##
(*##) :: Double# -> Double# -> Double#
*## :: Double# -> Double# -> Double#
(*##) = Double# -> Double# -> Double#
(*##)

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
infixl 7 /##
(/##) :: Double# -> Double# -> Double#
/## :: Double# -> Double# -> Double#
(/##) = Double# -> Double# -> Double#
(/##)

negateDouble# :: Double# -> Double#
negateDouble# :: Double# -> Double#
negateDouble# = Double# -> Double#
negateDouble#

fabsDouble# :: Double# -> Double#
fabsDouble# :: Double# -> Double#
fabsDouble# = Double# -> Double#
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# :: Double# -> Int#
double2Int# = Double# -> Int#
double2Int#

double2Float# :: Double# -> Float#
double2Float# :: Double# -> Float#
double2Float# = Double# -> Float#
double2Float#

expDouble# :: Double# -> Double#
expDouble# :: Double# -> Double#
expDouble# = Double# -> Double#
expDouble#

expm1Double# :: Double# -> Double#
expm1Double# :: Double# -> Double#
expm1Double# = Double# -> Double#
expm1Double#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
logDouble# :: Double# -> Double#
logDouble# :: Double# -> Double#
logDouble# = Double# -> Double#
logDouble#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
log1pDouble# :: Double# -> Double#
log1pDouble# :: Double# -> Double#
log1pDouble# = Double# -> Double#
log1pDouble#

sqrtDouble# :: Double# -> Double#
sqrtDouble# :: Double# -> Double#
sqrtDouble# = Double# -> Double#
sqrtDouble#

sinDouble# :: Double# -> Double#
sinDouble# :: Double# -> Double#
sinDouble# = Double# -> Double#
sinDouble#

cosDouble# :: Double# -> Double#
cosDouble# :: Double# -> Double#
cosDouble# = Double# -> Double#
cosDouble#

tanDouble# :: Double# -> Double#
tanDouble# :: Double# -> Double#
tanDouble# = Double# -> Double#
tanDouble#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
asinDouble# :: Double# -> Double#
asinDouble# :: Double# -> Double#
asinDouble# = Double# -> Double#
asinDouble#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
acosDouble# :: Double# -> Double#
acosDouble# :: Double# -> Double#
acosDouble# = Double# -> Double#
acosDouble#

atanDouble# :: Double# -> Double#
atanDouble# :: Double# -> Double#
atanDouble# = Double# -> Double#
atanDouble#

sinhDouble# :: Double# -> Double#
sinhDouble# :: Double# -> Double#
sinhDouble# = Double# -> Double#
sinhDouble#

coshDouble# :: Double# -> Double#
coshDouble# :: Double# -> Double#
coshDouble# = Double# -> Double#
coshDouble#

tanhDouble# :: Double# -> Double#
tanhDouble# :: Double# -> Double#
tanhDouble# = Double# -> Double#
tanhDouble#

asinhDouble# :: Double# -> Double#
asinhDouble# :: Double# -> Double#
asinhDouble# = Double# -> Double#
asinhDouble#

acoshDouble# :: Double# -> Double#
acoshDouble# :: Double# -> Double#
acoshDouble# = Double# -> Double#
acoshDouble#

atanhDouble# :: Double# -> Double#
atanhDouble# :: Double# -> Double#
atanhDouble# = Double# -> Double#
atanhDouble#

-- |Exponentiation.
(**##) :: Double# -> Double# -> Double#
**## :: Double# -> Double# -> Double#
(**##) = 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# :: Double# -> (# Int#, Word#, Word#, Int# #)
decodeDouble_2Int# = Double# -> (# Int#, Word#, Word#, Int# #)
decodeDouble_2Int#

-- |Decode @Double\#@ into mantissa and base-2 exponent.
decodeDouble_Int64# :: Double# -> (# Int64#,Int# #)
decodeDouble_Int64# :: Double# -> (# Int64#, Int# #)
decodeDouble_Int64# = Double# -> (# Int64#, Int# #)
decodeDouble_Int64#

data Float#

gtFloat# :: Float# -> Float# -> Int#
gtFloat# :: Float# -> Float# -> Int#
gtFloat# = Float# -> Float# -> Int#
gtFloat#

geFloat# :: Float# -> Float# -> Int#
geFloat# :: Float# -> Float# -> Int#
geFloat# = Float# -> Float# -> Int#
geFloat#

eqFloat# :: Float# -> Float# -> Int#
eqFloat# :: Float# -> Float# -> Int#
eqFloat# = Float# -> Float# -> Int#
eqFloat#

neFloat# :: Float# -> Float# -> Int#
neFloat# :: Float# -> Float# -> Int#
neFloat# = Float# -> Float# -> Int#
neFloat#

ltFloat# :: Float# -> Float# -> Int#
ltFloat# :: Float# -> Float# -> Int#
ltFloat# = Float# -> Float# -> Int#
ltFloat#

leFloat# :: Float# -> Float# -> Int#
leFloat# :: Float# -> Float# -> Int#
leFloat# = Float# -> Float# -> Int#
leFloat#

plusFloat# :: Float# -> Float# -> Float#
plusFloat# :: Float# -> Float# -> Float#
plusFloat# = Float# -> Float# -> Float#
plusFloat#

minusFloat# :: Float# -> Float# -> Float#
minusFloat# :: Float# -> Float# -> Float#
minusFloat# = Float# -> Float# -> Float#
minusFloat#

timesFloat# :: Float# -> Float# -> Float#
timesFloat# :: Float# -> Float# -> Float#
timesFloat# = Float# -> Float# -> Float#
timesFloat#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
divideFloat# :: Float# -> Float# -> Float#
divideFloat# :: Float# -> Float# -> Float#
divideFloat# = Float# -> Float# -> Float#
divideFloat#

negateFloat# :: Float# -> Float#
negateFloat# :: Float# -> Float#
negateFloat# = Float# -> Float#
negateFloat#

fabsFloat# :: Float# -> Float#
fabsFloat# :: Float# -> Float#
fabsFloat# = Float# -> Float#
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# :: Float# -> Int#
float2Int# = Float# -> Int#
float2Int#

expFloat# :: Float# -> Float#
expFloat# :: Float# -> Float#
expFloat# = Float# -> Float#
expFloat#

expm1Float# :: Float# -> Float#
expm1Float# :: Float# -> Float#
expm1Float# = Float# -> Float#
expm1Float#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
logFloat# :: Float# -> Float#
logFloat# :: Float# -> Float#
logFloat# = Float# -> Float#
logFloat#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
log1pFloat# :: Float# -> Float#
log1pFloat# :: Float# -> Float#
log1pFloat# = Float# -> Float#
log1pFloat#

sqrtFloat# :: Float# -> Float#
sqrtFloat# :: Float# -> Float#
sqrtFloat# = Float# -> Float#
sqrtFloat#

sinFloat# :: Float# -> Float#
sinFloat# :: Float# -> Float#
sinFloat# = Float# -> Float#
sinFloat#

cosFloat# :: Float# -> Float#
cosFloat# :: Float# -> Float#
cosFloat# = Float# -> Float#
cosFloat#

tanFloat# :: Float# -> Float#
tanFloat# :: Float# -> Float#
tanFloat# = Float# -> Float#
tanFloat#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
asinFloat# :: Float# -> Float#
asinFloat# :: Float# -> Float#
asinFloat# = Float# -> Float#
asinFloat#

-- |
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
acosFloat# :: Float# -> Float#
acosFloat# :: Float# -> Float#
acosFloat# = Float# -> Float#
acosFloat#

atanFloat# :: Float# -> Float#
atanFloat# :: Float# -> Float#
atanFloat# = Float# -> Float#
atanFloat#

sinhFloat# :: Float# -> Float#
sinhFloat# :: Float# -> Float#
sinhFloat# = Float# -> Float#
sinhFloat#

coshFloat# :: Float# -> Float#
coshFloat# :: Float# -> Float#
coshFloat# = Float# -> Float#
coshFloat#

tanhFloat# :: Float# -> Float#
tanhFloat# :: Float# -> Float#
tanhFloat# = Float# -> Float#
tanhFloat#

asinhFloat# :: Float# -> Float#
asinhFloat# :: Float# -> Float#
asinhFloat# = Float# -> Float#
asinhFloat#

acoshFloat# :: Float# -> Float#
acoshFloat# :: Float# -> Float#
acoshFloat# = Float# -> Float#
acoshFloat#

atanhFloat# :: Float# -> Float#
atanhFloat# :: Float# -> Float#
atanhFloat# = Float# -> Float#
atanhFloat#

powerFloat# :: Float# -> Float# -> Float#
powerFloat# :: Float# -> Float# -> Float#
powerFloat# = Float# -> Float# -> Float#
powerFloat#

float2Double# :: Float# -> Double#
float2Double# :: Float# -> Double#
float2Double# = Float# -> Double#
float2Double#

-- |Convert to integers.
--     First @Int\#@ in result is the mantissa; second is the exponent.
decodeFloat_Int# :: Float# -> (# Int#,Int# #)
decodeFloat_Int# :: Float# -> (# Int#, Int# #)
decodeFloat_Int# = Float# -> (# Int#, 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# -> v -> State# s -> (# State# s,MutableArray# s v #)
newArray# :: forall v s.
Int# -> v -> State# s -> (# State# s, MutableArray# s v #)
newArray# = Int# -> v -> State# s -> (# State# s, MutableArray# s v #)
forall v s.
Int# -> v -> State# s -> (# State# s, MutableArray# s v #)
newArray#

-- |Read from specified index of mutable array. Result is not yet evaluated.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readArray# :: MutableArray# s v -> Int# -> State# s -> (# State# s,v #)
readArray# :: forall s v.
MutableArray# s v -> Int# -> State# s -> (# State# s, v #)
readArray# = MutableArray# s v -> Int# -> State# s -> (# State# s, v #)
forall s v.
MutableArray# s v -> Int# -> State# s -> (# State# s, v #)
readArray#

-- |Write to specified index of mutable array.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
writeArray# :: MutableArray# s v -> Int# -> v -> State# s -> State# s
writeArray# :: forall s v. MutableArray# s v -> Int# -> v -> State# s -> State# s
writeArray# = MutableArray# s v -> Int# -> v -> State# s -> State# s
forall s v. MutableArray# s v -> Int# -> v -> State# s -> State# s
writeArray#

-- |Return the number of elements in the array.
sizeofArray# :: Array# v -> Int#
sizeofArray# :: forall v. Array# v -> Int#
sizeofArray# = Array# v -> Int#
forall v. Array# v -> Int#
sizeofArray#

-- |Return the number of elements in the array.
sizeofMutableArray# :: MutableArray# s v -> Int#
sizeofMutableArray# :: forall s v. MutableArray# s v -> Int#
sizeofMutableArray# = MutableArray# s v -> Int#
forall s v. MutableArray# s v -> Int#
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# v -> Int# -> (# v #)
indexArray# :: forall v. Array# v -> Int# -> (# v #)
indexArray# = Array# v -> Int# -> (# v #)
forall v. Array# v -> Int# -> (# v #)
indexArray#

-- |Make a mutable array immutable, without copying.
unsafeFreezeArray# :: MutableArray# s v -> State# s -> (# State# s,Array# v #)
unsafeFreezeArray# :: forall s v.
MutableArray# s v -> State# s -> (# State# s, Array# v #)
unsafeFreezeArray# = MutableArray# s v -> State# s -> (# State# s, Array# v #)
forall s v.
MutableArray# s v -> State# s -> (# State# s, Array# v #)
unsafeFreezeArray#

-- |Make an immutable array mutable, without copying.
unsafeThawArray# :: Array# v -> State# s -> (# State# s,MutableArray# s v #)
unsafeThawArray# :: forall v s.
Array# v -> State# s -> (# State# s, MutableArray# s v #)
unsafeThawArray# = Array# v -> State# s -> (# State# s, MutableArray# s v #)
forall v s.
Array# v -> State# s -> (# State# s, MutableArray# s v #)
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# v -> Int# -> MutableArray# s v -> Int# -> Int# -> State# s -> State# s
copyArray# :: forall v s.
Array# v
-> Int#
-> MutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
copyArray# = Array# v
-> Int#
-> MutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
forall v s.
Array# v
-> Int#
-> MutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
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 v -> Int# -> MutableArray# s v -> Int# -> Int# -> State# s -> State# s
copyMutableArray# :: forall s v.
MutableArray# s v
-> Int#
-> MutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
copyMutableArray# = MutableArray# s v
-> Int#
-> MutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
forall s v.
MutableArray# s v
-> Int#
-> MutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
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# v -> Int# -> Int# -> Array# v
cloneArray# :: forall v. Array# v -> Int# -> Int# -> Array# v
cloneArray# = Array# v -> Int# -> Int# -> Array# v
forall v. Array# v -> Int# -> Int# -> Array# v
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 v -> Int# -> Int# -> State# s -> (# State# s,MutableArray# s v #)
cloneMutableArray# :: forall s v.
MutableArray# s v
-> Int# -> Int# -> State# s -> (# State# s, MutableArray# s v #)
cloneMutableArray# = MutableArray# s v
-> Int# -> Int# -> State# s -> (# State# s, MutableArray# s v #)
forall s v.
MutableArray# s v
-> Int# -> Int# -> State# s -> (# State# s, MutableArray# s v #)
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 v -> Int# -> Int# -> State# s -> (# State# s,Array# v #)
freezeArray# :: forall s v.
MutableArray# s v
-> Int# -> Int# -> State# s -> (# State# s, Array# v #)
freezeArray# = MutableArray# s v
-> Int# -> Int# -> State# s -> (# State# s, Array# v #)
forall s v.
MutableArray# s v
-> Int# -> Int# -> State# s -> (# State# s, Array# v #)
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# v -> Int# -> Int# -> State# s -> (# State# s,MutableArray# s v #)
thawArray# :: forall v s.
Array# v
-> Int# -> Int# -> State# s -> (# State# s, MutableArray# s v #)
thawArray# = Array# v
-> Int# -> Int# -> State# s -> (# State# s, MutableArray# s v #)
forall v s.
Array# v
-> Int# -> Int# -> State# s -> (# State# s, MutableArray# s v #)
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 boxed value makes this function harder
--     to use correctly than @casIntArray\#@. All of the difficulties
--     of using @reallyUnsafePtrEquality\#@ correctly apply to
--     @casArray\#@ as well.
--    
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
casArray# :: MutableArray# s v -> Int# -> v -> v -> State# s -> (# State# s,Int#,v #)
casArray# :: forall s v.
MutableArray# s v
-> Int# -> v -> v -> State# s -> (# State# s, Int#, v #)
casArray# = MutableArray# s v
-> Int# -> v -> v -> State# s -> (# State# s, Int#, v #)
forall s v.
MutableArray# s v
-> Int# -> v -> v -> State# s -> (# State# s, Int#, v #)
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# -> v -> State# s -> (# State# s,SmallMutableArray# s v #)
newSmallArray# :: forall v s.
Int# -> v -> State# s -> (# State# s, SmallMutableArray# s v #)
newSmallArray# = Int# -> v -> State# s -> (# State# s, SmallMutableArray# s v #)
forall v s.
Int# -> v -> State# s -> (# State# s, SmallMutableArray# s v #)
newSmallArray#

-- |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 @getSizeofSmallMutableArray\#@.
shrinkSmallMutableArray# :: SmallMutableArray# s v -> Int# -> State# s -> State# s
shrinkSmallMutableArray# :: forall s v. SmallMutableArray# s v -> Int# -> State# s -> State# s
shrinkSmallMutableArray# = SmallMutableArray# s v -> Int# -> State# s -> State# s
forall s v. SmallMutableArray# s v -> Int# -> State# s -> State# s
shrinkSmallMutableArray#

-- |Read from specified index of mutable array. Result is not yet evaluated.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readSmallArray# :: SmallMutableArray# s v -> Int# -> State# s -> (# State# s,v #)
readSmallArray# :: forall s v.
SmallMutableArray# s v -> Int# -> State# s -> (# State# s, v #)
readSmallArray# = SmallMutableArray# s v -> Int# -> State# s -> (# State# s, v #)
forall s v.
SmallMutableArray# s v -> Int# -> State# s -> (# State# s, v #)
readSmallArray#

-- |Write to specified index of mutable array.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
writeSmallArray# :: SmallMutableArray# s v -> Int# -> v -> State# s -> State# s
writeSmallArray# :: forall s v.
SmallMutableArray# s v -> Int# -> v -> State# s -> State# s
writeSmallArray# = SmallMutableArray# s v -> Int# -> v -> State# s -> State# s
forall s v.
SmallMutableArray# s v -> Int# -> v -> State# s -> State# s
writeSmallArray#

-- |Return the number of elements in the array.
sizeofSmallArray# :: SmallArray# v -> Int#
sizeofSmallArray# :: forall v. SmallArray# v -> Int#
sizeofSmallArray# = SmallArray# v -> Int#
forall v. SmallArray# v -> Int#
sizeofSmallArray#

-- |Return the number of elements in the array. Note that this is deprecated
--    as it is unsafe in the presence of shrink and resize operations on the
--    same small mutable array.
{-# DEPRECATED sizeofSmallMutableArray# " Use 'getSizeofSmallMutableArray#' instead " #-}
sizeofSmallMutableArray# :: SmallMutableArray# s v -> Int#
sizeofSmallMutableArray# :: forall s v. SmallMutableArray# s v -> Int#
sizeofSmallMutableArray# = SmallMutableArray# s v -> Int#
forall s v. SmallMutableArray# s v -> Int#
sizeofSmallMutableArray#

-- |Return the number of elements in the array.
getSizeofSmallMutableArray# :: SmallMutableArray# s v -> State# s -> (# State# s,Int# #)
getSizeofSmallMutableArray# :: forall s v.
SmallMutableArray# s v -> State# s -> (# State# s, Int# #)
getSizeofSmallMutableArray# = SmallMutableArray# s v -> State# s -> (# State# s, Int# #)
forall s v.
SmallMutableArray# s v -> State# s -> (# State# s, Int# #)
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# v -> Int# -> (# v #)
indexSmallArray# :: forall v. SmallArray# v -> Int# -> (# v #)
indexSmallArray# = SmallArray# v -> Int# -> (# v #)
forall v. SmallArray# v -> Int# -> (# v #)
indexSmallArray#

-- |Make a mutable array immutable, without copying.
unsafeFreezeSmallArray# :: SmallMutableArray# s v -> State# s -> (# State# s,SmallArray# v #)
unsafeFreezeSmallArray# :: forall s v.
SmallMutableArray# s v -> State# s -> (# State# s, SmallArray# v #)
unsafeFreezeSmallArray# = SmallMutableArray# s v -> State# s -> (# State# s, SmallArray# v #)
forall s v.
SmallMutableArray# s v -> State# s -> (# State# s, SmallArray# v #)
unsafeFreezeSmallArray#

-- |Make an immutable array mutable, without copying.
unsafeThawSmallArray# :: SmallArray# v -> State# s -> (# State# s,SmallMutableArray# s v #)
unsafeThawSmallArray# :: forall v s.
SmallArray# v -> State# s -> (# State# s, SmallMutableArray# s v #)
unsafeThawSmallArray# = SmallArray# v -> State# s -> (# State# s, SmallMutableArray# s v #)
forall v s.
SmallArray# v -> State# s -> (# State# s, SmallMutableArray# s v #)
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# v -> Int# -> SmallMutableArray# s v -> Int# -> Int# -> State# s -> State# s
copySmallArray# :: forall v s.
SmallArray# v
-> Int#
-> SmallMutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
copySmallArray# = SmallArray# v
-> Int#
-> SmallMutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
forall v s.
SmallArray# v
-> Int#
-> SmallMutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
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 v -> Int# -> SmallMutableArray# s v -> Int# -> Int# -> State# s -> State# s
copySmallMutableArray# :: forall s v.
SmallMutableArray# s v
-> Int#
-> SmallMutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
copySmallMutableArray# = SmallMutableArray# s v
-> Int#
-> SmallMutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
forall s v.
SmallMutableArray# s v
-> Int#
-> SmallMutableArray# s v
-> Int#
-> Int#
-> State# s
-> State# s
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# v -> Int# -> Int# -> SmallArray# v
cloneSmallArray# :: forall v. SmallArray# v -> Int# -> Int# -> SmallArray# v
cloneSmallArray# = SmallArray# v -> Int# -> Int# -> SmallArray# v
forall v. SmallArray# v -> Int# -> Int# -> SmallArray# v
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 v -> Int# -> Int# -> State# s -> (# State# s,SmallMutableArray# s v #)
cloneSmallMutableArray# :: forall s v.
SmallMutableArray# s v
-> Int#
-> Int#
-> State# s
-> (# State# s, SmallMutableArray# s v #)
cloneSmallMutableArray# = SmallMutableArray# s v
-> Int#
-> Int#
-> State# s
-> (# State# s, SmallMutableArray# s v #)
forall s v.
SmallMutableArray# s v
-> Int#
-> Int#
-> State# s
-> (# State# s, SmallMutableArray# s v #)
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 v -> Int# -> Int# -> State# s -> (# State# s,SmallArray# v #)
freezeSmallArray# :: forall s v.
SmallMutableArray# s v
-> Int# -> Int# -> State# s -> (# State# s, SmallArray# v #)
freezeSmallArray# = SmallMutableArray# s v
-> Int# -> Int# -> State# s -> (# State# s, SmallArray# v #)
forall s v.
SmallMutableArray# s v
-> Int# -> Int# -> State# s -> (# State# s, SmallArray# v #)
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# v -> Int# -> Int# -> State# s -> (# State# s,SmallMutableArray# s v #)
thawSmallArray# :: forall v s.
SmallArray# v
-> Int#
-> Int#
-> State# s
-> (# State# s, SmallMutableArray# s v #)
thawSmallArray# = SmallArray# v
-> Int#
-> Int#
-> State# s
-> (# State# s, SmallMutableArray# s v #)
forall v s.
SmallArray# v
-> Int#
-> Int#
-> State# s
-> (# State# s, SmallMutableArray# s v #)
thawSmallArray#

-- |Unsafe, machine-level atomic compare and swap on an element within an array.
--     See the documentation of @casArray\#@.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
casSmallArray# :: SmallMutableArray# s v -> Int# -> v -> v -> State# s -> (# State# s,Int#,v #)
casSmallArray# :: forall s v.
SmallMutableArray# s v
-> Int# -> v -> v -> State# s -> (# State# s, Int#, v #)
casSmallArray# = SmallMutableArray# s v
-> Int# -> v -> v -> State# s -> (# State# s, Int#, v #)
forall s v.
SmallMutableArray# s v
-> Int# -> v -> v -> State# s -> (# State# s, Int#, v #)
casSmallArray#

-- |
--   A boxed, unlifted datatype representing a region of raw memory in the garbage-collected heap,
--   which is not scanned for pointers during garbage collection.
-- 
--   It is created by freezing a \'MutableByteArray#\' with \'unsafeFreezeByteArray#\'.
--   Freezing is essentially a no-op, as MutableByteArray# and ByteArray# share the same heap structure under the hood.
-- 
--   The immutable and mutable variants are commonly used for scenarios requiring high-performance data structures,
--   like Text, Primitive Vector, Unboxed Array, and ShortByteString.
--  
--   Another application of fundamental importance is \'Integer\', which is backed by \'ByteArray#\'.
--  
--   The representation on the heap of a Byte Array is:
--  
--   > +------------+-----------------+-----------------------+
--   > |            |                 |                       |
--   > |   HEADER   | SIZE (in bytes) |       PAYLOAD         |
--   > |            |                 |                       |
--   > +------------+-----------------+-----------------------+
--  
--   To obtain a pointer to actual payload (e.g., for FFI purposes) use \'byteArrayContents#\' or \'mutableByteArrayContents#\'.
--  
--   Alternatively, enabling the UnliftedFFITypes extension
--   allows to mention \'ByteArray#\' and \'MutableByteArray#\' in FFI type signatures directly.
data ByteArray#

-- | A mutable ByteAray#. It can be created in three ways:
-- 
--   * \'newByteArray#\': Create an unpinned array.
--   * \'newPinnedByteArray#\': This will create a pinned array,
--   * \'newAlignedPinnedByteArray#\': This will create a pinned array, with a custom alignment.
-- 
--   Unpinned arrays can be moved around during garbage collection, so you must not store or pass pointers to these values
--   if there is a chance for the garbage collector to kick in. That said, even unpinned arrays can be passed to unsafe FFI calls,
--   because no garbage collection happens during these unsafe calls
--   (see [Guaranteed Call Safety](https:\/\/ghc.gitlab.haskell.org\/ghc\/doc\/users_guide\/exts\/ffi.html#guaranteed-call-safety)
--   in the GHC Manual). For safe FFI calls, byte arrays must be not only pinned, but also kept alive by means of the keepAlive# function
--   for the duration of a call (that\'s because garbage collection cannot move a pinned array, but is free to scrap it altogether).
data MutableByteArray# s

-- |Create a new mutable byte array of specified size (in bytes), in
--     the specified state thread. The size of the memory underlying the
--     array will be rounded up to the platform\'s word size.
newByteArray# :: Int# -> State# s -> (# State# s,MutableByteArray# s #)
newByteArray# :: forall s. Int# -> State# s -> (# State# s, MutableByteArray# s #)
newByteArray# = Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall s. Int# -> State# s -> (# State# s, MutableByteArray# s #)
newByteArray#

-- |Like \'newByteArray#\' but GC guarantees not to move it.
newPinnedByteArray# :: Int# -> State# s -> (# State# s,MutableByteArray# s #)
newPinnedByteArray# :: forall s. Int# -> State# s -> (# State# s, MutableByteArray# s #)
newPinnedByteArray# = Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall s. Int# -> State# s -> (# State# s, MutableByteArray# s #)
newPinnedByteArray#

-- |Like \'newPinnedByteArray#\' but allow specifying an arbitrary
--     alignment, which must be a power of two.
newAlignedPinnedByteArray# :: Int# -> Int# -> State# s -> (# State# s,MutableByteArray# s #)
newAlignedPinnedByteArray# :: forall s.
Int# -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
newAlignedPinnedByteArray# = Int# -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall s.
Int# -> Int# -> State# s -> (# State# s, MutableByteArray# s #)
newAlignedPinnedByteArray#

-- |Determine whether a @MutableByteArray\#@ is guaranteed not to move
--    during GC.
isMutableByteArrayPinned# :: MutableByteArray# s -> Int#
isMutableByteArrayPinned# :: forall s. MutableByteArray# s -> Int#
isMutableByteArrayPinned# = MutableByteArray# s -> Int#
forall s. MutableByteArray# s -> Int#
isMutableByteArrayPinned#

-- |Determine whether a @ByteArray\#@ is guaranteed not to move during GC.
isByteArrayPinned# :: ByteArray# -> Int#
isByteArrayPinned# :: ByteArray# -> Int#
isByteArrayPinned# = ByteArray# -> Int#
isByteArrayPinned#

-- |Intended for use with pinned arrays; otherwise very unsafe!
byteArrayContents# :: ByteArray# -> Addr#
byteArrayContents# :: ByteArray# -> Addr#
byteArrayContents# = ByteArray# -> Addr#
byteArrayContents#

-- |Intended for use with pinned arrays; otherwise very unsafe!
mutableByteArrayContents# :: MutableByteArray# s -> Addr#
mutableByteArrayContents# :: forall s. MutableByteArray# s -> Addr#
mutableByteArrayContents# = MutableByteArray# s -> Addr#
forall s. MutableByteArray# s -> Addr#
mutableByteArrayContents#

-- |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 @getSizeofMutableByteArray\#@.
shrinkMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> State# s
shrinkMutableByteArray# :: forall s. MutableByteArray# s -> Int# -> State# s -> State# s
shrinkMutableByteArray# = MutableByteArray# s -> Int# -> State# s -> State# s
forall s. MutableByteArray# s -> Int# -> State# s -> State# s
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# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, MutableByteArray# s #)
resizeMutableByteArray# = MutableByteArray# s
-> Int# -> State# s -> (# State# s, MutableByteArray# s #)
forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, MutableByteArray# s #)
resizeMutableByteArray#

-- |Make a mutable byte array immutable, without copying.
unsafeFreezeByteArray# :: MutableByteArray# s -> State# s -> (# State# s,ByteArray# #)
unsafeFreezeByteArray# :: forall s.
MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
unsafeFreezeByteArray# = MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
forall s.
MutableByteArray# s -> State# s -> (# State# s, ByteArray# #)
unsafeFreezeByteArray#

-- |Return the size of the array in bytes.
sizeofByteArray# :: ByteArray# -> Int#
sizeofByteArray# :: ByteArray# -> Int#
sizeofByteArray# = ByteArray# -> Int#
sizeofByteArray#

-- |Return the size of the array in bytes. Note that this is deprecated as it is
--    unsafe in the presence of shrink and resize operations on the same mutable byte
--    array.
{-# DEPRECATED sizeofMutableByteArray# " Use 'getSizeofMutableByteArray#' instead " #-}
sizeofMutableByteArray# :: MutableByteArray# s -> Int#
sizeofMutableByteArray# :: forall s. MutableByteArray# s -> Int#
sizeofMutableByteArray# = MutableByteArray# s -> Int#
forall s. MutableByteArray# s -> Int#
sizeofMutableByteArray#

-- |Return the number of elements in the array.
getSizeofMutableByteArray# :: MutableByteArray# s -> State# s -> (# State# s,Int# #)
getSizeofMutableByteArray# :: forall s. MutableByteArray# s -> State# s -> (# State# s, Int# #)
getSizeofMutableByteArray# = MutableByteArray# s -> State# s -> (# State# s, Int# #)
forall s. MutableByteArray# s -> State# s -> (# State# s, Int# #)
getSizeofMutableByteArray#

-- |Read a 8-bit character; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexCharArray# :: ByteArray# -> Int# -> Char#
indexCharArray# :: ByteArray# -> Int# -> Char#
indexCharArray# = ByteArray# -> Int# -> Char#
indexCharArray#

-- |Read a 32-bit character; offset in 4-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWideCharArray# :: ByteArray# -> Int# -> Char#
indexWideCharArray# :: ByteArray# -> Int# -> Char#
indexWideCharArray# = ByteArray# -> Int# -> Char#
indexWideCharArray#

-- |Read a word-sized integer; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexIntArray# :: ByteArray# -> Int# -> Int#
indexIntArray# :: ByteArray# -> Int# -> Int#
indexIntArray# = ByteArray# -> Int# -> Int#
indexIntArray#

-- |Read a word-sized unsigned integer; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWordArray# :: ByteArray# -> Int# -> Word#
indexWordArray# :: ByteArray# -> Int# -> Word#
indexWordArray# = ByteArray# -> Int# -> Word#
indexWordArray#

-- |Read a machine address; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexAddrArray# :: ByteArray# -> Int# -> Addr#
indexAddrArray# :: ByteArray# -> Int# -> Addr#
indexAddrArray# = ByteArray# -> Int# -> Addr#
indexAddrArray#

-- |Read a single-precision floating-point value; offset in 4-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexFloatArray# :: ByteArray# -> Int# -> Float#
indexFloatArray# :: ByteArray# -> Int# -> Float#
indexFloatArray# = ByteArray# -> Int# -> Float#
indexFloatArray#

-- |Read a double-precision floating-point value; offset in 8-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexDoubleArray# :: ByteArray# -> Int# -> Double#
indexDoubleArray# :: ByteArray# -> Int# -> Double#
indexDoubleArray# = ByteArray# -> Int# -> Double#
indexDoubleArray#

-- |Read a @StablePtr#@ value; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexStablePtrArray# :: ByteArray# -> Int# -> StablePtr# a
indexStablePtrArray# :: forall a. ByteArray# -> Int# -> StablePtr# a
indexStablePtrArray# = ByteArray# -> Int# -> StablePtr# a
forall a. ByteArray# -> Int# -> StablePtr# a
indexStablePtrArray#

-- |Read a 8-bit signed integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexInt8Array# :: ByteArray# -> Int# -> Int8#
indexInt8Array# :: ByteArray# -> Int# -> Int8#
indexInt8Array# = ByteArray# -> Int# -> Int8#
indexInt8Array#

-- |Read a 16-bit signed integer; offset in 2-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexInt16Array# :: ByteArray# -> Int# -> Int16#
indexInt16Array# :: ByteArray# -> Int# -> Int16#
indexInt16Array# = ByteArray# -> Int# -> Int16#
indexInt16Array#

-- |Read a 32-bit signed integer; offset in 4-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexInt32Array# :: ByteArray# -> Int# -> Int32#
indexInt32Array# :: ByteArray# -> Int# -> Int32#
indexInt32Array# = ByteArray# -> Int# -> Int32#
indexInt32Array#

-- |Read a 64-bit signed integer; offset in 8-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexInt64Array# :: ByteArray# -> Int# -> Int64#
indexInt64Array# :: ByteArray# -> Int# -> Int64#
indexInt64Array# = ByteArray# -> Int# -> Int64#
indexInt64Array#

-- |Read a 8-bit unsigned integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8Array# :: ByteArray# -> Int# -> Word8#
indexWord8Array# :: ByteArray# -> Int# -> Word8#
indexWord8Array# = ByteArray# -> Int# -> Word8#
indexWord8Array#

-- |Read a 16-bit unsigned integer; offset in 2-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord16Array# :: ByteArray# -> Int# -> Word16#
indexWord16Array# :: ByteArray# -> Int# -> Word16#
indexWord16Array# = ByteArray# -> Int# -> Word16#
indexWord16Array#

-- |Read a 32-bit unsigned integer; offset in 4-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord32Array# :: ByteArray# -> Int# -> Word32#
indexWord32Array# :: ByteArray# -> Int# -> Word32#
indexWord32Array# = ByteArray# -> Int# -> Word32#
indexWord32Array#

-- |Read a 64-bit unsigned integer; offset in 8-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord64Array# :: ByteArray# -> Int# -> Word64#
indexWord64Array# :: ByteArray# -> Int# -> Word64#
indexWord64Array# = ByteArray# -> Int# -> Word64#
indexWord64Array#

-- |Read a 8-bit character; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char#
indexWord8ArrayAsChar# :: ByteArray# -> Int# -> Char#
indexWord8ArrayAsChar# = ByteArray# -> Int# -> Char#
indexWord8ArrayAsChar#

-- |Read a 32-bit character; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char#
indexWord8ArrayAsWideChar# :: ByteArray# -> Int# -> Char#
indexWord8ArrayAsWideChar# = ByteArray# -> Int# -> Char#
indexWord8ArrayAsWideChar#

-- |Read a word-sized integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int#
indexWord8ArrayAsInt# :: ByteArray# -> Int# -> Int#
indexWord8ArrayAsInt# = ByteArray# -> Int# -> Int#
indexWord8ArrayAsInt#

-- |Read a word-sized unsigned integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word#
indexWord8ArrayAsWord# :: ByteArray# -> Int# -> Word#
indexWord8ArrayAsWord# = ByteArray# -> Int# -> Word#
indexWord8ArrayAsWord#

-- |Read a machine address; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr#
indexWord8ArrayAsAddr# :: ByteArray# -> Int# -> Addr#
indexWord8ArrayAsAddr# = ByteArray# -> Int# -> Addr#
indexWord8ArrayAsAddr#

-- |Read a single-precision floating-point value; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float#
indexWord8ArrayAsFloat# :: ByteArray# -> Int# -> Float#
indexWord8ArrayAsFloat# = ByteArray# -> Int# -> Float#
indexWord8ArrayAsFloat#

-- |Read a double-precision floating-point value; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double#
indexWord8ArrayAsDouble# :: ByteArray# -> Int# -> Double#
indexWord8ArrayAsDouble# = ByteArray# -> Int# -> Double#
indexWord8ArrayAsDouble#

-- |Read a @StablePtr#@ value; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsStablePtr# :: ByteArray# -> Int# -> StablePtr# a
indexWord8ArrayAsStablePtr# :: forall a. ByteArray# -> Int# -> StablePtr# a
indexWord8ArrayAsStablePtr# = ByteArray# -> Int# -> StablePtr# a
forall a. ByteArray# -> Int# -> StablePtr# a
indexWord8ArrayAsStablePtr#

-- |Read a 16-bit signed integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16#
indexWord8ArrayAsInt16# :: ByteArray# -> Int# -> Int16#
indexWord8ArrayAsInt16# = ByteArray# -> Int# -> Int16#
indexWord8ArrayAsInt16#

-- |Read a 32-bit signed integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32#
indexWord8ArrayAsInt32# :: ByteArray# -> Int# -> Int32#
indexWord8ArrayAsInt32# = ByteArray# -> Int# -> Int32#
indexWord8ArrayAsInt32#

-- |Read a 64-bit signed integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64#
indexWord8ArrayAsInt64# :: ByteArray# -> Int# -> Int64#
indexWord8ArrayAsInt64# = ByteArray# -> Int# -> Int64#
indexWord8ArrayAsInt64#

-- |Read a 16-bit unsigned integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16#
indexWord8ArrayAsWord16# :: ByteArray# -> Int# -> Word16#
indexWord8ArrayAsWord16# = ByteArray# -> Int# -> Word16#
indexWord8ArrayAsWord16#

-- |Read a 32-bit unsigned integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32#
indexWord8ArrayAsWord32# :: ByteArray# -> Int# -> Word32#
indexWord8ArrayAsWord32# = ByteArray# -> Int# -> Word32#
indexWord8ArrayAsWord32#

-- |Read a 64-bit unsigned integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64#
indexWord8ArrayAsWord64# :: ByteArray# -> Int# -> Word64#
indexWord8ArrayAsWord64# = ByteArray# -> Int# -> Word64#
indexWord8ArrayAsWord64#

-- |Read a 8-bit character; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readCharArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Char# #)
readCharArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
readCharArray# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
readCharArray#

-- |Read a 32-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# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
readWideCharArray# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
readWideCharArray#

-- |Read a word-sized integer; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readIntArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #)
readIntArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
readIntArray# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
readIntArray#

-- |Read a word-sized unsigned integer; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWordArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #)
readWordArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
readWordArray# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
readWordArray#

-- |Read a machine address; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readAddrArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Addr# #)
readAddrArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Addr# #)
readAddrArray# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Addr# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Addr# #)
readAddrArray#

-- |Read a single-precision floating-point value; offset in 4-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readFloatArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Float# #)
readFloatArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Float# #)
readFloatArray# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Float# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Float# #)
readFloatArray#

-- |Read a double-precision floating-point value; offset in 8-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readDoubleArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Double# #)
readDoubleArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
readDoubleArray# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
readDoubleArray#

-- |Read a @StablePtr#@ value; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readStablePtrArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,StablePtr# a #)
readStablePtrArray# :: forall s a.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, StablePtr# a #)
readStablePtrArray# = MutableByteArray# s
-> Int# -> State# s -> (# State# s, StablePtr# a #)
forall s a.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, StablePtr# a #)
readStablePtrArray#

-- |Read a 8-bit signed integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readInt8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int8# #)
readInt8Array# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int8# #)
readInt8Array# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Int8# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int8# #)
readInt8Array#

-- |Read a 16-bit signed integer; offset in 2-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readInt16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int16# #)
readInt16Array# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16# #)
readInt16Array# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16# #)
readInt16Array#

-- |Read a 32-bit signed integer; offset in 4-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readInt32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int32# #)
readInt32Array# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32# #)
readInt32Array# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32# #)
readInt32Array#

-- |Read a 64-bit signed integer; offset in 8-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readInt64Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int64# #)
readInt64Array# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64# #)
readInt64Array# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64# #)
readInt64Array#

-- |Read a 8-bit unsigned integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word8# #)
readWord8Array# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word8# #)
readWord8Array# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Word8# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word8# #)
readWord8Array#

-- |Read a 16-bit unsigned integer; offset in 2-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord16Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word16# #)
readWord16Array# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16# #)
readWord16Array# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16# #)
readWord16Array#

-- |Read a 32-bit unsigned integer; offset in 4-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord32Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word32# #)
readWord32Array# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32# #)
readWord32Array# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32# #)
readWord32Array#

-- |Read a 64-bit unsigned integer; offset in 8-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord64Array# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word64# #)
readWord64Array# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64# #)
readWord64Array# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64# #)
readWord64Array#

-- |Read a 8-bit character; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsChar# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Char# #)
readWord8ArrayAsChar# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
readWord8ArrayAsChar# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
readWord8ArrayAsChar#

-- |Read a 32-bit character; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsWideChar# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Char# #)
readWord8ArrayAsWideChar# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
readWord8ArrayAsWideChar# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Char# #)
readWord8ArrayAsWideChar#

-- |Read a word-sized integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsInt# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int# #)
readWord8ArrayAsInt# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
readWord8ArrayAsInt# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int# #)
readWord8ArrayAsInt#

-- |Read a word-sized unsigned integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsWord# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word# #)
readWord8ArrayAsWord# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
readWord8ArrayAsWord# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word# #)
readWord8ArrayAsWord#

-- |Read a machine address; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsAddr# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Addr# #)
readWord8ArrayAsAddr# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Addr# #)
readWord8ArrayAsAddr# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Addr# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Addr# #)
readWord8ArrayAsAddr#

-- |Read a single-precision floating-point value; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsFloat# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Float# #)
readWord8ArrayAsFloat# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Float# #)
readWord8ArrayAsFloat# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Float# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Float# #)
readWord8ArrayAsFloat#

-- |Read a double-precision floating-point value; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsDouble# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Double# #)
readWord8ArrayAsDouble# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
readWord8ArrayAsDouble# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Double# #)
readWord8ArrayAsDouble#

-- |Read a @StablePtr#@ value; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsStablePtr# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,StablePtr# a #)
readWord8ArrayAsStablePtr# :: forall s a.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, StablePtr# a #)
readWord8ArrayAsStablePtr# = MutableByteArray# s
-> Int# -> State# s -> (# State# s, StablePtr# a #)
forall s a.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, StablePtr# a #)
readWord8ArrayAsStablePtr#

-- |Read a 16-bit signed integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsInt16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int16# #)
readWord8ArrayAsInt16# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16# #)
readWord8ArrayAsInt16# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16# #)
readWord8ArrayAsInt16#

-- |Read a 32-bit signed integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsInt32# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int32# #)
readWord8ArrayAsInt32# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32# #)
readWord8ArrayAsInt32# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32# #)
readWord8ArrayAsInt32#

-- |Read a 64-bit signed integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsInt64# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Int64# #)
readWord8ArrayAsInt64# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64# #)
readWord8ArrayAsInt64# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64# #)
readWord8ArrayAsInt64#

-- |Read a 16-bit unsigned integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsWord16# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word16# #)
readWord8ArrayAsWord16# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16# #)
readWord8ArrayAsWord16# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16# #)
readWord8ArrayAsWord16#

-- |Read a 32-bit unsigned integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsWord32# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word32# #)
readWord8ArrayAsWord32# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32# #)
readWord8ArrayAsWord32# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32# #)
readWord8ArrayAsWord32#

-- |Read a 64-bit unsigned integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
readWord8ArrayAsWord64# :: MutableByteArray# s -> Int# -> State# s -> (# State# s,Word64# #)
readWord8ArrayAsWord64# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64# #)
readWord8ArrayAsWord64# = MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64# #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64# #)
readWord8ArrayAsWord64#

-- |Write a 8-bit character; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
writeCharArray# :: MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
writeCharArray# :: forall s.
MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
writeCharArray# = MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
writeCharArray#

-- |Write a 32-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# :: forall s.
MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
writeWideCharArray# = MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> Char# -> State# s -> State# s
writeWideCharArray#

-- |Write a word-sized integer; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
writeIntArray# :: MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeIntArray# :: forall s.
MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeIntArray# = MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> Int# -> State# s -> State# s
writeIntArray#

-- |Write a word-sized unsigned integer; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
writeWordArray# :: MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeWordArray# :: forall s.
MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeWordArray# = MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> Word# -> State# s -> State# s
writeWordArray#

-- |Write a machine address; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
writeAddrArray# :: MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s
writeAddrArray# :: forall s.
MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s
writeAddrArray# = MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> Addr# -> State# s -> State# s
writeAddrArray#

-- |Write a single-precision floating-point value; offset in 4-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
writeFloatArray# :: MutableByteArray# s -> Int# -> Float# -> State# s -> State# s
writeFloatArray# :: forall s.
MutableByteArray# s -> Int# -> Float# -> State# s -> State# s
writeFloatArray# = MutableByteArray# s -> Int# -> Float# -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> Float# -> State# s -> State# s
writeFloatArray#

-- |Write a double-precision floating-point value; offset in 8-byte words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
writeDoubleArray# :: MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
writeDoubleArray# :: forall s.
MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
writeDoubleArray# = MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> Double# -> State# s -> State# s
writeDoubleArray#

-- |Write a @StablePtr#@ value; offset in machine words.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
writeStablePtrArray# :: MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s
writeStablePtrArray# :: forall s a.
MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s
writeStablePtrArray# = MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s
forall s a.
MutableByteArray# s -> Int# -> StablePtr# a -> State# s -> State# s
writeStablePtrArray#

-- |Write a 8-bit signed integer; offset in bytes.
-- 
-- __/Warning:/__ this can fail with an unchecked exception.
writeInt8Array# :: MutableByteArray# s -> Int# -> Int8# -> State# s -> State# s