{-# LANGUAGE MagicHash #-}
{-# LANGUAGE UnboxedTuples #-}
{-# LANGUAGE UndecidableInstances #-}

-- | Internally, all numbers are represented in little-endian format
-- (since that is what the host endianness is on any arch we'd be using).
-- 'Prim' instances for big endian variants actually do the conversion
-- at read/write time.
module Dahdit.Nums
  ( Word16LE (..)
  , Int16LE (..)
  , Word24LE (..)
  , Int24LE (..)
  , Word32LE (..)
  , Int32LE (..)
  , Word64LE (..)
  , Int64LE (..)
  , FloatLE (..)
  , DoubleLE (..)
  , Word16BE (..)
  , Int16BE (..)
  , Word24BE (..)
  , Int24BE (..)
  , Word32BE (..)
  , Int32BE (..)
  , Word64BE (..)
  , Int64BE (..)
  , FloatBE (..)
  , DoubleBE (..)
  )
where

import Dahdit.ShortWord ()
import Data.Bits (Bits (..), FiniteBits (..))
import Data.Coerce (Coercible, coerce)
import Data.Default (Default (..))
import Data.Int (Int16, Int32, Int64, Int8)
import Data.Primitive (Prim (..))
import Data.Primitive.ByteArray.Unaligned (PrimUnaligned (..))
import Data.Proxy (Proxy (..))
import Data.ShortWord (Int24, Word24)
import Data.Word (Word16, Word32, Word64, Word8, byteSwap16, byteSwap32, byteSwap64)
import GHC.Float (castDoubleToWord64, castFloatToWord32, castWord32ToFloat, castWord64ToDouble)

newtype Word16LE = Word16LE {Word16LE -> Word16
unWord16LE :: Word16}
  deriving stock (Int -> Word16LE -> ShowS
[Word16LE] -> ShowS
Word16LE -> String
(Int -> Word16LE -> ShowS)
-> (Word16LE -> String) -> ([Word16LE] -> ShowS) -> Show Word16LE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Word16LE -> ShowS
showsPrec :: Int -> Word16LE -> ShowS
$cshow :: Word16LE -> String
show :: Word16LE -> String
$cshowList :: [Word16LE] -> ShowS
showList :: [Word16LE] -> ShowS
Show)
  deriving newtype (Word16LE -> Word16LE -> Bool
(Word16LE -> Word16LE -> Bool)
-> (Word16LE -> Word16LE -> Bool) -> Eq Word16LE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Word16LE -> Word16LE -> Bool
== :: Word16LE -> Word16LE -> Bool
$c/= :: Word16LE -> Word16LE -> Bool
/= :: Word16LE -> Word16LE -> Bool
Eq, Eq Word16LE
Eq Word16LE =>
(Word16LE -> Word16LE -> Ordering)
-> (Word16LE -> Word16LE -> Bool)
-> (Word16LE -> Word16LE -> Bool)
-> (Word16LE -> Word16LE -> Bool)
-> (Word16LE -> Word16LE -> Bool)
-> (Word16LE -> Word16LE -> Word16LE)
-> (Word16LE -> Word16LE -> Word16LE)
-> Ord Word16LE
Word16LE -> Word16LE -> Bool
Word16LE -> Word16LE -> Ordering
Word16LE -> Word16LE -> Word16LE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Word16LE -> Word16LE -> Ordering
compare :: Word16LE -> Word16LE -> Ordering
$c< :: Word16LE -> Word16LE -> Bool
< :: Word16LE -> Word16LE -> Bool
$c<= :: Word16LE -> Word16LE -> Bool
<= :: Word16LE -> Word16LE -> Bool
$c> :: Word16LE -> Word16LE -> Bool
> :: Word16LE -> Word16LE -> Bool
$c>= :: Word16LE -> Word16LE -> Bool
>= :: Word16LE -> Word16LE -> Bool
$cmax :: Word16LE -> Word16LE -> Word16LE
max :: Word16LE -> Word16LE -> Word16LE
$cmin :: Word16LE -> Word16LE -> Word16LE
min :: Word16LE -> Word16LE -> Word16LE
Ord, Integer -> Word16LE
Word16LE -> Word16LE
Word16LE -> Word16LE -> Word16LE
(Word16LE -> Word16LE -> Word16LE)
-> (Word16LE -> Word16LE -> Word16LE)
-> (Word16LE -> Word16LE -> Word16LE)
-> (Word16LE -> Word16LE)
-> (Word16LE -> Word16LE)
-> (Word16LE -> Word16LE)
-> (Integer -> Word16LE)
-> Num Word16LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Word16LE -> Word16LE -> Word16LE
+ :: Word16LE -> Word16LE -> Word16LE
$c- :: Word16LE -> Word16LE -> Word16LE
- :: Word16LE -> Word16LE -> Word16LE
$c* :: Word16LE -> Word16LE -> Word16LE
* :: Word16LE -> Word16LE -> Word16LE
$cnegate :: Word16LE -> Word16LE
negate :: Word16LE -> Word16LE
$cabs :: Word16LE -> Word16LE
abs :: Word16LE -> Word16LE
$csignum :: Word16LE -> Word16LE
signum :: Word16LE -> Word16LE
$cfromInteger :: Integer -> Word16LE
fromInteger :: Integer -> Word16LE
Num, Int -> Word16LE
Word16LE -> Int
Word16LE -> [Word16LE]
Word16LE -> Word16LE
Word16LE -> Word16LE -> [Word16LE]
Word16LE -> Word16LE -> Word16LE -> [Word16LE]
(Word16LE -> Word16LE)
-> (Word16LE -> Word16LE)
-> (Int -> Word16LE)
-> (Word16LE -> Int)
-> (Word16LE -> [Word16LE])
-> (Word16LE -> Word16LE -> [Word16LE])
-> (Word16LE -> Word16LE -> [Word16LE])
-> (Word16LE -> Word16LE -> Word16LE -> [Word16LE])
-> Enum Word16LE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Word16LE -> Word16LE
succ :: Word16LE -> Word16LE
$cpred :: Word16LE -> Word16LE
pred :: Word16LE -> Word16LE
$ctoEnum :: Int -> Word16LE
toEnum :: Int -> Word16LE
$cfromEnum :: Word16LE -> Int
fromEnum :: Word16LE -> Int
$cenumFrom :: Word16LE -> [Word16LE]
enumFrom :: Word16LE -> [Word16LE]
$cenumFromThen :: Word16LE -> Word16LE -> [Word16LE]
enumFromThen :: Word16LE -> Word16LE -> [Word16LE]
$cenumFromTo :: Word16LE -> Word16LE -> [Word16LE]
enumFromTo :: Word16LE -> Word16LE -> [Word16LE]
$cenumFromThenTo :: Word16LE -> Word16LE -> Word16LE -> [Word16LE]
enumFromThenTo :: Word16LE -> Word16LE -> Word16LE -> [Word16LE]
Enum, Num Word16LE
Ord Word16LE
(Num Word16LE, Ord Word16LE) =>
(Word16LE -> Rational) -> Real Word16LE
Word16LE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Word16LE -> Rational
toRational :: Word16LE -> Rational
Real, Enum Word16LE
Real Word16LE
(Real Word16LE, Enum Word16LE) =>
(Word16LE -> Word16LE -> Word16LE)
-> (Word16LE -> Word16LE -> Word16LE)
-> (Word16LE -> Word16LE -> Word16LE)
-> (Word16LE -> Word16LE -> Word16LE)
-> (Word16LE -> Word16LE -> (Word16LE, Word16LE))
-> (Word16LE -> Word16LE -> (Word16LE, Word16LE))
-> (Word16LE -> Integer)
-> Integral Word16LE
Word16LE -> Integer
Word16LE -> Word16LE -> (Word16LE, Word16LE)
Word16LE -> Word16LE -> Word16LE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Word16LE -> Word16LE -> Word16LE
quot :: Word16LE -> Word16LE -> Word16LE
$crem :: Word16LE -> Word16LE -> Word16LE
rem :: Word16LE -> Word16LE -> Word16LE
$cdiv :: Word16LE -> Word16LE -> Word16LE
div :: Word16LE -> Word16LE -> Word16LE
$cmod :: Word16LE -> Word16LE -> Word16LE
mod :: Word16LE -> Word16LE -> Word16LE
$cquotRem :: Word16LE -> Word16LE -> (Word16LE, Word16LE)
quotRem :: Word16LE -> Word16LE -> (Word16LE, Word16LE)
$cdivMod :: Word16LE -> Word16LE -> (Word16LE, Word16LE)
divMod :: Word16LE -> Word16LE -> (Word16LE, Word16LE)
$ctoInteger :: Word16LE -> Integer
toInteger :: Word16LE -> Integer
Integral, Addr# -> Int# -> Word16LE
ByteArray# -> Int# -> Word16LE
Proxy Word16LE -> Int#
Word16LE -> Int#
(Proxy Word16LE -> Int#)
-> (Word16LE -> Int#)
-> (Proxy Word16LE -> Int#)
-> (Word16LE -> Int#)
-> (ByteArray# -> Int# -> Word16LE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word16LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word16LE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Word16LE -> State# s -> State# s)
-> (Addr# -> Int# -> Word16LE)
-> (forall s.
    Addr# -> Int# -> State# s -> (# State# s, Word16LE #))
-> (forall s. Addr# -> Int# -> Word16LE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Word16LE -> State# s -> State# s)
-> Prim Word16LE
forall s. Addr# -> Int# -> Int# -> Word16LE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Word16LE #)
forall s. Addr# -> Int# -> Word16LE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Word16LE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16LE #)
forall s.
MutableByteArray# s -> Int# -> Word16LE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Word16LE -> Int#
sizeOfType# :: Proxy Word16LE -> Int#
$csizeOf# :: Word16LE -> Int#
sizeOf# :: Word16LE -> Int#
$calignmentOfType# :: Proxy Word16LE -> Int#
alignmentOfType# :: Proxy Word16LE -> Int#
$calignment# :: Word16LE -> Int#
alignment# :: Word16LE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Word16LE
indexByteArray# :: ByteArray# -> Int# -> Word16LE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16LE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16LE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word16LE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word16LE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word16LE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word16LE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Word16LE
indexOffAddr# :: Addr# -> Int# -> Word16LE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word16LE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word16LE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Word16LE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Word16LE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word16LE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word16LE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Word16LE
(ByteArray# -> Int# -> Word16LE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word16LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word16LE -> State# s -> State# s)
-> PrimUnaligned Word16LE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16LE #)
forall s.
MutableByteArray# s -> Int# -> Word16LE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Word16LE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Word16LE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16LE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16LE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word16LE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word16LE -> State# s -> State# s
PrimUnaligned, Word16LE
Word16LE -> Default Word16LE
forall a. a -> Default a
$cdef :: Word16LE
def :: Word16LE
Default, Eq Word16LE
Word16LE
Eq Word16LE =>
(Word16LE -> Word16LE -> Word16LE)
-> (Word16LE -> Word16LE -> Word16LE)
-> (Word16LE -> Word16LE -> Word16LE)
-> (Word16LE -> Word16LE)
-> (Word16LE -> Int -> Word16LE)
-> (Word16LE -> Int -> Word16LE)
-> Word16LE
-> (Int -> Word16LE)
-> (Word16LE -> Int -> Word16LE)
-> (Word16LE -> Int -> Word16LE)
-> (Word16LE -> Int -> Word16LE)
-> (Word16LE -> Int -> Bool)
-> (Word16LE -> Maybe Int)
-> (Word16LE -> Int)
-> (Word16LE -> Bool)
-> (Word16LE -> Int -> Word16LE)
-> (Word16LE -> Int -> Word16LE)
-> (Word16LE -> Int -> Word16LE)
-> (Word16LE -> Int -> Word16LE)
-> (Word16LE -> Int -> Word16LE)
-> (Word16LE -> Int -> Word16LE)
-> (Word16LE -> Int)
-> Bits Word16LE
Int -> Word16LE
Word16LE -> Bool
Word16LE -> Int
Word16LE -> Maybe Int
Word16LE -> Word16LE
Word16LE -> Int -> Bool
Word16LE -> Int -> Word16LE
Word16LE -> Word16LE -> Word16LE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Word16LE -> Word16LE -> Word16LE
.&. :: Word16LE -> Word16LE -> Word16LE
$c.|. :: Word16LE -> Word16LE -> Word16LE
.|. :: Word16LE -> Word16LE -> Word16LE
$cxor :: Word16LE -> Word16LE -> Word16LE
xor :: Word16LE -> Word16LE -> Word16LE
$ccomplement :: Word16LE -> Word16LE
complement :: Word16LE -> Word16LE
$cshift :: Word16LE -> Int -> Word16LE
shift :: Word16LE -> Int -> Word16LE
$crotate :: Word16LE -> Int -> Word16LE
rotate :: Word16LE -> Int -> Word16LE
$czeroBits :: Word16LE
zeroBits :: Word16LE
$cbit :: Int -> Word16LE
bit :: Int -> Word16LE
$csetBit :: Word16LE -> Int -> Word16LE
setBit :: Word16LE -> Int -> Word16LE
$cclearBit :: Word16LE -> Int -> Word16LE
clearBit :: Word16LE -> Int -> Word16LE
$ccomplementBit :: Word16LE -> Int -> Word16LE
complementBit :: Word16LE -> Int -> Word16LE
$ctestBit :: Word16LE -> Int -> Bool
testBit :: Word16LE -> Int -> Bool
$cbitSizeMaybe :: Word16LE -> Maybe Int
bitSizeMaybe :: Word16LE -> Maybe Int
$cbitSize :: Word16LE -> Int
bitSize :: Word16LE -> Int
$cisSigned :: Word16LE -> Bool
isSigned :: Word16LE -> Bool
$cshiftL :: Word16LE -> Int -> Word16LE
shiftL :: Word16LE -> Int -> Word16LE
$cunsafeShiftL :: Word16LE -> Int -> Word16LE
unsafeShiftL :: Word16LE -> Int -> Word16LE
$cshiftR :: Word16LE -> Int -> Word16LE
shiftR :: Word16LE -> Int -> Word16LE
$cunsafeShiftR :: Word16LE -> Int -> Word16LE
unsafeShiftR :: Word16LE -> Int -> Word16LE
$crotateL :: Word16LE -> Int -> Word16LE
rotateL :: Word16LE -> Int -> Word16LE
$crotateR :: Word16LE -> Int -> Word16LE
rotateR :: Word16LE -> Int -> Word16LE
$cpopCount :: Word16LE -> Int
popCount :: Word16LE -> Int
Bits, Bits Word16LE
Bits Word16LE =>
(Word16LE -> Int)
-> (Word16LE -> Int) -> (Word16LE -> Int) -> FiniteBits Word16LE
Word16LE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Word16LE -> Int
finiteBitSize :: Word16LE -> Int
$ccountLeadingZeros :: Word16LE -> Int
countLeadingZeros :: Word16LE -> Int
$ccountTrailingZeros :: Word16LE -> Int
countTrailingZeros :: Word16LE -> Int
FiniteBits, Word16LE
Word16LE -> Word16LE -> Bounded Word16LE
forall a. a -> a -> Bounded a
$cminBound :: Word16LE
minBound :: Word16LE
$cmaxBound :: Word16LE
maxBound :: Word16LE
Bounded)

newtype Word24LE = Word24LE {Word24LE -> Word24
unWord24LE :: Word24}
  deriving stock (Int -> Word24LE -> ShowS
[Word24LE] -> ShowS
Word24LE -> String
(Int -> Word24LE -> ShowS)
-> (Word24LE -> String) -> ([Word24LE] -> ShowS) -> Show Word24LE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Word24LE -> ShowS
showsPrec :: Int -> Word24LE -> ShowS
$cshow :: Word24LE -> String
show :: Word24LE -> String
$cshowList :: [Word24LE] -> ShowS
showList :: [Word24LE] -> ShowS
Show)
  deriving newtype (Word24LE -> Word24LE -> Bool
(Word24LE -> Word24LE -> Bool)
-> (Word24LE -> Word24LE -> Bool) -> Eq Word24LE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Word24LE -> Word24LE -> Bool
== :: Word24LE -> Word24LE -> Bool
$c/= :: Word24LE -> Word24LE -> Bool
/= :: Word24LE -> Word24LE -> Bool
Eq, Eq Word24LE
Eq Word24LE =>
(Word24LE -> Word24LE -> Ordering)
-> (Word24LE -> Word24LE -> Bool)
-> (Word24LE -> Word24LE -> Bool)
-> (Word24LE -> Word24LE -> Bool)
-> (Word24LE -> Word24LE -> Bool)
-> (Word24LE -> Word24LE -> Word24LE)
-> (Word24LE -> Word24LE -> Word24LE)
-> Ord Word24LE
Word24LE -> Word24LE -> Bool
Word24LE -> Word24LE -> Ordering
Word24LE -> Word24LE -> Word24LE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Word24LE -> Word24LE -> Ordering
compare :: Word24LE -> Word24LE -> Ordering
$c< :: Word24LE -> Word24LE -> Bool
< :: Word24LE -> Word24LE -> Bool
$c<= :: Word24LE -> Word24LE -> Bool
<= :: Word24LE -> Word24LE -> Bool
$c> :: Word24LE -> Word24LE -> Bool
> :: Word24LE -> Word24LE -> Bool
$c>= :: Word24LE -> Word24LE -> Bool
>= :: Word24LE -> Word24LE -> Bool
$cmax :: Word24LE -> Word24LE -> Word24LE
max :: Word24LE -> Word24LE -> Word24LE
$cmin :: Word24LE -> Word24LE -> Word24LE
min :: Word24LE -> Word24LE -> Word24LE
Ord, Integer -> Word24LE
Word24LE -> Word24LE
Word24LE -> Word24LE -> Word24LE
(Word24LE -> Word24LE -> Word24LE)
-> (Word24LE -> Word24LE -> Word24LE)
-> (Word24LE -> Word24LE -> Word24LE)
-> (Word24LE -> Word24LE)
-> (Word24LE -> Word24LE)
-> (Word24LE -> Word24LE)
-> (Integer -> Word24LE)
-> Num Word24LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Word24LE -> Word24LE -> Word24LE
+ :: Word24LE -> Word24LE -> Word24LE
$c- :: Word24LE -> Word24LE -> Word24LE
- :: Word24LE -> Word24LE -> Word24LE
$c* :: Word24LE -> Word24LE -> Word24LE
* :: Word24LE -> Word24LE -> Word24LE
$cnegate :: Word24LE -> Word24LE
negate :: Word24LE -> Word24LE
$cabs :: Word24LE -> Word24LE
abs :: Word24LE -> Word24LE
$csignum :: Word24LE -> Word24LE
signum :: Word24LE -> Word24LE
$cfromInteger :: Integer -> Word24LE
fromInteger :: Integer -> Word24LE
Num, Int -> Word24LE
Word24LE -> Int
Word24LE -> [Word24LE]
Word24LE -> Word24LE
Word24LE -> Word24LE -> [Word24LE]
Word24LE -> Word24LE -> Word24LE -> [Word24LE]
(Word24LE -> Word24LE)
-> (Word24LE -> Word24LE)
-> (Int -> Word24LE)
-> (Word24LE -> Int)
-> (Word24LE -> [Word24LE])
-> (Word24LE -> Word24LE -> [Word24LE])
-> (Word24LE -> Word24LE -> [Word24LE])
-> (Word24LE -> Word24LE -> Word24LE -> [Word24LE])
-> Enum Word24LE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Word24LE -> Word24LE
succ :: Word24LE -> Word24LE
$cpred :: Word24LE -> Word24LE
pred :: Word24LE -> Word24LE
$ctoEnum :: Int -> Word24LE
toEnum :: Int -> Word24LE
$cfromEnum :: Word24LE -> Int
fromEnum :: Word24LE -> Int
$cenumFrom :: Word24LE -> [Word24LE]
enumFrom :: Word24LE -> [Word24LE]
$cenumFromThen :: Word24LE -> Word24LE -> [Word24LE]
enumFromThen :: Word24LE -> Word24LE -> [Word24LE]
$cenumFromTo :: Word24LE -> Word24LE -> [Word24LE]
enumFromTo :: Word24LE -> Word24LE -> [Word24LE]
$cenumFromThenTo :: Word24LE -> Word24LE -> Word24LE -> [Word24LE]
enumFromThenTo :: Word24LE -> Word24LE -> Word24LE -> [Word24LE]
Enum, Num Word24LE
Ord Word24LE
(Num Word24LE, Ord Word24LE) =>
(Word24LE -> Rational) -> Real Word24LE
Word24LE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Word24LE -> Rational
toRational :: Word24LE -> Rational
Real, Enum Word24LE
Real Word24LE
(Real Word24LE, Enum Word24LE) =>
(Word24LE -> Word24LE -> Word24LE)
-> (Word24LE -> Word24LE -> Word24LE)
-> (Word24LE -> Word24LE -> Word24LE)
-> (Word24LE -> Word24LE -> Word24LE)
-> (Word24LE -> Word24LE -> (Word24LE, Word24LE))
-> (Word24LE -> Word24LE -> (Word24LE, Word24LE))
-> (Word24LE -> Integer)
-> Integral Word24LE
Word24LE -> Integer
Word24LE -> Word24LE -> (Word24LE, Word24LE)
Word24LE -> Word24LE -> Word24LE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Word24LE -> Word24LE -> Word24LE
quot :: Word24LE -> Word24LE -> Word24LE
$crem :: Word24LE -> Word24LE -> Word24LE
rem :: Word24LE -> Word24LE -> Word24LE
$cdiv :: Word24LE -> Word24LE -> Word24LE
div :: Word24LE -> Word24LE -> Word24LE
$cmod :: Word24LE -> Word24LE -> Word24LE
mod :: Word24LE -> Word24LE -> Word24LE
$cquotRem :: Word24LE -> Word24LE -> (Word24LE, Word24LE)
quotRem :: Word24LE -> Word24LE -> (Word24LE, Word24LE)
$cdivMod :: Word24LE -> Word24LE -> (Word24LE, Word24LE)
divMod :: Word24LE -> Word24LE -> (Word24LE, Word24LE)
$ctoInteger :: Word24LE -> Integer
toInteger :: Word24LE -> Integer
Integral, Addr# -> Int# -> Word24LE
ByteArray# -> Int# -> Word24LE
Proxy Word24LE -> Int#
Word24LE -> Int#
(Proxy Word24LE -> Int#)
-> (Word24LE -> Int#)
-> (Proxy Word24LE -> Int#)
-> (Word24LE -> Int#)
-> (ByteArray# -> Int# -> Word24LE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word24LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word24LE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Word24LE -> State# s -> State# s)
-> (Addr# -> Int# -> Word24LE)
-> (forall s.
    Addr# -> Int# -> State# s -> (# State# s, Word24LE #))
-> (forall s. Addr# -> Int# -> Word24LE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Word24LE -> State# s -> State# s)
-> Prim Word24LE
forall s. Addr# -> Int# -> Int# -> Word24LE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Word24LE #)
forall s. Addr# -> Int# -> Word24LE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Word24LE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24LE #)
forall s.
MutableByteArray# s -> Int# -> Word24LE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Word24LE -> Int#
sizeOfType# :: Proxy Word24LE -> Int#
$csizeOf# :: Word24LE -> Int#
sizeOf# :: Word24LE -> Int#
$calignmentOfType# :: Proxy Word24LE -> Int#
alignmentOfType# :: Proxy Word24LE -> Int#
$calignment# :: Word24LE -> Int#
alignment# :: Word24LE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Word24LE
indexByteArray# :: ByteArray# -> Int# -> Word24LE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24LE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24LE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word24LE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word24LE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word24LE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word24LE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Word24LE
indexOffAddr# :: Addr# -> Int# -> Word24LE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word24LE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word24LE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Word24LE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Word24LE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word24LE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word24LE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Word24LE
(ByteArray# -> Int# -> Word24LE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word24LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word24LE -> State# s -> State# s)
-> PrimUnaligned Word24LE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24LE #)
forall s.
MutableByteArray# s -> Int# -> Word24LE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Word24LE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Word24LE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24LE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24LE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word24LE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word24LE -> State# s -> State# s
PrimUnaligned, Word24LE
Word24LE -> Default Word24LE
forall a. a -> Default a
$cdef :: Word24LE
def :: Word24LE
Default, Eq Word24LE
Word24LE
Eq Word24LE =>
(Word24LE -> Word24LE -> Word24LE)
-> (Word24LE -> Word24LE -> Word24LE)
-> (Word24LE -> Word24LE -> Word24LE)
-> (Word24LE -> Word24LE)
-> (Word24LE -> Int -> Word24LE)
-> (Word24LE -> Int -> Word24LE)
-> Word24LE
-> (Int -> Word24LE)
-> (Word24LE -> Int -> Word24LE)
-> (Word24LE -> Int -> Word24LE)
-> (Word24LE -> Int -> Word24LE)
-> (Word24LE -> Int -> Bool)
-> (Word24LE -> Maybe Int)
-> (Word24LE -> Int)
-> (Word24LE -> Bool)
-> (Word24LE -> Int -> Word24LE)
-> (Word24LE -> Int -> Word24LE)
-> (Word24LE -> Int -> Word24LE)
-> (Word24LE -> Int -> Word24LE)
-> (Word24LE -> Int -> Word24LE)
-> (Word24LE -> Int -> Word24LE)
-> (Word24LE -> Int)
-> Bits Word24LE
Int -> Word24LE
Word24LE -> Bool
Word24LE -> Int
Word24LE -> Maybe Int
Word24LE -> Word24LE
Word24LE -> Int -> Bool
Word24LE -> Int -> Word24LE
Word24LE -> Word24LE -> Word24LE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Word24LE -> Word24LE -> Word24LE
.&. :: Word24LE -> Word24LE -> Word24LE
$c.|. :: Word24LE -> Word24LE -> Word24LE
.|. :: Word24LE -> Word24LE -> Word24LE
$cxor :: Word24LE -> Word24LE -> Word24LE
xor :: Word24LE -> Word24LE -> Word24LE
$ccomplement :: Word24LE -> Word24LE
complement :: Word24LE -> Word24LE
$cshift :: Word24LE -> Int -> Word24LE
shift :: Word24LE -> Int -> Word24LE
$crotate :: Word24LE -> Int -> Word24LE
rotate :: Word24LE -> Int -> Word24LE
$czeroBits :: Word24LE
zeroBits :: Word24LE
$cbit :: Int -> Word24LE
bit :: Int -> Word24LE
$csetBit :: Word24LE -> Int -> Word24LE
setBit :: Word24LE -> Int -> Word24LE
$cclearBit :: Word24LE -> Int -> Word24LE
clearBit :: Word24LE -> Int -> Word24LE
$ccomplementBit :: Word24LE -> Int -> Word24LE
complementBit :: Word24LE -> Int -> Word24LE
$ctestBit :: Word24LE -> Int -> Bool
testBit :: Word24LE -> Int -> Bool
$cbitSizeMaybe :: Word24LE -> Maybe Int
bitSizeMaybe :: Word24LE -> Maybe Int
$cbitSize :: Word24LE -> Int
bitSize :: Word24LE -> Int
$cisSigned :: Word24LE -> Bool
isSigned :: Word24LE -> Bool
$cshiftL :: Word24LE -> Int -> Word24LE
shiftL :: Word24LE -> Int -> Word24LE
$cunsafeShiftL :: Word24LE -> Int -> Word24LE
unsafeShiftL :: Word24LE -> Int -> Word24LE
$cshiftR :: Word24LE -> Int -> Word24LE
shiftR :: Word24LE -> Int -> Word24LE
$cunsafeShiftR :: Word24LE -> Int -> Word24LE
unsafeShiftR :: Word24LE -> Int -> Word24LE
$crotateL :: Word24LE -> Int -> Word24LE
rotateL :: Word24LE -> Int -> Word24LE
$crotateR :: Word24LE -> Int -> Word24LE
rotateR :: Word24LE -> Int -> Word24LE
$cpopCount :: Word24LE -> Int
popCount :: Word24LE -> Int
Bits, Bits Word24LE
Bits Word24LE =>
(Word24LE -> Int)
-> (Word24LE -> Int) -> (Word24LE -> Int) -> FiniteBits Word24LE
Word24LE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Word24LE -> Int
finiteBitSize :: Word24LE -> Int
$ccountLeadingZeros :: Word24LE -> Int
countLeadingZeros :: Word24LE -> Int
$ccountTrailingZeros :: Word24LE -> Int
countTrailingZeros :: Word24LE -> Int
FiniteBits, Word24LE
Word24LE -> Word24LE -> Bounded Word24LE
forall a. a -> a -> Bounded a
$cminBound :: Word24LE
minBound :: Word24LE
$cmaxBound :: Word24LE
maxBound :: Word24LE
Bounded)

newtype Word32LE = Word32LE {Word32LE -> Word32
unWord32LE :: Word32}
  deriving stock (Int -> Word32LE -> ShowS
[Word32LE] -> ShowS
Word32LE -> String
(Int -> Word32LE -> ShowS)
-> (Word32LE -> String) -> ([Word32LE] -> ShowS) -> Show Word32LE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Word32LE -> ShowS
showsPrec :: Int -> Word32LE -> ShowS
$cshow :: Word32LE -> String
show :: Word32LE -> String
$cshowList :: [Word32LE] -> ShowS
showList :: [Word32LE] -> ShowS
Show)
  deriving newtype (Word32LE -> Word32LE -> Bool
(Word32LE -> Word32LE -> Bool)
-> (Word32LE -> Word32LE -> Bool) -> Eq Word32LE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Word32LE -> Word32LE -> Bool
== :: Word32LE -> Word32LE -> Bool
$c/= :: Word32LE -> Word32LE -> Bool
/= :: Word32LE -> Word32LE -> Bool
Eq, Eq Word32LE
Eq Word32LE =>
(Word32LE -> Word32LE -> Ordering)
-> (Word32LE -> Word32LE -> Bool)
-> (Word32LE -> Word32LE -> Bool)
-> (Word32LE -> Word32LE -> Bool)
-> (Word32LE -> Word32LE -> Bool)
-> (Word32LE -> Word32LE -> Word32LE)
-> (Word32LE -> Word32LE -> Word32LE)
-> Ord Word32LE
Word32LE -> Word32LE -> Bool
Word32LE -> Word32LE -> Ordering
Word32LE -> Word32LE -> Word32LE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Word32LE -> Word32LE -> Ordering
compare :: Word32LE -> Word32LE -> Ordering
$c< :: Word32LE -> Word32LE -> Bool
< :: Word32LE -> Word32LE -> Bool
$c<= :: Word32LE -> Word32LE -> Bool
<= :: Word32LE -> Word32LE -> Bool
$c> :: Word32LE -> Word32LE -> Bool
> :: Word32LE -> Word32LE -> Bool
$c>= :: Word32LE -> Word32LE -> Bool
>= :: Word32LE -> Word32LE -> Bool
$cmax :: Word32LE -> Word32LE -> Word32LE
max :: Word32LE -> Word32LE -> Word32LE
$cmin :: Word32LE -> Word32LE -> Word32LE
min :: Word32LE -> Word32LE -> Word32LE
Ord, Integer -> Word32LE
Word32LE -> Word32LE
Word32LE -> Word32LE -> Word32LE
(Word32LE -> Word32LE -> Word32LE)
-> (Word32LE -> Word32LE -> Word32LE)
-> (Word32LE -> Word32LE -> Word32LE)
-> (Word32LE -> Word32LE)
-> (Word32LE -> Word32LE)
-> (Word32LE -> Word32LE)
-> (Integer -> Word32LE)
-> Num Word32LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Word32LE -> Word32LE -> Word32LE
+ :: Word32LE -> Word32LE -> Word32LE
$c- :: Word32LE -> Word32LE -> Word32LE
- :: Word32LE -> Word32LE -> Word32LE
$c* :: Word32LE -> Word32LE -> Word32LE
* :: Word32LE -> Word32LE -> Word32LE
$cnegate :: Word32LE -> Word32LE
negate :: Word32LE -> Word32LE
$cabs :: Word32LE -> Word32LE
abs :: Word32LE -> Word32LE
$csignum :: Word32LE -> Word32LE
signum :: Word32LE -> Word32LE
$cfromInteger :: Integer -> Word32LE
fromInteger :: Integer -> Word32LE
Num, Int -> Word32LE
Word32LE -> Int
Word32LE -> [Word32LE]
Word32LE -> Word32LE
Word32LE -> Word32LE -> [Word32LE]
Word32LE -> Word32LE -> Word32LE -> [Word32LE]
(Word32LE -> Word32LE)
-> (Word32LE -> Word32LE)
-> (Int -> Word32LE)
-> (Word32LE -> Int)
-> (Word32LE -> [Word32LE])
-> (Word32LE -> Word32LE -> [Word32LE])
-> (Word32LE -> Word32LE -> [Word32LE])
-> (Word32LE -> Word32LE -> Word32LE -> [Word32LE])
-> Enum Word32LE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Word32LE -> Word32LE
succ :: Word32LE -> Word32LE
$cpred :: Word32LE -> Word32LE
pred :: Word32LE -> Word32LE
$ctoEnum :: Int -> Word32LE
toEnum :: Int -> Word32LE
$cfromEnum :: Word32LE -> Int
fromEnum :: Word32LE -> Int
$cenumFrom :: Word32LE -> [Word32LE]
enumFrom :: Word32LE -> [Word32LE]
$cenumFromThen :: Word32LE -> Word32LE -> [Word32LE]
enumFromThen :: Word32LE -> Word32LE -> [Word32LE]
$cenumFromTo :: Word32LE -> Word32LE -> [Word32LE]
enumFromTo :: Word32LE -> Word32LE -> [Word32LE]
$cenumFromThenTo :: Word32LE -> Word32LE -> Word32LE -> [Word32LE]
enumFromThenTo :: Word32LE -> Word32LE -> Word32LE -> [Word32LE]
Enum, Num Word32LE
Ord Word32LE
(Num Word32LE, Ord Word32LE) =>
(Word32LE -> Rational) -> Real Word32LE
Word32LE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Word32LE -> Rational
toRational :: Word32LE -> Rational
Real, Enum Word32LE
Real Word32LE
(Real Word32LE, Enum Word32LE) =>
(Word32LE -> Word32LE -> Word32LE)
-> (Word32LE -> Word32LE -> Word32LE)
-> (Word32LE -> Word32LE -> Word32LE)
-> (Word32LE -> Word32LE -> Word32LE)
-> (Word32LE -> Word32LE -> (Word32LE, Word32LE))
-> (Word32LE -> Word32LE -> (Word32LE, Word32LE))
-> (Word32LE -> Integer)
-> Integral Word32LE
Word32LE -> Integer
Word32LE -> Word32LE -> (Word32LE, Word32LE)
Word32LE -> Word32LE -> Word32LE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Word32LE -> Word32LE -> Word32LE
quot :: Word32LE -> Word32LE -> Word32LE
$crem :: Word32LE -> Word32LE -> Word32LE
rem :: Word32LE -> Word32LE -> Word32LE
$cdiv :: Word32LE -> Word32LE -> Word32LE
div :: Word32LE -> Word32LE -> Word32LE
$cmod :: Word32LE -> Word32LE -> Word32LE
mod :: Word32LE -> Word32LE -> Word32LE
$cquotRem :: Word32LE -> Word32LE -> (Word32LE, Word32LE)
quotRem :: Word32LE -> Word32LE -> (Word32LE, Word32LE)
$cdivMod :: Word32LE -> Word32LE -> (Word32LE, Word32LE)
divMod :: Word32LE -> Word32LE -> (Word32LE, Word32LE)
$ctoInteger :: Word32LE -> Integer
toInteger :: Word32LE -> Integer
Integral, Addr# -> Int# -> Word32LE
ByteArray# -> Int# -> Word32LE
Proxy Word32LE -> Int#
Word32LE -> Int#
(Proxy Word32LE -> Int#)
-> (Word32LE -> Int#)
-> (Proxy Word32LE -> Int#)
-> (Word32LE -> Int#)
-> (ByteArray# -> Int# -> Word32LE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word32LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word32LE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Word32LE -> State# s -> State# s)
-> (Addr# -> Int# -> Word32LE)
-> (forall s.
    Addr# -> Int# -> State# s -> (# State# s, Word32LE #))
-> (forall s. Addr# -> Int# -> Word32LE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Word32LE -> State# s -> State# s)
-> Prim Word32LE
forall s. Addr# -> Int# -> Int# -> Word32LE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Word32LE #)
forall s. Addr# -> Int# -> Word32LE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Word32LE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32LE #)
forall s.
MutableByteArray# s -> Int# -> Word32LE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Word32LE -> Int#
sizeOfType# :: Proxy Word32LE -> Int#
$csizeOf# :: Word32LE -> Int#
sizeOf# :: Word32LE -> Int#
$calignmentOfType# :: Proxy Word32LE -> Int#
alignmentOfType# :: Proxy Word32LE -> Int#
$calignment# :: Word32LE -> Int#
alignment# :: Word32LE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Word32LE
indexByteArray# :: ByteArray# -> Int# -> Word32LE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32LE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32LE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word32LE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word32LE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word32LE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word32LE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Word32LE
indexOffAddr# :: Addr# -> Int# -> Word32LE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word32LE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word32LE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Word32LE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Word32LE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word32LE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word32LE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Word32LE
(ByteArray# -> Int# -> Word32LE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word32LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word32LE -> State# s -> State# s)
-> PrimUnaligned Word32LE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32LE #)
forall s.
MutableByteArray# s -> Int# -> Word32LE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Word32LE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Word32LE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32LE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32LE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word32LE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word32LE -> State# s -> State# s
PrimUnaligned, Word32LE
Word32LE -> Default Word32LE
forall a. a -> Default a
$cdef :: Word32LE
def :: Word32LE
Default, Eq Word32LE
Word32LE
Eq Word32LE =>
(Word32LE -> Word32LE -> Word32LE)
-> (Word32LE -> Word32LE -> Word32LE)
-> (Word32LE -> Word32LE -> Word32LE)
-> (Word32LE -> Word32LE)
-> (Word32LE -> Int -> Word32LE)
-> (Word32LE -> Int -> Word32LE)
-> Word32LE
-> (Int -> Word32LE)
-> (Word32LE -> Int -> Word32LE)
-> (Word32LE -> Int -> Word32LE)
-> (Word32LE -> Int -> Word32LE)
-> (Word32LE -> Int -> Bool)
-> (Word32LE -> Maybe Int)
-> (Word32LE -> Int)
-> (Word32LE -> Bool)
-> (Word32LE -> Int -> Word32LE)
-> (Word32LE -> Int -> Word32LE)
-> (Word32LE -> Int -> Word32LE)
-> (Word32LE -> Int -> Word32LE)
-> (Word32LE -> Int -> Word32LE)
-> (Word32LE -> Int -> Word32LE)
-> (Word32LE -> Int)
-> Bits Word32LE
Int -> Word32LE
Word32LE -> Bool
Word32LE -> Int
Word32LE -> Maybe Int
Word32LE -> Word32LE
Word32LE -> Int -> Bool
Word32LE -> Int -> Word32LE
Word32LE -> Word32LE -> Word32LE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Word32LE -> Word32LE -> Word32LE
.&. :: Word32LE -> Word32LE -> Word32LE
$c.|. :: Word32LE -> Word32LE -> Word32LE
.|. :: Word32LE -> Word32LE -> Word32LE
$cxor :: Word32LE -> Word32LE -> Word32LE
xor :: Word32LE -> Word32LE -> Word32LE
$ccomplement :: Word32LE -> Word32LE
complement :: Word32LE -> Word32LE
$cshift :: Word32LE -> Int -> Word32LE
shift :: Word32LE -> Int -> Word32LE
$crotate :: Word32LE -> Int -> Word32LE
rotate :: Word32LE -> Int -> Word32LE
$czeroBits :: Word32LE
zeroBits :: Word32LE
$cbit :: Int -> Word32LE
bit :: Int -> Word32LE
$csetBit :: Word32LE -> Int -> Word32LE
setBit :: Word32LE -> Int -> Word32LE
$cclearBit :: Word32LE -> Int -> Word32LE
clearBit :: Word32LE -> Int -> Word32LE
$ccomplementBit :: Word32LE -> Int -> Word32LE
complementBit :: Word32LE -> Int -> Word32LE
$ctestBit :: Word32LE -> Int -> Bool
testBit :: Word32LE -> Int -> Bool
$cbitSizeMaybe :: Word32LE -> Maybe Int
bitSizeMaybe :: Word32LE -> Maybe Int
$cbitSize :: Word32LE -> Int
bitSize :: Word32LE -> Int
$cisSigned :: Word32LE -> Bool
isSigned :: Word32LE -> Bool
$cshiftL :: Word32LE -> Int -> Word32LE
shiftL :: Word32LE -> Int -> Word32LE
$cunsafeShiftL :: Word32LE -> Int -> Word32LE
unsafeShiftL :: Word32LE -> Int -> Word32LE
$cshiftR :: Word32LE -> Int -> Word32LE
shiftR :: Word32LE -> Int -> Word32LE
$cunsafeShiftR :: Word32LE -> Int -> Word32LE
unsafeShiftR :: Word32LE -> Int -> Word32LE
$crotateL :: Word32LE -> Int -> Word32LE
rotateL :: Word32LE -> Int -> Word32LE
$crotateR :: Word32LE -> Int -> Word32LE
rotateR :: Word32LE -> Int -> Word32LE
$cpopCount :: Word32LE -> Int
popCount :: Word32LE -> Int
Bits, Bits Word32LE
Bits Word32LE =>
(Word32LE -> Int)
-> (Word32LE -> Int) -> (Word32LE -> Int) -> FiniteBits Word32LE
Word32LE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Word32LE -> Int
finiteBitSize :: Word32LE -> Int
$ccountLeadingZeros :: Word32LE -> Int
countLeadingZeros :: Word32LE -> Int
$ccountTrailingZeros :: Word32LE -> Int
countTrailingZeros :: Word32LE -> Int
FiniteBits, Word32LE
Word32LE -> Word32LE -> Bounded Word32LE
forall a. a -> a -> Bounded a
$cminBound :: Word32LE
minBound :: Word32LE
$cmaxBound :: Word32LE
maxBound :: Word32LE
Bounded)

newtype Word64LE = Word64LE {Word64LE -> Word64
unWord64LE :: Word64}
  deriving stock (Int -> Word64LE -> ShowS
[Word64LE] -> ShowS
Word64LE -> String
(Int -> Word64LE -> ShowS)
-> (Word64LE -> String) -> ([Word64LE] -> ShowS) -> Show Word64LE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Word64LE -> ShowS
showsPrec :: Int -> Word64LE -> ShowS
$cshow :: Word64LE -> String
show :: Word64LE -> String
$cshowList :: [Word64LE] -> ShowS
showList :: [Word64LE] -> ShowS
Show)
  deriving newtype (Word64LE -> Word64LE -> Bool
(Word64LE -> Word64LE -> Bool)
-> (Word64LE -> Word64LE -> Bool) -> Eq Word64LE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Word64LE -> Word64LE -> Bool
== :: Word64LE -> Word64LE -> Bool
$c/= :: Word64LE -> Word64LE -> Bool
/= :: Word64LE -> Word64LE -> Bool
Eq, Eq Word64LE
Eq Word64LE =>
(Word64LE -> Word64LE -> Ordering)
-> (Word64LE -> Word64LE -> Bool)
-> (Word64LE -> Word64LE -> Bool)
-> (Word64LE -> Word64LE -> Bool)
-> (Word64LE -> Word64LE -> Bool)
-> (Word64LE -> Word64LE -> Word64LE)
-> (Word64LE -> Word64LE -> Word64LE)
-> Ord Word64LE
Word64LE -> Word64LE -> Bool
Word64LE -> Word64LE -> Ordering
Word64LE -> Word64LE -> Word64LE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Word64LE -> Word64LE -> Ordering
compare :: Word64LE -> Word64LE -> Ordering
$c< :: Word64LE -> Word64LE -> Bool
< :: Word64LE -> Word64LE -> Bool
$c<= :: Word64LE -> Word64LE -> Bool
<= :: Word64LE -> Word64LE -> Bool
$c> :: Word64LE -> Word64LE -> Bool
> :: Word64LE -> Word64LE -> Bool
$c>= :: Word64LE -> Word64LE -> Bool
>= :: Word64LE -> Word64LE -> Bool
$cmax :: Word64LE -> Word64LE -> Word64LE
max :: Word64LE -> Word64LE -> Word64LE
$cmin :: Word64LE -> Word64LE -> Word64LE
min :: Word64LE -> Word64LE -> Word64LE
Ord, Integer -> Word64LE
Word64LE -> Word64LE
Word64LE -> Word64LE -> Word64LE
(Word64LE -> Word64LE -> Word64LE)
-> (Word64LE -> Word64LE -> Word64LE)
-> (Word64LE -> Word64LE -> Word64LE)
-> (Word64LE -> Word64LE)
-> (Word64LE -> Word64LE)
-> (Word64LE -> Word64LE)
-> (Integer -> Word64LE)
-> Num Word64LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Word64LE -> Word64LE -> Word64LE
+ :: Word64LE -> Word64LE -> Word64LE
$c- :: Word64LE -> Word64LE -> Word64LE
- :: Word64LE -> Word64LE -> Word64LE
$c* :: Word64LE -> Word64LE -> Word64LE
* :: Word64LE -> Word64LE -> Word64LE
$cnegate :: Word64LE -> Word64LE
negate :: Word64LE -> Word64LE
$cabs :: Word64LE -> Word64LE
abs :: Word64LE -> Word64LE
$csignum :: Word64LE -> Word64LE
signum :: Word64LE -> Word64LE
$cfromInteger :: Integer -> Word64LE
fromInteger :: Integer -> Word64LE
Num, Int -> Word64LE
Word64LE -> Int
Word64LE -> [Word64LE]
Word64LE -> Word64LE
Word64LE -> Word64LE -> [Word64LE]
Word64LE -> Word64LE -> Word64LE -> [Word64LE]
(Word64LE -> Word64LE)
-> (Word64LE -> Word64LE)
-> (Int -> Word64LE)
-> (Word64LE -> Int)
-> (Word64LE -> [Word64LE])
-> (Word64LE -> Word64LE -> [Word64LE])
-> (Word64LE -> Word64LE -> [Word64LE])
-> (Word64LE -> Word64LE -> Word64LE -> [Word64LE])
-> Enum Word64LE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Word64LE -> Word64LE
succ :: Word64LE -> Word64LE
$cpred :: Word64LE -> Word64LE
pred :: Word64LE -> Word64LE
$ctoEnum :: Int -> Word64LE
toEnum :: Int -> Word64LE
$cfromEnum :: Word64LE -> Int
fromEnum :: Word64LE -> Int
$cenumFrom :: Word64LE -> [Word64LE]
enumFrom :: Word64LE -> [Word64LE]
$cenumFromThen :: Word64LE -> Word64LE -> [Word64LE]
enumFromThen :: Word64LE -> Word64LE -> [Word64LE]
$cenumFromTo :: Word64LE -> Word64LE -> [Word64LE]
enumFromTo :: Word64LE -> Word64LE -> [Word64LE]
$cenumFromThenTo :: Word64LE -> Word64LE -> Word64LE -> [Word64LE]
enumFromThenTo :: Word64LE -> Word64LE -> Word64LE -> [Word64LE]
Enum, Num Word64LE
Ord Word64LE
(Num Word64LE, Ord Word64LE) =>
(Word64LE -> Rational) -> Real Word64LE
Word64LE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Word64LE -> Rational
toRational :: Word64LE -> Rational
Real, Enum Word64LE
Real Word64LE
(Real Word64LE, Enum Word64LE) =>
(Word64LE -> Word64LE -> Word64LE)
-> (Word64LE -> Word64LE -> Word64LE)
-> (Word64LE -> Word64LE -> Word64LE)
-> (Word64LE -> Word64LE -> Word64LE)
-> (Word64LE -> Word64LE -> (Word64LE, Word64LE))
-> (Word64LE -> Word64LE -> (Word64LE, Word64LE))
-> (Word64LE -> Integer)
-> Integral Word64LE
Word64LE -> Integer
Word64LE -> Word64LE -> (Word64LE, Word64LE)
Word64LE -> Word64LE -> Word64LE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Word64LE -> Word64LE -> Word64LE
quot :: Word64LE -> Word64LE -> Word64LE
$crem :: Word64LE -> Word64LE -> Word64LE
rem :: Word64LE -> Word64LE -> Word64LE
$cdiv :: Word64LE -> Word64LE -> Word64LE
div :: Word64LE -> Word64LE -> Word64LE
$cmod :: Word64LE -> Word64LE -> Word64LE
mod :: Word64LE -> Word64LE -> Word64LE
$cquotRem :: Word64LE -> Word64LE -> (Word64LE, Word64LE)
quotRem :: Word64LE -> Word64LE -> (Word64LE, Word64LE)
$cdivMod :: Word64LE -> Word64LE -> (Word64LE, Word64LE)
divMod :: Word64LE -> Word64LE -> (Word64LE, Word64LE)
$ctoInteger :: Word64LE -> Integer
toInteger :: Word64LE -> Integer
Integral, Addr# -> Int# -> Word64LE
ByteArray# -> Int# -> Word64LE
Proxy Word64LE -> Int#
Word64LE -> Int#
(Proxy Word64LE -> Int#)
-> (Word64LE -> Int#)
-> (Proxy Word64LE -> Int#)
-> (Word64LE -> Int#)
-> (ByteArray# -> Int# -> Word64LE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word64LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word64LE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Word64LE -> State# s -> State# s)
-> (Addr# -> Int# -> Word64LE)
-> (forall s.
    Addr# -> Int# -> State# s -> (# State# s, Word64LE #))
-> (forall s. Addr# -> Int# -> Word64LE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Word64LE -> State# s -> State# s)
-> Prim Word64LE
forall s. Addr# -> Int# -> Int# -> Word64LE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Word64LE #)
forall s. Addr# -> Int# -> Word64LE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Word64LE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64LE #)
forall s.
MutableByteArray# s -> Int# -> Word64LE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Word64LE -> Int#
sizeOfType# :: Proxy Word64LE -> Int#
$csizeOf# :: Word64LE -> Int#
sizeOf# :: Word64LE -> Int#
$calignmentOfType# :: Proxy Word64LE -> Int#
alignmentOfType# :: Proxy Word64LE -> Int#
$calignment# :: Word64LE -> Int#
alignment# :: Word64LE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Word64LE
indexByteArray# :: ByteArray# -> Int# -> Word64LE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64LE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64LE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word64LE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word64LE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word64LE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word64LE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Word64LE
indexOffAddr# :: Addr# -> Int# -> Word64LE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word64LE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word64LE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Word64LE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Word64LE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word64LE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word64LE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Word64LE
(ByteArray# -> Int# -> Word64LE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word64LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word64LE -> State# s -> State# s)
-> PrimUnaligned Word64LE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64LE #)
forall s.
MutableByteArray# s -> Int# -> Word64LE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Word64LE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Word64LE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64LE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64LE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word64LE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word64LE -> State# s -> State# s
PrimUnaligned, Word64LE
Word64LE -> Default Word64LE
forall a. a -> Default a
$cdef :: Word64LE
def :: Word64LE
Default, Eq Word64LE
Word64LE
Eq Word64LE =>
(Word64LE -> Word64LE -> Word64LE)
-> (Word64LE -> Word64LE -> Word64LE)
-> (Word64LE -> Word64LE -> Word64LE)
-> (Word64LE -> Word64LE)
-> (Word64LE -> Int -> Word64LE)
-> (Word64LE -> Int -> Word64LE)
-> Word64LE
-> (Int -> Word64LE)
-> (Word64LE -> Int -> Word64LE)
-> (Word64LE -> Int -> Word64LE)
-> (Word64LE -> Int -> Word64LE)
-> (Word64LE -> Int -> Bool)
-> (Word64LE -> Maybe Int)
-> (Word64LE -> Int)
-> (Word64LE -> Bool)
-> (Word64LE -> Int -> Word64LE)
-> (Word64LE -> Int -> Word64LE)
-> (Word64LE -> Int -> Word64LE)
-> (Word64LE -> Int -> Word64LE)
-> (Word64LE -> Int -> Word64LE)
-> (Word64LE -> Int -> Word64LE)
-> (Word64LE -> Int)
-> Bits Word64LE
Int -> Word64LE
Word64LE -> Bool
Word64LE -> Int
Word64LE -> Maybe Int
Word64LE -> Word64LE
Word64LE -> Int -> Bool
Word64LE -> Int -> Word64LE
Word64LE -> Word64LE -> Word64LE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Word64LE -> Word64LE -> Word64LE
.&. :: Word64LE -> Word64LE -> Word64LE
$c.|. :: Word64LE -> Word64LE -> Word64LE
.|. :: Word64LE -> Word64LE -> Word64LE
$cxor :: Word64LE -> Word64LE -> Word64LE
xor :: Word64LE -> Word64LE -> Word64LE
$ccomplement :: Word64LE -> Word64LE
complement :: Word64LE -> Word64LE
$cshift :: Word64LE -> Int -> Word64LE
shift :: Word64LE -> Int -> Word64LE
$crotate :: Word64LE -> Int -> Word64LE
rotate :: Word64LE -> Int -> Word64LE
$czeroBits :: Word64LE
zeroBits :: Word64LE
$cbit :: Int -> Word64LE
bit :: Int -> Word64LE
$csetBit :: Word64LE -> Int -> Word64LE
setBit :: Word64LE -> Int -> Word64LE
$cclearBit :: Word64LE -> Int -> Word64LE
clearBit :: Word64LE -> Int -> Word64LE
$ccomplementBit :: Word64LE -> Int -> Word64LE
complementBit :: Word64LE -> Int -> Word64LE
$ctestBit :: Word64LE -> Int -> Bool
testBit :: Word64LE -> Int -> Bool
$cbitSizeMaybe :: Word64LE -> Maybe Int
bitSizeMaybe :: Word64LE -> Maybe Int
$cbitSize :: Word64LE -> Int
bitSize :: Word64LE -> Int
$cisSigned :: Word64LE -> Bool
isSigned :: Word64LE -> Bool
$cshiftL :: Word64LE -> Int -> Word64LE
shiftL :: Word64LE -> Int -> Word64LE
$cunsafeShiftL :: Word64LE -> Int -> Word64LE
unsafeShiftL :: Word64LE -> Int -> Word64LE
$cshiftR :: Word64LE -> Int -> Word64LE
shiftR :: Word64LE -> Int -> Word64LE
$cunsafeShiftR :: Word64LE -> Int -> Word64LE
unsafeShiftR :: Word64LE -> Int -> Word64LE
$crotateL :: Word64LE -> Int -> Word64LE
rotateL :: Word64LE -> Int -> Word64LE
$crotateR :: Word64LE -> Int -> Word64LE
rotateR :: Word64LE -> Int -> Word64LE
$cpopCount :: Word64LE -> Int
popCount :: Word64LE -> Int
Bits, Bits Word64LE
Bits Word64LE =>
(Word64LE -> Int)
-> (Word64LE -> Int) -> (Word64LE -> Int) -> FiniteBits Word64LE
Word64LE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Word64LE -> Int
finiteBitSize :: Word64LE -> Int
$ccountLeadingZeros :: Word64LE -> Int
countLeadingZeros :: Word64LE -> Int
$ccountTrailingZeros :: Word64LE -> Int
countTrailingZeros :: Word64LE -> Int
FiniteBits, Word64LE
Word64LE -> Word64LE -> Bounded Word64LE
forall a. a -> a -> Bounded a
$cminBound :: Word64LE
minBound :: Word64LE
$cmaxBound :: Word64LE
maxBound :: Word64LE
Bounded)

newtype Int16LE = Int16LE {Int16LE -> Int16
unInt16LE :: Int16}
  deriving stock (Int -> Int16LE -> ShowS
[Int16LE] -> ShowS
Int16LE -> String
(Int -> Int16LE -> ShowS)
-> (Int16LE -> String) -> ([Int16LE] -> ShowS) -> Show Int16LE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Int16LE -> ShowS
showsPrec :: Int -> Int16LE -> ShowS
$cshow :: Int16LE -> String
show :: Int16LE -> String
$cshowList :: [Int16LE] -> ShowS
showList :: [Int16LE] -> ShowS
Show)
  deriving newtype (Int16LE -> Int16LE -> Bool
(Int16LE -> Int16LE -> Bool)
-> (Int16LE -> Int16LE -> Bool) -> Eq Int16LE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Int16LE -> Int16LE -> Bool
== :: Int16LE -> Int16LE -> Bool
$c/= :: Int16LE -> Int16LE -> Bool
/= :: Int16LE -> Int16LE -> Bool
Eq, Eq Int16LE
Eq Int16LE =>
(Int16LE -> Int16LE -> Ordering)
-> (Int16LE -> Int16LE -> Bool)
-> (Int16LE -> Int16LE -> Bool)
-> (Int16LE -> Int16LE -> Bool)
-> (Int16LE -> Int16LE -> Bool)
-> (Int16LE -> Int16LE -> Int16LE)
-> (Int16LE -> Int16LE -> Int16LE)
-> Ord Int16LE
Int16LE -> Int16LE -> Bool
Int16LE -> Int16LE -> Ordering
Int16LE -> Int16LE -> Int16LE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Int16LE -> Int16LE -> Ordering
compare :: Int16LE -> Int16LE -> Ordering
$c< :: Int16LE -> Int16LE -> Bool
< :: Int16LE -> Int16LE -> Bool
$c<= :: Int16LE -> Int16LE -> Bool
<= :: Int16LE -> Int16LE -> Bool
$c> :: Int16LE -> Int16LE -> Bool
> :: Int16LE -> Int16LE -> Bool
$c>= :: Int16LE -> Int16LE -> Bool
>= :: Int16LE -> Int16LE -> Bool
$cmax :: Int16LE -> Int16LE -> Int16LE
max :: Int16LE -> Int16LE -> Int16LE
$cmin :: Int16LE -> Int16LE -> Int16LE
min :: Int16LE -> Int16LE -> Int16LE
Ord, Integer -> Int16LE
Int16LE -> Int16LE
Int16LE -> Int16LE -> Int16LE
(Int16LE -> Int16LE -> Int16LE)
-> (Int16LE -> Int16LE -> Int16LE)
-> (Int16LE -> Int16LE -> Int16LE)
-> (Int16LE -> Int16LE)
-> (Int16LE -> Int16LE)
-> (Int16LE -> Int16LE)
-> (Integer -> Int16LE)
-> Num Int16LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Int16LE -> Int16LE -> Int16LE
+ :: Int16LE -> Int16LE -> Int16LE
$c- :: Int16LE -> Int16LE -> Int16LE
- :: Int16LE -> Int16LE -> Int16LE
$c* :: Int16LE -> Int16LE -> Int16LE
* :: Int16LE -> Int16LE -> Int16LE
$cnegate :: Int16LE -> Int16LE
negate :: Int16LE -> Int16LE
$cabs :: Int16LE -> Int16LE
abs :: Int16LE -> Int16LE
$csignum :: Int16LE -> Int16LE
signum :: Int16LE -> Int16LE
$cfromInteger :: Integer -> Int16LE
fromInteger :: Integer -> Int16LE
Num, Int -> Int16LE
Int16LE -> Int
Int16LE -> [Int16LE]
Int16LE -> Int16LE
Int16LE -> Int16LE -> [Int16LE]
Int16LE -> Int16LE -> Int16LE -> [Int16LE]
(Int16LE -> Int16LE)
-> (Int16LE -> Int16LE)
-> (Int -> Int16LE)
-> (Int16LE -> Int)
-> (Int16LE -> [Int16LE])
-> (Int16LE -> Int16LE -> [Int16LE])
-> (Int16LE -> Int16LE -> [Int16LE])
-> (Int16LE -> Int16LE -> Int16LE -> [Int16LE])
-> Enum Int16LE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Int16LE -> Int16LE
succ :: Int16LE -> Int16LE
$cpred :: Int16LE -> Int16LE
pred :: Int16LE -> Int16LE
$ctoEnum :: Int -> Int16LE
toEnum :: Int -> Int16LE
$cfromEnum :: Int16LE -> Int
fromEnum :: Int16LE -> Int
$cenumFrom :: Int16LE -> [Int16LE]
enumFrom :: Int16LE -> [Int16LE]
$cenumFromThen :: Int16LE -> Int16LE -> [Int16LE]
enumFromThen :: Int16LE -> Int16LE -> [Int16LE]
$cenumFromTo :: Int16LE -> Int16LE -> [Int16LE]
enumFromTo :: Int16LE -> Int16LE -> [Int16LE]
$cenumFromThenTo :: Int16LE -> Int16LE -> Int16LE -> [Int16LE]
enumFromThenTo :: Int16LE -> Int16LE -> Int16LE -> [Int16LE]
Enum, Num Int16LE
Ord Int16LE
(Num Int16LE, Ord Int16LE) => (Int16LE -> Rational) -> Real Int16LE
Int16LE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Int16LE -> Rational
toRational :: Int16LE -> Rational
Real, Enum Int16LE
Real Int16LE
(Real Int16LE, Enum Int16LE) =>
(Int16LE -> Int16LE -> Int16LE)
-> (Int16LE -> Int16LE -> Int16LE)
-> (Int16LE -> Int16LE -> Int16LE)
-> (Int16LE -> Int16LE -> Int16LE)
-> (Int16LE -> Int16LE -> (Int16LE, Int16LE))
-> (Int16LE -> Int16LE -> (Int16LE, Int16LE))
-> (Int16LE -> Integer)
-> Integral Int16LE
Int16LE -> Integer
Int16LE -> Int16LE -> (Int16LE, Int16LE)
Int16LE -> Int16LE -> Int16LE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Int16LE -> Int16LE -> Int16LE
quot :: Int16LE -> Int16LE -> Int16LE
$crem :: Int16LE -> Int16LE -> Int16LE
rem :: Int16LE -> Int16LE -> Int16LE
$cdiv :: Int16LE -> Int16LE -> Int16LE
div :: Int16LE -> Int16LE -> Int16LE
$cmod :: Int16LE -> Int16LE -> Int16LE
mod :: Int16LE -> Int16LE -> Int16LE
$cquotRem :: Int16LE -> Int16LE -> (Int16LE, Int16LE)
quotRem :: Int16LE -> Int16LE -> (Int16LE, Int16LE)
$cdivMod :: Int16LE -> Int16LE -> (Int16LE, Int16LE)
divMod :: Int16LE -> Int16LE -> (Int16LE, Int16LE)
$ctoInteger :: Int16LE -> Integer
toInteger :: Int16LE -> Integer
Integral, Addr# -> Int# -> Int16LE
ByteArray# -> Int# -> Int16LE
Proxy Int16LE -> Int#
Int16LE -> Int#
(Proxy Int16LE -> Int#)
-> (Int16LE -> Int#)
-> (Proxy Int16LE -> Int#)
-> (Int16LE -> Int#)
-> (ByteArray# -> Int# -> Int16LE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int16LE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Int16LE -> State# s -> State# s)
-> (Addr# -> Int# -> Int16LE)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, Int16LE #))
-> (forall s. Addr# -> Int# -> Int16LE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Int16LE -> State# s -> State# s)
-> Prim Int16LE
forall s. Addr# -> Int# -> Int# -> Int16LE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Int16LE #)
forall s. Addr# -> Int# -> Int16LE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Int16LE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16LE #)
forall s.
MutableByteArray# s -> Int# -> Int16LE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Int16LE -> Int#
sizeOfType# :: Proxy Int16LE -> Int#
$csizeOf# :: Int16LE -> Int#
sizeOf# :: Int16LE -> Int#
$calignmentOfType# :: Proxy Int16LE -> Int#
alignmentOfType# :: Proxy Int16LE -> Int#
$calignment# :: Int16LE -> Int#
alignment# :: Int16LE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Int16LE
indexByteArray# :: ByteArray# -> Int# -> Int16LE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16LE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16LE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int16LE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int16LE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int16LE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int16LE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Int16LE
indexOffAddr# :: Addr# -> Int# -> Int16LE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int16LE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int16LE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Int16LE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Int16LE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int16LE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int16LE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Int16LE
(ByteArray# -> Int# -> Int16LE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int16LE -> State# s -> State# s)
-> PrimUnaligned Int16LE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16LE #)
forall s.
MutableByteArray# s -> Int# -> Int16LE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Int16LE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Int16LE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16LE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16LE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int16LE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int16LE -> State# s -> State# s
PrimUnaligned, Int16LE
Int16LE -> Default Int16LE
forall a. a -> Default a
$cdef :: Int16LE
def :: Int16LE
Default, Eq Int16LE
Int16LE
Eq Int16LE =>
(Int16LE -> Int16LE -> Int16LE)
-> (Int16LE -> Int16LE -> Int16LE)
-> (Int16LE -> Int16LE -> Int16LE)
-> (Int16LE -> Int16LE)
-> (Int16LE -> Int -> Int16LE)
-> (Int16LE -> Int -> Int16LE)
-> Int16LE
-> (Int -> Int16LE)
-> (Int16LE -> Int -> Int16LE)
-> (Int16LE -> Int -> Int16LE)
-> (Int16LE -> Int -> Int16LE)
-> (Int16LE -> Int -> Bool)
-> (Int16LE -> Maybe Int)
-> (Int16LE -> Int)
-> (Int16LE -> Bool)
-> (Int16LE -> Int -> Int16LE)
-> (Int16LE -> Int -> Int16LE)
-> (Int16LE -> Int -> Int16LE)
-> (Int16LE -> Int -> Int16LE)
-> (Int16LE -> Int -> Int16LE)
-> (Int16LE -> Int -> Int16LE)
-> (Int16LE -> Int)
-> Bits Int16LE
Int -> Int16LE
Int16LE -> Bool
Int16LE -> Int
Int16LE -> Maybe Int
Int16LE -> Int16LE
Int16LE -> Int -> Bool
Int16LE -> Int -> Int16LE
Int16LE -> Int16LE -> Int16LE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Int16LE -> Int16LE -> Int16LE
.&. :: Int16LE -> Int16LE -> Int16LE
$c.|. :: Int16LE -> Int16LE -> Int16LE
.|. :: Int16LE -> Int16LE -> Int16LE
$cxor :: Int16LE -> Int16LE -> Int16LE
xor :: Int16LE -> Int16LE -> Int16LE
$ccomplement :: Int16LE -> Int16LE
complement :: Int16LE -> Int16LE
$cshift :: Int16LE -> Int -> Int16LE
shift :: Int16LE -> Int -> Int16LE
$crotate :: Int16LE -> Int -> Int16LE
rotate :: Int16LE -> Int -> Int16LE
$czeroBits :: Int16LE
zeroBits :: Int16LE
$cbit :: Int -> Int16LE
bit :: Int -> Int16LE
$csetBit :: Int16LE -> Int -> Int16LE
setBit :: Int16LE -> Int -> Int16LE
$cclearBit :: Int16LE -> Int -> Int16LE
clearBit :: Int16LE -> Int -> Int16LE
$ccomplementBit :: Int16LE -> Int -> Int16LE
complementBit :: Int16LE -> Int -> Int16LE
$ctestBit :: Int16LE -> Int -> Bool
testBit :: Int16LE -> Int -> Bool
$cbitSizeMaybe :: Int16LE -> Maybe Int
bitSizeMaybe :: Int16LE -> Maybe Int
$cbitSize :: Int16LE -> Int
bitSize :: Int16LE -> Int
$cisSigned :: Int16LE -> Bool
isSigned :: Int16LE -> Bool
$cshiftL :: Int16LE -> Int -> Int16LE
shiftL :: Int16LE -> Int -> Int16LE
$cunsafeShiftL :: Int16LE -> Int -> Int16LE
unsafeShiftL :: Int16LE -> Int -> Int16LE
$cshiftR :: Int16LE -> Int -> Int16LE
shiftR :: Int16LE -> Int -> Int16LE
$cunsafeShiftR :: Int16LE -> Int -> Int16LE
unsafeShiftR :: Int16LE -> Int -> Int16LE
$crotateL :: Int16LE -> Int -> Int16LE
rotateL :: Int16LE -> Int -> Int16LE
$crotateR :: Int16LE -> Int -> Int16LE
rotateR :: Int16LE -> Int -> Int16LE
$cpopCount :: Int16LE -> Int
popCount :: Int16LE -> Int
Bits, Bits Int16LE
Bits Int16LE =>
(Int16LE -> Int)
-> (Int16LE -> Int) -> (Int16LE -> Int) -> FiniteBits Int16LE
Int16LE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Int16LE -> Int
finiteBitSize :: Int16LE -> Int
$ccountLeadingZeros :: Int16LE -> Int
countLeadingZeros :: Int16LE -> Int
$ccountTrailingZeros :: Int16LE -> Int
countTrailingZeros :: Int16LE -> Int
FiniteBits, Int16LE
Int16LE -> Int16LE -> Bounded Int16LE
forall a. a -> a -> Bounded a
$cminBound :: Int16LE
minBound :: Int16LE
$cmaxBound :: Int16LE
maxBound :: Int16LE
Bounded)

newtype Int24LE = Int24LE {Int24LE -> Int24
unInt24LE :: Int24}
  deriving stock (Int -> Int24LE -> ShowS
[Int24LE] -> ShowS
Int24LE -> String
(Int -> Int24LE -> ShowS)
-> (Int24LE -> String) -> ([Int24LE] -> ShowS) -> Show Int24LE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Int24LE -> ShowS
showsPrec :: Int -> Int24LE -> ShowS
$cshow :: Int24LE -> String
show :: Int24LE -> String
$cshowList :: [Int24LE] -> ShowS
showList :: [Int24LE] -> ShowS
Show)
  deriving newtype (Int24LE -> Int24LE -> Bool
(Int24LE -> Int24LE -> Bool)
-> (Int24LE -> Int24LE -> Bool) -> Eq Int24LE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Int24LE -> Int24LE -> Bool
== :: Int24LE -> Int24LE -> Bool
$c/= :: Int24LE -> Int24LE -> Bool
/= :: Int24LE -> Int24LE -> Bool
Eq, Eq Int24LE
Eq Int24LE =>
(Int24LE -> Int24LE -> Ordering)
-> (Int24LE -> Int24LE -> Bool)
-> (Int24LE -> Int24LE -> Bool)
-> (Int24LE -> Int24LE -> Bool)
-> (Int24LE -> Int24LE -> Bool)
-> (Int24LE -> Int24LE -> Int24LE)
-> (Int24LE -> Int24LE -> Int24LE)
-> Ord Int24LE
Int24LE -> Int24LE -> Bool
Int24LE -> Int24LE -> Ordering
Int24LE -> Int24LE -> Int24LE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Int24LE -> Int24LE -> Ordering
compare :: Int24LE -> Int24LE -> Ordering
$c< :: Int24LE -> Int24LE -> Bool
< :: Int24LE -> Int24LE -> Bool
$c<= :: Int24LE -> Int24LE -> Bool
<= :: Int24LE -> Int24LE -> Bool
$c> :: Int24LE -> Int24LE -> Bool
> :: Int24LE -> Int24LE -> Bool
$c>= :: Int24LE -> Int24LE -> Bool
>= :: Int24LE -> Int24LE -> Bool
$cmax :: Int24LE -> Int24LE -> Int24LE
max :: Int24LE -> Int24LE -> Int24LE
$cmin :: Int24LE -> Int24LE -> Int24LE
min :: Int24LE -> Int24LE -> Int24LE
Ord, Integer -> Int24LE
Int24LE -> Int24LE
Int24LE -> Int24LE -> Int24LE
(Int24LE -> Int24LE -> Int24LE)
-> (Int24LE -> Int24LE -> Int24LE)
-> (Int24LE -> Int24LE -> Int24LE)
-> (Int24LE -> Int24LE)
-> (Int24LE -> Int24LE)
-> (Int24LE -> Int24LE)
-> (Integer -> Int24LE)
-> Num Int24LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Int24LE -> Int24LE -> Int24LE
+ :: Int24LE -> Int24LE -> Int24LE
$c- :: Int24LE -> Int24LE -> Int24LE
- :: Int24LE -> Int24LE -> Int24LE
$c* :: Int24LE -> Int24LE -> Int24LE
* :: Int24LE -> Int24LE -> Int24LE
$cnegate :: Int24LE -> Int24LE
negate :: Int24LE -> Int24LE
$cabs :: Int24LE -> Int24LE
abs :: Int24LE -> Int24LE
$csignum :: Int24LE -> Int24LE
signum :: Int24LE -> Int24LE
$cfromInteger :: Integer -> Int24LE
fromInteger :: Integer -> Int24LE
Num, Int -> Int24LE
Int24LE -> Int
Int24LE -> [Int24LE]
Int24LE -> Int24LE
Int24LE -> Int24LE -> [Int24LE]
Int24LE -> Int24LE -> Int24LE -> [Int24LE]
(Int24LE -> Int24LE)
-> (Int24LE -> Int24LE)
-> (Int -> Int24LE)
-> (Int24LE -> Int)
-> (Int24LE -> [Int24LE])
-> (Int24LE -> Int24LE -> [Int24LE])
-> (Int24LE -> Int24LE -> [Int24LE])
-> (Int24LE -> Int24LE -> Int24LE -> [Int24LE])
-> Enum Int24LE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Int24LE -> Int24LE
succ :: Int24LE -> Int24LE
$cpred :: Int24LE -> Int24LE
pred :: Int24LE -> Int24LE
$ctoEnum :: Int -> Int24LE
toEnum :: Int -> Int24LE
$cfromEnum :: Int24LE -> Int
fromEnum :: Int24LE -> Int
$cenumFrom :: Int24LE -> [Int24LE]
enumFrom :: Int24LE -> [Int24LE]
$cenumFromThen :: Int24LE -> Int24LE -> [Int24LE]
enumFromThen :: Int24LE -> Int24LE -> [Int24LE]
$cenumFromTo :: Int24LE -> Int24LE -> [Int24LE]
enumFromTo :: Int24LE -> Int24LE -> [Int24LE]
$cenumFromThenTo :: Int24LE -> Int24LE -> Int24LE -> [Int24LE]
enumFromThenTo :: Int24LE -> Int24LE -> Int24LE -> [Int24LE]
Enum, Num Int24LE
Ord Int24LE
(Num Int24LE, Ord Int24LE) => (Int24LE -> Rational) -> Real Int24LE
Int24LE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Int24LE -> Rational
toRational :: Int24LE -> Rational
Real, Enum Int24LE
Real Int24LE
(Real Int24LE, Enum Int24LE) =>
(Int24LE -> Int24LE -> Int24LE)
-> (Int24LE -> Int24LE -> Int24LE)
-> (Int24LE -> Int24LE -> Int24LE)
-> (Int24LE -> Int24LE -> Int24LE)
-> (Int24LE -> Int24LE -> (Int24LE, Int24LE))
-> (Int24LE -> Int24LE -> (Int24LE, Int24LE))
-> (Int24LE -> Integer)
-> Integral Int24LE
Int24LE -> Integer
Int24LE -> Int24LE -> (Int24LE, Int24LE)
Int24LE -> Int24LE -> Int24LE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Int24LE -> Int24LE -> Int24LE
quot :: Int24LE -> Int24LE -> Int24LE
$crem :: Int24LE -> Int24LE -> Int24LE
rem :: Int24LE -> Int24LE -> Int24LE
$cdiv :: Int24LE -> Int24LE -> Int24LE
div :: Int24LE -> Int24LE -> Int24LE
$cmod :: Int24LE -> Int24LE -> Int24LE
mod :: Int24LE -> Int24LE -> Int24LE
$cquotRem :: Int24LE -> Int24LE -> (Int24LE, Int24LE)
quotRem :: Int24LE -> Int24LE -> (Int24LE, Int24LE)
$cdivMod :: Int24LE -> Int24LE -> (Int24LE, Int24LE)
divMod :: Int24LE -> Int24LE -> (Int24LE, Int24LE)
$ctoInteger :: Int24LE -> Integer
toInteger :: Int24LE -> Integer
Integral, Addr# -> Int# -> Int24LE
ByteArray# -> Int# -> Int24LE
Proxy Int24LE -> Int#
Int24LE -> Int#
(Proxy Int24LE -> Int#)
-> (Int24LE -> Int#)
-> (Proxy Int24LE -> Int#)
-> (Int24LE -> Int#)
-> (ByteArray# -> Int# -> Int24LE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int24LE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Int24LE -> State# s -> State# s)
-> (Addr# -> Int# -> Int24LE)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, Int24LE #))
-> (forall s. Addr# -> Int# -> Int24LE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Int24LE -> State# s -> State# s)
-> Prim Int24LE
forall s. Addr# -> Int# -> Int# -> Int24LE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Int24LE #)
forall s. Addr# -> Int# -> Int24LE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Int24LE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24LE #)
forall s.
MutableByteArray# s -> Int# -> Int24LE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Int24LE -> Int#
sizeOfType# :: Proxy Int24LE -> Int#
$csizeOf# :: Int24LE -> Int#
sizeOf# :: Int24LE -> Int#
$calignmentOfType# :: Proxy Int24LE -> Int#
alignmentOfType# :: Proxy Int24LE -> Int#
$calignment# :: Int24LE -> Int#
alignment# :: Int24LE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Int24LE
indexByteArray# :: ByteArray# -> Int# -> Int24LE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24LE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24LE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int24LE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int24LE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int24LE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int24LE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Int24LE
indexOffAddr# :: Addr# -> Int# -> Int24LE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int24LE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int24LE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Int24LE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Int24LE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int24LE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int24LE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Int24LE
(ByteArray# -> Int# -> Int24LE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int24LE -> State# s -> State# s)
-> PrimUnaligned Int24LE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24LE #)
forall s.
MutableByteArray# s -> Int# -> Int24LE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Int24LE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Int24LE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24LE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24LE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int24LE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int24LE -> State# s -> State# s
PrimUnaligned, Int24LE
Int24LE -> Default Int24LE
forall a. a -> Default a
$cdef :: Int24LE
def :: Int24LE
Default, Eq Int24LE
Int24LE
Eq Int24LE =>
(Int24LE -> Int24LE -> Int24LE)
-> (Int24LE -> Int24LE -> Int24LE)
-> (Int24LE -> Int24LE -> Int24LE)
-> (Int24LE -> Int24LE)
-> (Int24LE -> Int -> Int24LE)
-> (Int24LE -> Int -> Int24LE)
-> Int24LE
-> (Int -> Int24LE)
-> (Int24LE -> Int -> Int24LE)
-> (Int24LE -> Int -> Int24LE)
-> (Int24LE -> Int -> Int24LE)
-> (Int24LE -> Int -> Bool)
-> (Int24LE -> Maybe Int)
-> (Int24LE -> Int)
-> (Int24LE -> Bool)
-> (Int24LE -> Int -> Int24LE)
-> (Int24LE -> Int -> Int24LE)
-> (Int24LE -> Int -> Int24LE)
-> (Int24LE -> Int -> Int24LE)
-> (Int24LE -> Int -> Int24LE)
-> (Int24LE -> Int -> Int24LE)
-> (Int24LE -> Int)
-> Bits Int24LE
Int -> Int24LE
Int24LE -> Bool
Int24LE -> Int
Int24LE -> Maybe Int
Int24LE -> Int24LE
Int24LE -> Int -> Bool
Int24LE -> Int -> Int24LE
Int24LE -> Int24LE -> Int24LE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Int24LE -> Int24LE -> Int24LE
.&. :: Int24LE -> Int24LE -> Int24LE
$c.|. :: Int24LE -> Int24LE -> Int24LE
.|. :: Int24LE -> Int24LE -> Int24LE
$cxor :: Int24LE -> Int24LE -> Int24LE
xor :: Int24LE -> Int24LE -> Int24LE
$ccomplement :: Int24LE -> Int24LE
complement :: Int24LE -> Int24LE
$cshift :: Int24LE -> Int -> Int24LE
shift :: Int24LE -> Int -> Int24LE
$crotate :: Int24LE -> Int -> Int24LE
rotate :: Int24LE -> Int -> Int24LE
$czeroBits :: Int24LE
zeroBits :: Int24LE
$cbit :: Int -> Int24LE
bit :: Int -> Int24LE
$csetBit :: Int24LE -> Int -> Int24LE
setBit :: Int24LE -> Int -> Int24LE
$cclearBit :: Int24LE -> Int -> Int24LE
clearBit :: Int24LE -> Int -> Int24LE
$ccomplementBit :: Int24LE -> Int -> Int24LE
complementBit :: Int24LE -> Int -> Int24LE
$ctestBit :: Int24LE -> Int -> Bool
testBit :: Int24LE -> Int -> Bool
$cbitSizeMaybe :: Int24LE -> Maybe Int
bitSizeMaybe :: Int24LE -> Maybe Int
$cbitSize :: Int24LE -> Int
bitSize :: Int24LE -> Int
$cisSigned :: Int24LE -> Bool
isSigned :: Int24LE -> Bool
$cshiftL :: Int24LE -> Int -> Int24LE
shiftL :: Int24LE -> Int -> Int24LE
$cunsafeShiftL :: Int24LE -> Int -> Int24LE
unsafeShiftL :: Int24LE -> Int -> Int24LE
$cshiftR :: Int24LE -> Int -> Int24LE
shiftR :: Int24LE -> Int -> Int24LE
$cunsafeShiftR :: Int24LE -> Int -> Int24LE
unsafeShiftR :: Int24LE -> Int -> Int24LE
$crotateL :: Int24LE -> Int -> Int24LE
rotateL :: Int24LE -> Int -> Int24LE
$crotateR :: Int24LE -> Int -> Int24LE
rotateR :: Int24LE -> Int -> Int24LE
$cpopCount :: Int24LE -> Int
popCount :: Int24LE -> Int
Bits, Bits Int24LE
Bits Int24LE =>
(Int24LE -> Int)
-> (Int24LE -> Int) -> (Int24LE -> Int) -> FiniteBits Int24LE
Int24LE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Int24LE -> Int
finiteBitSize :: Int24LE -> Int
$ccountLeadingZeros :: Int24LE -> Int
countLeadingZeros :: Int24LE -> Int
$ccountTrailingZeros :: Int24LE -> Int
countTrailingZeros :: Int24LE -> Int
FiniteBits, Int24LE
Int24LE -> Int24LE -> Bounded Int24LE
forall a. a -> a -> Bounded a
$cminBound :: Int24LE
minBound :: Int24LE
$cmaxBound :: Int24LE
maxBound :: Int24LE
Bounded)

newtype Int32LE = Int32LE {Int32LE -> Int32
unInt32LE :: Int32}
  deriving stock (Int -> Int32LE -> ShowS
[Int32LE] -> ShowS
Int32LE -> String
(Int -> Int32LE -> ShowS)
-> (Int32LE -> String) -> ([Int32LE] -> ShowS) -> Show Int32LE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Int32LE -> ShowS
showsPrec :: Int -> Int32LE -> ShowS
$cshow :: Int32LE -> String
show :: Int32LE -> String
$cshowList :: [Int32LE] -> ShowS
showList :: [Int32LE] -> ShowS
Show)
  deriving newtype (Int32LE -> Int32LE -> Bool
(Int32LE -> Int32LE -> Bool)
-> (Int32LE -> Int32LE -> Bool) -> Eq Int32LE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Int32LE -> Int32LE -> Bool
== :: Int32LE -> Int32LE -> Bool
$c/= :: Int32LE -> Int32LE -> Bool
/= :: Int32LE -> Int32LE -> Bool
Eq, Eq Int32LE
Eq Int32LE =>
(Int32LE -> Int32LE -> Ordering)
-> (Int32LE -> Int32LE -> Bool)
-> (Int32LE -> Int32LE -> Bool)
-> (Int32LE -> Int32LE -> Bool)
-> (Int32LE -> Int32LE -> Bool)
-> (Int32LE -> Int32LE -> Int32LE)
-> (Int32LE -> Int32LE -> Int32LE)
-> Ord Int32LE
Int32LE -> Int32LE -> Bool
Int32LE -> Int32LE -> Ordering
Int32LE -> Int32LE -> Int32LE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Int32LE -> Int32LE -> Ordering
compare :: Int32LE -> Int32LE -> Ordering
$c< :: Int32LE -> Int32LE -> Bool
< :: Int32LE -> Int32LE -> Bool
$c<= :: Int32LE -> Int32LE -> Bool
<= :: Int32LE -> Int32LE -> Bool
$c> :: Int32LE -> Int32LE -> Bool
> :: Int32LE -> Int32LE -> Bool
$c>= :: Int32LE -> Int32LE -> Bool
>= :: Int32LE -> Int32LE -> Bool
$cmax :: Int32LE -> Int32LE -> Int32LE
max :: Int32LE -> Int32LE -> Int32LE
$cmin :: Int32LE -> Int32LE -> Int32LE
min :: Int32LE -> Int32LE -> Int32LE
Ord, Integer -> Int32LE
Int32LE -> Int32LE
Int32LE -> Int32LE -> Int32LE
(Int32LE -> Int32LE -> Int32LE)
-> (Int32LE -> Int32LE -> Int32LE)
-> (Int32LE -> Int32LE -> Int32LE)
-> (Int32LE -> Int32LE)
-> (Int32LE -> Int32LE)
-> (Int32LE -> Int32LE)
-> (Integer -> Int32LE)
-> Num Int32LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Int32LE -> Int32LE -> Int32LE
+ :: Int32LE -> Int32LE -> Int32LE
$c- :: Int32LE -> Int32LE -> Int32LE
- :: Int32LE -> Int32LE -> Int32LE
$c* :: Int32LE -> Int32LE -> Int32LE
* :: Int32LE -> Int32LE -> Int32LE
$cnegate :: Int32LE -> Int32LE
negate :: Int32LE -> Int32LE
$cabs :: Int32LE -> Int32LE
abs :: Int32LE -> Int32LE
$csignum :: Int32LE -> Int32LE
signum :: Int32LE -> Int32LE
$cfromInteger :: Integer -> Int32LE
fromInteger :: Integer -> Int32LE
Num, Int -> Int32LE
Int32LE -> Int
Int32LE -> [Int32LE]
Int32LE -> Int32LE
Int32LE -> Int32LE -> [Int32LE]
Int32LE -> Int32LE -> Int32LE -> [Int32LE]
(Int32LE -> Int32LE)
-> (Int32LE -> Int32LE)
-> (Int -> Int32LE)
-> (Int32LE -> Int)
-> (Int32LE -> [Int32LE])
-> (Int32LE -> Int32LE -> [Int32LE])
-> (Int32LE -> Int32LE -> [Int32LE])
-> (Int32LE -> Int32LE -> Int32LE -> [Int32LE])
-> Enum Int32LE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Int32LE -> Int32LE
succ :: Int32LE -> Int32LE
$cpred :: Int32LE -> Int32LE
pred :: Int32LE -> Int32LE
$ctoEnum :: Int -> Int32LE
toEnum :: Int -> Int32LE
$cfromEnum :: Int32LE -> Int
fromEnum :: Int32LE -> Int
$cenumFrom :: Int32LE -> [Int32LE]
enumFrom :: Int32LE -> [Int32LE]
$cenumFromThen :: Int32LE -> Int32LE -> [Int32LE]
enumFromThen :: Int32LE -> Int32LE -> [Int32LE]
$cenumFromTo :: Int32LE -> Int32LE -> [Int32LE]
enumFromTo :: Int32LE -> Int32LE -> [Int32LE]
$cenumFromThenTo :: Int32LE -> Int32LE -> Int32LE -> [Int32LE]
enumFromThenTo :: Int32LE -> Int32LE -> Int32LE -> [Int32LE]
Enum, Num Int32LE
Ord Int32LE
(Num Int32LE, Ord Int32LE) => (Int32LE -> Rational) -> Real Int32LE
Int32LE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Int32LE -> Rational
toRational :: Int32LE -> Rational
Real, Enum Int32LE
Real Int32LE
(Real Int32LE, Enum Int32LE) =>
(Int32LE -> Int32LE -> Int32LE)
-> (Int32LE -> Int32LE -> Int32LE)
-> (Int32LE -> Int32LE -> Int32LE)
-> (Int32LE -> Int32LE -> Int32LE)
-> (Int32LE -> Int32LE -> (Int32LE, Int32LE))
-> (Int32LE -> Int32LE -> (Int32LE, Int32LE))
-> (Int32LE -> Integer)
-> Integral Int32LE
Int32LE -> Integer
Int32LE -> Int32LE -> (Int32LE, Int32LE)
Int32LE -> Int32LE -> Int32LE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Int32LE -> Int32LE -> Int32LE
quot :: Int32LE -> Int32LE -> Int32LE
$crem :: Int32LE -> Int32LE -> Int32LE
rem :: Int32LE -> Int32LE -> Int32LE
$cdiv :: Int32LE -> Int32LE -> Int32LE
div :: Int32LE -> Int32LE -> Int32LE
$cmod :: Int32LE -> Int32LE -> Int32LE
mod :: Int32LE -> Int32LE -> Int32LE
$cquotRem :: Int32LE -> Int32LE -> (Int32LE, Int32LE)
quotRem :: Int32LE -> Int32LE -> (Int32LE, Int32LE)
$cdivMod :: Int32LE -> Int32LE -> (Int32LE, Int32LE)
divMod :: Int32LE -> Int32LE -> (Int32LE, Int32LE)
$ctoInteger :: Int32LE -> Integer
toInteger :: Int32LE -> Integer
Integral, Addr# -> Int# -> Int32LE
ByteArray# -> Int# -> Int32LE
Proxy Int32LE -> Int#
Int32LE -> Int#
(Proxy Int32LE -> Int#)
-> (Int32LE -> Int#)
-> (Proxy Int32LE -> Int#)
-> (Int32LE -> Int#)
-> (ByteArray# -> Int# -> Int32LE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int32LE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Int32LE -> State# s -> State# s)
-> (Addr# -> Int# -> Int32LE)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, Int32LE #))
-> (forall s. Addr# -> Int# -> Int32LE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Int32LE -> State# s -> State# s)
-> Prim Int32LE
forall s. Addr# -> Int# -> Int# -> Int32LE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Int32LE #)
forall s. Addr# -> Int# -> Int32LE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Int32LE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32LE #)
forall s.
MutableByteArray# s -> Int# -> Int32LE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Int32LE -> Int#
sizeOfType# :: Proxy Int32LE -> Int#
$csizeOf# :: Int32LE -> Int#
sizeOf# :: Int32LE -> Int#
$calignmentOfType# :: Proxy Int32LE -> Int#
alignmentOfType# :: Proxy Int32LE -> Int#
$calignment# :: Int32LE -> Int#
alignment# :: Int32LE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Int32LE
indexByteArray# :: ByteArray# -> Int# -> Int32LE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32LE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32LE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int32LE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int32LE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int32LE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int32LE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Int32LE
indexOffAddr# :: Addr# -> Int# -> Int32LE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int32LE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int32LE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Int32LE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Int32LE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int32LE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int32LE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Int32LE
(ByteArray# -> Int# -> Int32LE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int32LE -> State# s -> State# s)
-> PrimUnaligned Int32LE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32LE #)
forall s.
MutableByteArray# s -> Int# -> Int32LE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Int32LE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Int32LE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32LE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32LE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int32LE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int32LE -> State# s -> State# s
PrimUnaligned, Int32LE
Int32LE -> Default Int32LE
forall a. a -> Default a
$cdef :: Int32LE
def :: Int32LE
Default, Eq Int32LE
Int32LE
Eq Int32LE =>
(Int32LE -> Int32LE -> Int32LE)
-> (Int32LE -> Int32LE -> Int32LE)
-> (Int32LE -> Int32LE -> Int32LE)
-> (Int32LE -> Int32LE)
-> (Int32LE -> Int -> Int32LE)
-> (Int32LE -> Int -> Int32LE)
-> Int32LE
-> (Int -> Int32LE)
-> (Int32LE -> Int -> Int32LE)
-> (Int32LE -> Int -> Int32LE)
-> (Int32LE -> Int -> Int32LE)
-> (Int32LE -> Int -> Bool)
-> (Int32LE -> Maybe Int)
-> (Int32LE -> Int)
-> (Int32LE -> Bool)
-> (Int32LE -> Int -> Int32LE)
-> (Int32LE -> Int -> Int32LE)
-> (Int32LE -> Int -> Int32LE)
-> (Int32LE -> Int -> Int32LE)
-> (Int32LE -> Int -> Int32LE)
-> (Int32LE -> Int -> Int32LE)
-> (Int32LE -> Int)
-> Bits Int32LE
Int -> Int32LE
Int32LE -> Bool
Int32LE -> Int
Int32LE -> Maybe Int
Int32LE -> Int32LE
Int32LE -> Int -> Bool
Int32LE -> Int -> Int32LE
Int32LE -> Int32LE -> Int32LE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Int32LE -> Int32LE -> Int32LE
.&. :: Int32LE -> Int32LE -> Int32LE
$c.|. :: Int32LE -> Int32LE -> Int32LE
.|. :: Int32LE -> Int32LE -> Int32LE
$cxor :: Int32LE -> Int32LE -> Int32LE
xor :: Int32LE -> Int32LE -> Int32LE
$ccomplement :: Int32LE -> Int32LE
complement :: Int32LE -> Int32LE
$cshift :: Int32LE -> Int -> Int32LE
shift :: Int32LE -> Int -> Int32LE
$crotate :: Int32LE -> Int -> Int32LE
rotate :: Int32LE -> Int -> Int32LE
$czeroBits :: Int32LE
zeroBits :: Int32LE
$cbit :: Int -> Int32LE
bit :: Int -> Int32LE
$csetBit :: Int32LE -> Int -> Int32LE
setBit :: Int32LE -> Int -> Int32LE
$cclearBit :: Int32LE -> Int -> Int32LE
clearBit :: Int32LE -> Int -> Int32LE
$ccomplementBit :: Int32LE -> Int -> Int32LE
complementBit :: Int32LE -> Int -> Int32LE
$ctestBit :: Int32LE -> Int -> Bool
testBit :: Int32LE -> Int -> Bool
$cbitSizeMaybe :: Int32LE -> Maybe Int
bitSizeMaybe :: Int32LE -> Maybe Int
$cbitSize :: Int32LE -> Int
bitSize :: Int32LE -> Int
$cisSigned :: Int32LE -> Bool
isSigned :: Int32LE -> Bool
$cshiftL :: Int32LE -> Int -> Int32LE
shiftL :: Int32LE -> Int -> Int32LE
$cunsafeShiftL :: Int32LE -> Int -> Int32LE
unsafeShiftL :: Int32LE -> Int -> Int32LE
$cshiftR :: Int32LE -> Int -> Int32LE
shiftR :: Int32LE -> Int -> Int32LE
$cunsafeShiftR :: Int32LE -> Int -> Int32LE
unsafeShiftR :: Int32LE -> Int -> Int32LE
$crotateL :: Int32LE -> Int -> Int32LE
rotateL :: Int32LE -> Int -> Int32LE
$crotateR :: Int32LE -> Int -> Int32LE
rotateR :: Int32LE -> Int -> Int32LE
$cpopCount :: Int32LE -> Int
popCount :: Int32LE -> Int
Bits, Bits Int32LE
Bits Int32LE =>
(Int32LE -> Int)
-> (Int32LE -> Int) -> (Int32LE -> Int) -> FiniteBits Int32LE
Int32LE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Int32LE -> Int
finiteBitSize :: Int32LE -> Int
$ccountLeadingZeros :: Int32LE -> Int
countLeadingZeros :: Int32LE -> Int
$ccountTrailingZeros :: Int32LE -> Int
countTrailingZeros :: Int32LE -> Int
FiniteBits, Int32LE
Int32LE -> Int32LE -> Bounded Int32LE
forall a. a -> a -> Bounded a
$cminBound :: Int32LE
minBound :: Int32LE
$cmaxBound :: Int32LE
maxBound :: Int32LE
Bounded)

newtype Int64LE = Int64LE {Int64LE -> Int64
unInt64LE :: Int64}
  deriving stock (Int -> Int64LE -> ShowS
[Int64LE] -> ShowS
Int64LE -> String
(Int -> Int64LE -> ShowS)
-> (Int64LE -> String) -> ([Int64LE] -> ShowS) -> Show Int64LE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Int64LE -> ShowS
showsPrec :: Int -> Int64LE -> ShowS
$cshow :: Int64LE -> String
show :: Int64LE -> String
$cshowList :: [Int64LE] -> ShowS
showList :: [Int64LE] -> ShowS
Show)
  deriving newtype (Int64LE -> Int64LE -> Bool
(Int64LE -> Int64LE -> Bool)
-> (Int64LE -> Int64LE -> Bool) -> Eq Int64LE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Int64LE -> Int64LE -> Bool
== :: Int64LE -> Int64LE -> Bool
$c/= :: Int64LE -> Int64LE -> Bool
/= :: Int64LE -> Int64LE -> Bool
Eq, Eq Int64LE
Eq Int64LE =>
(Int64LE -> Int64LE -> Ordering)
-> (Int64LE -> Int64LE -> Bool)
-> (Int64LE -> Int64LE -> Bool)
-> (Int64LE -> Int64LE -> Bool)
-> (Int64LE -> Int64LE -> Bool)
-> (Int64LE -> Int64LE -> Int64LE)
-> (Int64LE -> Int64LE -> Int64LE)
-> Ord Int64LE
Int64LE -> Int64LE -> Bool
Int64LE -> Int64LE -> Ordering
Int64LE -> Int64LE -> Int64LE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Int64LE -> Int64LE -> Ordering
compare :: Int64LE -> Int64LE -> Ordering
$c< :: Int64LE -> Int64LE -> Bool
< :: Int64LE -> Int64LE -> Bool
$c<= :: Int64LE -> Int64LE -> Bool
<= :: Int64LE -> Int64LE -> Bool
$c> :: Int64LE -> Int64LE -> Bool
> :: Int64LE -> Int64LE -> Bool
$c>= :: Int64LE -> Int64LE -> Bool
>= :: Int64LE -> Int64LE -> Bool
$cmax :: Int64LE -> Int64LE -> Int64LE
max :: Int64LE -> Int64LE -> Int64LE
$cmin :: Int64LE -> Int64LE -> Int64LE
min :: Int64LE -> Int64LE -> Int64LE
Ord, Integer -> Int64LE
Int64LE -> Int64LE
Int64LE -> Int64LE -> Int64LE
(Int64LE -> Int64LE -> Int64LE)
-> (Int64LE -> Int64LE -> Int64LE)
-> (Int64LE -> Int64LE -> Int64LE)
-> (Int64LE -> Int64LE)
-> (Int64LE -> Int64LE)
-> (Int64LE -> Int64LE)
-> (Integer -> Int64LE)
-> Num Int64LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Int64LE -> Int64LE -> Int64LE
+ :: Int64LE -> Int64LE -> Int64LE
$c- :: Int64LE -> Int64LE -> Int64LE
- :: Int64LE -> Int64LE -> Int64LE
$c* :: Int64LE -> Int64LE -> Int64LE
* :: Int64LE -> Int64LE -> Int64LE
$cnegate :: Int64LE -> Int64LE
negate :: Int64LE -> Int64LE
$cabs :: Int64LE -> Int64LE
abs :: Int64LE -> Int64LE
$csignum :: Int64LE -> Int64LE
signum :: Int64LE -> Int64LE
$cfromInteger :: Integer -> Int64LE
fromInteger :: Integer -> Int64LE
Num, Int -> Int64LE
Int64LE -> Int
Int64LE -> [Int64LE]
Int64LE -> Int64LE
Int64LE -> Int64LE -> [Int64LE]
Int64LE -> Int64LE -> Int64LE -> [Int64LE]
(Int64LE -> Int64LE)
-> (Int64LE -> Int64LE)
-> (Int -> Int64LE)
-> (Int64LE -> Int)
-> (Int64LE -> [Int64LE])
-> (Int64LE -> Int64LE -> [Int64LE])
-> (Int64LE -> Int64LE -> [Int64LE])
-> (Int64LE -> Int64LE -> Int64LE -> [Int64LE])
-> Enum Int64LE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Int64LE -> Int64LE
succ :: Int64LE -> Int64LE
$cpred :: Int64LE -> Int64LE
pred :: Int64LE -> Int64LE
$ctoEnum :: Int -> Int64LE
toEnum :: Int -> Int64LE
$cfromEnum :: Int64LE -> Int
fromEnum :: Int64LE -> Int
$cenumFrom :: Int64LE -> [Int64LE]
enumFrom :: Int64LE -> [Int64LE]
$cenumFromThen :: Int64LE -> Int64LE -> [Int64LE]
enumFromThen :: Int64LE -> Int64LE -> [Int64LE]
$cenumFromTo :: Int64LE -> Int64LE -> [Int64LE]
enumFromTo :: Int64LE -> Int64LE -> [Int64LE]
$cenumFromThenTo :: Int64LE -> Int64LE -> Int64LE -> [Int64LE]
enumFromThenTo :: Int64LE -> Int64LE -> Int64LE -> [Int64LE]
Enum, Num Int64LE
Ord Int64LE
(Num Int64LE, Ord Int64LE) => (Int64LE -> Rational) -> Real Int64LE
Int64LE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Int64LE -> Rational
toRational :: Int64LE -> Rational
Real, Enum Int64LE
Real Int64LE
(Real Int64LE, Enum Int64LE) =>
(Int64LE -> Int64LE -> Int64LE)
-> (Int64LE -> Int64LE -> Int64LE)
-> (Int64LE -> Int64LE -> Int64LE)
-> (Int64LE -> Int64LE -> Int64LE)
-> (Int64LE -> Int64LE -> (Int64LE, Int64LE))
-> (Int64LE -> Int64LE -> (Int64LE, Int64LE))
-> (Int64LE -> Integer)
-> Integral Int64LE
Int64LE -> Integer
Int64LE -> Int64LE -> (Int64LE, Int64LE)
Int64LE -> Int64LE -> Int64LE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Int64LE -> Int64LE -> Int64LE
quot :: Int64LE -> Int64LE -> Int64LE
$crem :: Int64LE -> Int64LE -> Int64LE
rem :: Int64LE -> Int64LE -> Int64LE
$cdiv :: Int64LE -> Int64LE -> Int64LE
div :: Int64LE -> Int64LE -> Int64LE
$cmod :: Int64LE -> Int64LE -> Int64LE
mod :: Int64LE -> Int64LE -> Int64LE
$cquotRem :: Int64LE -> Int64LE -> (Int64LE, Int64LE)
quotRem :: Int64LE -> Int64LE -> (Int64LE, Int64LE)
$cdivMod :: Int64LE -> Int64LE -> (Int64LE, Int64LE)
divMod :: Int64LE -> Int64LE -> (Int64LE, Int64LE)
$ctoInteger :: Int64LE -> Integer
toInteger :: Int64LE -> Integer
Integral, Addr# -> Int# -> Int64LE
ByteArray# -> Int# -> Int64LE
Proxy Int64LE -> Int#
Int64LE -> Int#
(Proxy Int64LE -> Int#)
-> (Int64LE -> Int#)
-> (Proxy Int64LE -> Int#)
-> (Int64LE -> Int#)
-> (ByteArray# -> Int# -> Int64LE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int64LE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Int64LE -> State# s -> State# s)
-> (Addr# -> Int# -> Int64LE)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, Int64LE #))
-> (forall s. Addr# -> Int# -> Int64LE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Int64LE -> State# s -> State# s)
-> Prim Int64LE
forall s. Addr# -> Int# -> Int# -> Int64LE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Int64LE #)
forall s. Addr# -> Int# -> Int64LE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Int64LE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64LE #)
forall s.
MutableByteArray# s -> Int# -> Int64LE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Int64LE -> Int#
sizeOfType# :: Proxy Int64LE -> Int#
$csizeOf# :: Int64LE -> Int#
sizeOf# :: Int64LE -> Int#
$calignmentOfType# :: Proxy Int64LE -> Int#
alignmentOfType# :: Proxy Int64LE -> Int#
$calignment# :: Int64LE -> Int#
alignment# :: Int64LE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Int64LE
indexByteArray# :: ByteArray# -> Int# -> Int64LE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64LE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64LE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int64LE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int64LE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int64LE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int64LE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Int64LE
indexOffAddr# :: Addr# -> Int# -> Int64LE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int64LE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int64LE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Int64LE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Int64LE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int64LE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int64LE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Int64LE
(ByteArray# -> Int# -> Int64LE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64LE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int64LE -> State# s -> State# s)
-> PrimUnaligned Int64LE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64LE #)
forall s.
MutableByteArray# s -> Int# -> Int64LE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Int64LE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Int64LE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64LE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64LE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int64LE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int64LE -> State# s -> State# s
PrimUnaligned, Int64LE
Int64LE -> Default Int64LE
forall a. a -> Default a
$cdef :: Int64LE
def :: Int64LE
Default, Eq Int64LE
Int64LE
Eq Int64LE =>
(Int64LE -> Int64LE -> Int64LE)
-> (Int64LE -> Int64LE -> Int64LE)
-> (Int64LE -> Int64LE -> Int64LE)
-> (Int64LE -> Int64LE)
-> (Int64LE -> Int -> Int64LE)
-> (Int64LE -> Int -> Int64LE)
-> Int64LE
-> (Int -> Int64LE)
-> (Int64LE -> Int -> Int64LE)
-> (Int64LE -> Int -> Int64LE)
-> (Int64LE -> Int -> Int64LE)
-> (Int64LE -> Int -> Bool)
-> (Int64LE -> Maybe Int)
-> (Int64LE -> Int)
-> (Int64LE -> Bool)
-> (Int64LE -> Int -> Int64LE)
-> (Int64LE -> Int -> Int64LE)
-> (Int64LE -> Int -> Int64LE)
-> (Int64LE -> Int -> Int64LE)
-> (Int64LE -> Int -> Int64LE)
-> (Int64LE -> Int -> Int64LE)
-> (Int64LE -> Int)
-> Bits Int64LE
Int -> Int64LE
Int64LE -> Bool
Int64LE -> Int
Int64LE -> Maybe Int
Int64LE -> Int64LE
Int64LE -> Int -> Bool
Int64LE -> Int -> Int64LE
Int64LE -> Int64LE -> Int64LE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Int64LE -> Int64LE -> Int64LE
.&. :: Int64LE -> Int64LE -> Int64LE
$c.|. :: Int64LE -> Int64LE -> Int64LE
.|. :: Int64LE -> Int64LE -> Int64LE
$cxor :: Int64LE -> Int64LE -> Int64LE
xor :: Int64LE -> Int64LE -> Int64LE
$ccomplement :: Int64LE -> Int64LE
complement :: Int64LE -> Int64LE
$cshift :: Int64LE -> Int -> Int64LE
shift :: Int64LE -> Int -> Int64LE
$crotate :: Int64LE -> Int -> Int64LE
rotate :: Int64LE -> Int -> Int64LE
$czeroBits :: Int64LE
zeroBits :: Int64LE
$cbit :: Int -> Int64LE
bit :: Int -> Int64LE
$csetBit :: Int64LE -> Int -> Int64LE
setBit :: Int64LE -> Int -> Int64LE
$cclearBit :: Int64LE -> Int -> Int64LE
clearBit :: Int64LE -> Int -> Int64LE
$ccomplementBit :: Int64LE -> Int -> Int64LE
complementBit :: Int64LE -> Int -> Int64LE
$ctestBit :: Int64LE -> Int -> Bool
testBit :: Int64LE -> Int -> Bool
$cbitSizeMaybe :: Int64LE -> Maybe Int
bitSizeMaybe :: Int64LE -> Maybe Int
$cbitSize :: Int64LE -> Int
bitSize :: Int64LE -> Int
$cisSigned :: Int64LE -> Bool
isSigned :: Int64LE -> Bool
$cshiftL :: Int64LE -> Int -> Int64LE
shiftL :: Int64LE -> Int -> Int64LE
$cunsafeShiftL :: Int64LE -> Int -> Int64LE
unsafeShiftL :: Int64LE -> Int -> Int64LE
$cshiftR :: Int64LE -> Int -> Int64LE
shiftR :: Int64LE -> Int -> Int64LE
$cunsafeShiftR :: Int64LE -> Int -> Int64LE
unsafeShiftR :: Int64LE -> Int -> Int64LE
$crotateL :: Int64LE -> Int -> Int64LE
rotateL :: Int64LE -> Int -> Int64LE
$crotateR :: Int64LE -> Int -> Int64LE
rotateR :: Int64LE -> Int -> Int64LE
$cpopCount :: Int64LE -> Int
popCount :: Int64LE -> Int
Bits, Bits Int64LE
Bits Int64LE =>
(Int64LE -> Int)
-> (Int64LE -> Int) -> (Int64LE -> Int) -> FiniteBits Int64LE
Int64LE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Int64LE -> Int
finiteBitSize :: Int64LE -> Int
$ccountLeadingZeros :: Int64LE -> Int
countLeadingZeros :: Int64LE -> Int
$ccountTrailingZeros :: Int64LE -> Int
countTrailingZeros :: Int64LE -> Int
FiniteBits, Int64LE
Int64LE -> Int64LE -> Bounded Int64LE
forall a. a -> a -> Bounded a
$cminBound :: Int64LE
minBound :: Int64LE
$cmaxBound :: Int64LE
maxBound :: Int64LE
Bounded)

newtype FloatLE = FloatLE {FloatLE -> Float
unFloatLE :: Float}
  deriving stock (Int -> FloatLE -> ShowS
[FloatLE] -> ShowS
FloatLE -> String
(Int -> FloatLE -> ShowS)
-> (FloatLE -> String) -> ([FloatLE] -> ShowS) -> Show FloatLE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FloatLE -> ShowS
showsPrec :: Int -> FloatLE -> ShowS
$cshow :: FloatLE -> String
show :: FloatLE -> String
$cshowList :: [FloatLE] -> ShowS
showList :: [FloatLE] -> ShowS
Show)
  deriving newtype (FloatLE -> FloatLE -> Bool
(FloatLE -> FloatLE -> Bool)
-> (FloatLE -> FloatLE -> Bool) -> Eq FloatLE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FloatLE -> FloatLE -> Bool
== :: FloatLE -> FloatLE -> Bool
$c/= :: FloatLE -> FloatLE -> Bool
/= :: FloatLE -> FloatLE -> Bool
Eq, Eq FloatLE
Eq FloatLE =>
(FloatLE -> FloatLE -> Ordering)
-> (FloatLE -> FloatLE -> Bool)
-> (FloatLE -> FloatLE -> Bool)
-> (FloatLE -> FloatLE -> Bool)
-> (FloatLE -> FloatLE -> Bool)
-> (FloatLE -> FloatLE -> FloatLE)
-> (FloatLE -> FloatLE -> FloatLE)
-> Ord FloatLE
FloatLE -> FloatLE -> Bool
FloatLE -> FloatLE -> Ordering
FloatLE -> FloatLE -> FloatLE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FloatLE -> FloatLE -> Ordering
compare :: FloatLE -> FloatLE -> Ordering
$c< :: FloatLE -> FloatLE -> Bool
< :: FloatLE -> FloatLE -> Bool
$c<= :: FloatLE -> FloatLE -> Bool
<= :: FloatLE -> FloatLE -> Bool
$c> :: FloatLE -> FloatLE -> Bool
> :: FloatLE -> FloatLE -> Bool
$c>= :: FloatLE -> FloatLE -> Bool
>= :: FloatLE -> FloatLE -> Bool
$cmax :: FloatLE -> FloatLE -> FloatLE
max :: FloatLE -> FloatLE -> FloatLE
$cmin :: FloatLE -> FloatLE -> FloatLE
min :: FloatLE -> FloatLE -> FloatLE
Ord, Integer -> FloatLE
FloatLE -> FloatLE
FloatLE -> FloatLE -> FloatLE
(FloatLE -> FloatLE -> FloatLE)
-> (FloatLE -> FloatLE -> FloatLE)
-> (FloatLE -> FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (Integer -> FloatLE)
-> Num FloatLE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: FloatLE -> FloatLE -> FloatLE
+ :: FloatLE -> FloatLE -> FloatLE
$c- :: FloatLE -> FloatLE -> FloatLE
- :: FloatLE -> FloatLE -> FloatLE
$c* :: FloatLE -> FloatLE -> FloatLE
* :: FloatLE -> FloatLE -> FloatLE
$cnegate :: FloatLE -> FloatLE
negate :: FloatLE -> FloatLE
$cabs :: FloatLE -> FloatLE
abs :: FloatLE -> FloatLE
$csignum :: FloatLE -> FloatLE
signum :: FloatLE -> FloatLE
$cfromInteger :: Integer -> FloatLE
fromInteger :: Integer -> FloatLE
Num, Num FloatLE
Ord FloatLE
(Num FloatLE, Ord FloatLE) => (FloatLE -> Rational) -> Real FloatLE
FloatLE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: FloatLE -> Rational
toRational :: FloatLE -> Rational
Real, Num FloatLE
Num FloatLE =>
(FloatLE -> FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (Rational -> FloatLE)
-> Fractional FloatLE
Rational -> FloatLE
FloatLE -> FloatLE
FloatLE -> FloatLE -> FloatLE
forall a.
Num a =>
(a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
$c/ :: FloatLE -> FloatLE -> FloatLE
/ :: FloatLE -> FloatLE -> FloatLE
$crecip :: FloatLE -> FloatLE
recip :: FloatLE -> FloatLE
$cfromRational :: Rational -> FloatLE
fromRational :: Rational -> FloatLE
Fractional, Fractional FloatLE
FloatLE
Fractional FloatLE =>
FloatLE
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE -> FloatLE)
-> (FloatLE -> FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> (FloatLE -> FloatLE)
-> Floating FloatLE
FloatLE -> FloatLE
FloatLE -> FloatLE -> FloatLE
forall a.
Fractional a =>
a
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> Floating a
$cpi :: FloatLE
pi :: FloatLE
$cexp :: FloatLE -> FloatLE
exp :: FloatLE -> FloatLE
$clog :: FloatLE -> FloatLE
log :: FloatLE -> FloatLE
$csqrt :: FloatLE -> FloatLE
sqrt :: FloatLE -> FloatLE
$c** :: FloatLE -> FloatLE -> FloatLE
** :: FloatLE -> FloatLE -> FloatLE
$clogBase :: FloatLE -> FloatLE -> FloatLE
logBase :: FloatLE -> FloatLE -> FloatLE
$csin :: FloatLE -> FloatLE
sin :: FloatLE -> FloatLE
$ccos :: FloatLE -> FloatLE
cos :: FloatLE -> FloatLE
$ctan :: FloatLE -> FloatLE
tan :: FloatLE -> FloatLE
$casin :: FloatLE -> FloatLE
asin :: FloatLE -> FloatLE
$cacos :: FloatLE -> FloatLE
acos :: FloatLE -> FloatLE
$catan :: FloatLE -> FloatLE
atan :: FloatLE -> FloatLE
$csinh :: FloatLE -> FloatLE
sinh :: FloatLE -> FloatLE
$ccosh :: FloatLE -> FloatLE
cosh :: FloatLE -> FloatLE
$ctanh :: FloatLE -> FloatLE
tanh :: FloatLE -> FloatLE
$casinh :: FloatLE -> FloatLE
asinh :: FloatLE -> FloatLE
$cacosh :: FloatLE -> FloatLE
acosh :: FloatLE -> FloatLE
$catanh :: FloatLE -> FloatLE
atanh :: FloatLE -> FloatLE
$clog1p :: FloatLE -> FloatLE
log1p :: FloatLE -> FloatLE
$cexpm1 :: FloatLE -> FloatLE
expm1 :: FloatLE -> FloatLE
$clog1pexp :: FloatLE -> FloatLE
log1pexp :: FloatLE -> FloatLE
$clog1mexp :: FloatLE -> FloatLE
log1mexp :: FloatLE -> FloatLE
Floating, ByteArray# -> Int# -> FloatLE
(ByteArray# -> Int# -> FloatLE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatLE #))
-> (forall s.
    MutableByteArray# s -> Int# -> FloatLE -> State# s -> State# s)
-> PrimUnaligned FloatLE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatLE #)
forall s.
MutableByteArray# s -> Int# -> FloatLE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> FloatLE
indexUnalignedByteArray# :: ByteArray# -> Int# -> FloatLE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatLE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatLE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> FloatLE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> FloatLE -> State# s -> State# s
PrimUnaligned, Fractional FloatLE
Real FloatLE
(Real FloatLE, Fractional FloatLE) =>
(forall b. Integral b => FloatLE -> (b, FloatLE))
-> (forall b. Integral b => FloatLE -> b)
-> (forall b. Integral b => FloatLE -> b)
-> (forall b. Integral b => FloatLE -> b)
-> (forall b. Integral b => FloatLE -> b)
-> RealFrac FloatLE
forall b. Integral b => FloatLE -> b
forall b. Integral b => FloatLE -> (b, FloatLE)
forall a.
(Real a, Fractional a) =>
(forall b. Integral b => a -> (b, a))
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> RealFrac a
$cproperFraction :: forall b. Integral b => FloatLE -> (b, FloatLE)
properFraction :: forall b. Integral b => FloatLE -> (b, FloatLE)
$ctruncate :: forall b. Integral b => FloatLE -> b
truncate :: forall b. Integral b => FloatLE -> b
$cround :: forall b. Integral b => FloatLE -> b
round :: forall b. Integral b => FloatLE -> b
$cceiling :: forall b. Integral b => FloatLE -> b
ceiling :: forall b. Integral b => FloatLE -> b
$cfloor :: forall b. Integral b => FloatLE -> b
floor :: forall b. Integral b => FloatLE -> b
RealFrac, FloatLE
FloatLE -> Default FloatLE
forall a. a -> Default a
$cdef :: FloatLE
def :: FloatLE
Default, Addr# -> Int# -> FloatLE
ByteArray# -> Int# -> FloatLE
Proxy FloatLE -> Int#
FloatLE -> Int#
(Proxy FloatLE -> Int#)
-> (FloatLE -> Int#)
-> (Proxy FloatLE -> Int#)
-> (FloatLE -> Int#)
-> (ByteArray# -> Int# -> FloatLE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatLE #))
-> (forall s.
    MutableByteArray# s -> Int# -> FloatLE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> FloatLE -> State# s -> State# s)
-> (Addr# -> Int# -> FloatLE)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, FloatLE #))
-> (forall s. Addr# -> Int# -> FloatLE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> FloatLE -> State# s -> State# s)
-> Prim FloatLE
forall s. Addr# -> Int# -> Int# -> FloatLE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, FloatLE #)
forall s. Addr# -> Int# -> FloatLE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> FloatLE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatLE #)
forall s.
MutableByteArray# s -> Int# -> FloatLE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy FloatLE -> Int#
sizeOfType# :: Proxy FloatLE -> Int#
$csizeOf# :: FloatLE -> Int#
sizeOf# :: FloatLE -> Int#
$calignmentOfType# :: Proxy FloatLE -> Int#
alignmentOfType# :: Proxy FloatLE -> Int#
$calignment# :: FloatLE -> Int#
alignment# :: FloatLE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> FloatLE
indexByteArray# :: ByteArray# -> Int# -> FloatLE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatLE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatLE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> FloatLE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> FloatLE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> FloatLE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> FloatLE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> FloatLE
indexOffAddr# :: Addr# -> Int# -> FloatLE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, FloatLE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, FloatLE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> FloatLE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> FloatLE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> FloatLE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> FloatLE -> State# s -> State# s
Prim)

newtype DoubleLE = DoubleLE {DoubleLE -> Double
unDoubleLE :: Double}
  deriving stock (Int -> DoubleLE -> ShowS
[DoubleLE] -> ShowS
DoubleLE -> String
(Int -> DoubleLE -> ShowS)
-> (DoubleLE -> String) -> ([DoubleLE] -> ShowS) -> Show DoubleLE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DoubleLE -> ShowS
showsPrec :: Int -> DoubleLE -> ShowS
$cshow :: DoubleLE -> String
show :: DoubleLE -> String
$cshowList :: [DoubleLE] -> ShowS
showList :: [DoubleLE] -> ShowS
Show)
  deriving newtype (DoubleLE -> DoubleLE -> Bool
(DoubleLE -> DoubleLE -> Bool)
-> (DoubleLE -> DoubleLE -> Bool) -> Eq DoubleLE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DoubleLE -> DoubleLE -> Bool
== :: DoubleLE -> DoubleLE -> Bool
$c/= :: DoubleLE -> DoubleLE -> Bool
/= :: DoubleLE -> DoubleLE -> Bool
Eq, Eq DoubleLE
Eq DoubleLE =>
(DoubleLE -> DoubleLE -> Ordering)
-> (DoubleLE -> DoubleLE -> Bool)
-> (DoubleLE -> DoubleLE -> Bool)
-> (DoubleLE -> DoubleLE -> Bool)
-> (DoubleLE -> DoubleLE -> Bool)
-> (DoubleLE -> DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE -> DoubleLE)
-> Ord DoubleLE
DoubleLE -> DoubleLE -> Bool
DoubleLE -> DoubleLE -> Ordering
DoubleLE -> DoubleLE -> DoubleLE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DoubleLE -> DoubleLE -> Ordering
compare :: DoubleLE -> DoubleLE -> Ordering
$c< :: DoubleLE -> DoubleLE -> Bool
< :: DoubleLE -> DoubleLE -> Bool
$c<= :: DoubleLE -> DoubleLE -> Bool
<= :: DoubleLE -> DoubleLE -> Bool
$c> :: DoubleLE -> DoubleLE -> Bool
> :: DoubleLE -> DoubleLE -> Bool
$c>= :: DoubleLE -> DoubleLE -> Bool
>= :: DoubleLE -> DoubleLE -> Bool
$cmax :: DoubleLE -> DoubleLE -> DoubleLE
max :: DoubleLE -> DoubleLE -> DoubleLE
$cmin :: DoubleLE -> DoubleLE -> DoubleLE
min :: DoubleLE -> DoubleLE -> DoubleLE
Ord, Integer -> DoubleLE
DoubleLE -> DoubleLE
DoubleLE -> DoubleLE -> DoubleLE
(DoubleLE -> DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (Integer -> DoubleLE)
-> Num DoubleLE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: DoubleLE -> DoubleLE -> DoubleLE
+ :: DoubleLE -> DoubleLE -> DoubleLE
$c- :: DoubleLE -> DoubleLE -> DoubleLE
- :: DoubleLE -> DoubleLE -> DoubleLE
$c* :: DoubleLE -> DoubleLE -> DoubleLE
* :: DoubleLE -> DoubleLE -> DoubleLE
$cnegate :: DoubleLE -> DoubleLE
negate :: DoubleLE -> DoubleLE
$cabs :: DoubleLE -> DoubleLE
abs :: DoubleLE -> DoubleLE
$csignum :: DoubleLE -> DoubleLE
signum :: DoubleLE -> DoubleLE
$cfromInteger :: Integer -> DoubleLE
fromInteger :: Integer -> DoubleLE
Num, Num DoubleLE
Ord DoubleLE
(Num DoubleLE, Ord DoubleLE) =>
(DoubleLE -> Rational) -> Real DoubleLE
DoubleLE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: DoubleLE -> Rational
toRational :: DoubleLE -> Rational
Real, Num DoubleLE
Num DoubleLE =>
(DoubleLE -> DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (Rational -> DoubleLE)
-> Fractional DoubleLE
Rational -> DoubleLE
DoubleLE -> DoubleLE
DoubleLE -> DoubleLE -> DoubleLE
forall a.
Num a =>
(a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
$c/ :: DoubleLE -> DoubleLE -> DoubleLE
/ :: DoubleLE -> DoubleLE -> DoubleLE
$crecip :: DoubleLE -> DoubleLE
recip :: DoubleLE -> DoubleLE
$cfromRational :: Rational -> DoubleLE
fromRational :: Rational -> DoubleLE
Fractional, Fractional DoubleLE
DoubleLE
Fractional DoubleLE =>
DoubleLE
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> (DoubleLE -> DoubleLE)
-> Floating DoubleLE
DoubleLE -> DoubleLE
DoubleLE -> DoubleLE -> DoubleLE
forall a.
Fractional a =>
a
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> Floating a
$cpi :: DoubleLE
pi :: DoubleLE
$cexp :: DoubleLE -> DoubleLE
exp :: DoubleLE -> DoubleLE
$clog :: DoubleLE -> DoubleLE
log :: DoubleLE -> DoubleLE
$csqrt :: DoubleLE -> DoubleLE
sqrt :: DoubleLE -> DoubleLE
$c** :: DoubleLE -> DoubleLE -> DoubleLE
** :: DoubleLE -> DoubleLE -> DoubleLE
$clogBase :: DoubleLE -> DoubleLE -> DoubleLE
logBase :: DoubleLE -> DoubleLE -> DoubleLE
$csin :: DoubleLE -> DoubleLE
sin :: DoubleLE -> DoubleLE
$ccos :: DoubleLE -> DoubleLE
cos :: DoubleLE -> DoubleLE
$ctan :: DoubleLE -> DoubleLE
tan :: DoubleLE -> DoubleLE
$casin :: DoubleLE -> DoubleLE
asin :: DoubleLE -> DoubleLE
$cacos :: DoubleLE -> DoubleLE
acos :: DoubleLE -> DoubleLE
$catan :: DoubleLE -> DoubleLE
atan :: DoubleLE -> DoubleLE
$csinh :: DoubleLE -> DoubleLE
sinh :: DoubleLE -> DoubleLE
$ccosh :: DoubleLE -> DoubleLE
cosh :: DoubleLE -> DoubleLE
$ctanh :: DoubleLE -> DoubleLE
tanh :: DoubleLE -> DoubleLE
$casinh :: DoubleLE -> DoubleLE
asinh :: DoubleLE -> DoubleLE
$cacosh :: DoubleLE -> DoubleLE
acosh :: DoubleLE -> DoubleLE
$catanh :: DoubleLE -> DoubleLE
atanh :: DoubleLE -> DoubleLE
$clog1p :: DoubleLE -> DoubleLE
log1p :: DoubleLE -> DoubleLE
$cexpm1 :: DoubleLE -> DoubleLE
expm1 :: DoubleLE -> DoubleLE
$clog1pexp :: DoubleLE -> DoubleLE
log1pexp :: DoubleLE -> DoubleLE
$clog1mexp :: DoubleLE -> DoubleLE
log1mexp :: DoubleLE -> DoubleLE
Floating, ByteArray# -> Int# -> DoubleLE
(ByteArray# -> Int# -> DoubleLE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, DoubleLE #))
-> (forall s.
    MutableByteArray# s -> Int# -> DoubleLE -> State# s -> State# s)
-> PrimUnaligned DoubleLE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleLE #)
forall s.
MutableByteArray# s -> Int# -> DoubleLE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> DoubleLE
indexUnalignedByteArray# :: ByteArray# -> Int# -> DoubleLE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleLE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleLE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> DoubleLE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> DoubleLE -> State# s -> State# s
PrimUnaligned, Fractional DoubleLE
Real DoubleLE
(Real DoubleLE, Fractional DoubleLE) =>
(forall b. Integral b => DoubleLE -> (b, DoubleLE))
-> (forall b. Integral b => DoubleLE -> b)
-> (forall b. Integral b => DoubleLE -> b)
-> (forall b. Integral b => DoubleLE -> b)
-> (forall b. Integral b => DoubleLE -> b)
-> RealFrac DoubleLE
forall b. Integral b => DoubleLE -> b
forall b. Integral b => DoubleLE -> (b, DoubleLE)
forall a.
(Real a, Fractional a) =>
(forall b. Integral b => a -> (b, a))
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> RealFrac a
$cproperFraction :: forall b. Integral b => DoubleLE -> (b, DoubleLE)
properFraction :: forall b. Integral b => DoubleLE -> (b, DoubleLE)
$ctruncate :: forall b. Integral b => DoubleLE -> b
truncate :: forall b. Integral b => DoubleLE -> b
$cround :: forall b. Integral b => DoubleLE -> b
round :: forall b. Integral b => DoubleLE -> b
$cceiling :: forall b. Integral b => DoubleLE -> b
ceiling :: forall b. Integral b => DoubleLE -> b
$cfloor :: forall b. Integral b => DoubleLE -> b
floor :: forall b. Integral b => DoubleLE -> b
RealFrac, DoubleLE
DoubleLE -> Default DoubleLE
forall a. a -> Default a
$cdef :: DoubleLE
def :: DoubleLE
Default, Addr# -> Int# -> DoubleLE
ByteArray# -> Int# -> DoubleLE
Proxy DoubleLE -> Int#
DoubleLE -> Int#
(Proxy DoubleLE -> Int#)
-> (DoubleLE -> Int#)
-> (Proxy DoubleLE -> Int#)
-> (DoubleLE -> Int#)
-> (ByteArray# -> Int# -> DoubleLE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, DoubleLE #))
-> (forall s.
    MutableByteArray# s -> Int# -> DoubleLE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> DoubleLE -> State# s -> State# s)
-> (Addr# -> Int# -> DoubleLE)
-> (forall s.
    Addr# -> Int# -> State# s -> (# State# s, DoubleLE #))
-> (forall s. Addr# -> Int# -> DoubleLE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> DoubleLE -> State# s -> State# s)
-> Prim DoubleLE
forall s. Addr# -> Int# -> Int# -> DoubleLE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, DoubleLE #)
forall s. Addr# -> Int# -> DoubleLE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> DoubleLE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleLE #)
forall s.
MutableByteArray# s -> Int# -> DoubleLE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy DoubleLE -> Int#
sizeOfType# :: Proxy DoubleLE -> Int#
$csizeOf# :: DoubleLE -> Int#
sizeOf# :: DoubleLE -> Int#
$calignmentOfType# :: Proxy DoubleLE -> Int#
alignmentOfType# :: Proxy DoubleLE -> Int#
$calignment# :: DoubleLE -> Int#
alignment# :: DoubleLE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> DoubleLE
indexByteArray# :: ByteArray# -> Int# -> DoubleLE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleLE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleLE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> DoubleLE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> DoubleLE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> DoubleLE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> DoubleLE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> DoubleLE
indexOffAddr# :: Addr# -> Int# -> DoubleLE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, DoubleLE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, DoubleLE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> DoubleLE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> DoubleLE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> DoubleLE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> DoubleLE -> State# s -> State# s
Prim)

newtype Word16BE = Word16BE {Word16BE -> Word16
unWord16BE :: Word16}
  deriving stock (Int -> Word16BE -> ShowS
[Word16BE] -> ShowS
Word16BE -> String
(Int -> Word16BE -> ShowS)
-> (Word16BE -> String) -> ([Word16BE] -> ShowS) -> Show Word16BE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Word16BE -> ShowS
showsPrec :: Int -> Word16BE -> ShowS
$cshow :: Word16BE -> String
show :: Word16BE -> String
$cshowList :: [Word16BE] -> ShowS
showList :: [Word16BE] -> ShowS
Show)
  deriving newtype (Word16BE -> Word16BE -> Bool
(Word16BE -> Word16BE -> Bool)
-> (Word16BE -> Word16BE -> Bool) -> Eq Word16BE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Word16BE -> Word16BE -> Bool
== :: Word16BE -> Word16BE -> Bool
$c/= :: Word16BE -> Word16BE -> Bool
/= :: Word16BE -> Word16BE -> Bool
Eq, Eq Word16BE
Eq Word16BE =>
(Word16BE -> Word16BE -> Ordering)
-> (Word16BE -> Word16BE -> Bool)
-> (Word16BE -> Word16BE -> Bool)
-> (Word16BE -> Word16BE -> Bool)
-> (Word16BE -> Word16BE -> Bool)
-> (Word16BE -> Word16BE -> Word16BE)
-> (Word16BE -> Word16BE -> Word16BE)
-> Ord Word16BE
Word16BE -> Word16BE -> Bool
Word16BE -> Word16BE -> Ordering
Word16BE -> Word16BE -> Word16BE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Word16BE -> Word16BE -> Ordering
compare :: Word16BE -> Word16BE -> Ordering
$c< :: Word16BE -> Word16BE -> Bool
< :: Word16BE -> Word16BE -> Bool
$c<= :: Word16BE -> Word16BE -> Bool
<= :: Word16BE -> Word16BE -> Bool
$c> :: Word16BE -> Word16BE -> Bool
> :: Word16BE -> Word16BE -> Bool
$c>= :: Word16BE -> Word16BE -> Bool
>= :: Word16BE -> Word16BE -> Bool
$cmax :: Word16BE -> Word16BE -> Word16BE
max :: Word16BE -> Word16BE -> Word16BE
$cmin :: Word16BE -> Word16BE -> Word16BE
min :: Word16BE -> Word16BE -> Word16BE
Ord, Int -> Word16BE
Word16BE -> Int
Word16BE -> [Word16BE]
Word16BE -> Word16BE
Word16BE -> Word16BE -> [Word16BE]
Word16BE -> Word16BE -> Word16BE -> [Word16BE]
(Word16BE -> Word16BE)
-> (Word16BE -> Word16BE)
-> (Int -> Word16BE)
-> (Word16BE -> Int)
-> (Word16BE -> [Word16BE])
-> (Word16BE -> Word16BE -> [Word16BE])
-> (Word16BE -> Word16BE -> [Word16BE])
-> (Word16BE -> Word16BE -> Word16BE -> [Word16BE])
-> Enum Word16BE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Word16BE -> Word16BE
succ :: Word16BE -> Word16BE
$cpred :: Word16BE -> Word16BE
pred :: Word16BE -> Word16BE
$ctoEnum :: Int -> Word16BE
toEnum :: Int -> Word16BE
$cfromEnum :: Word16BE -> Int
fromEnum :: Word16BE -> Int
$cenumFrom :: Word16BE -> [Word16BE]
enumFrom :: Word16BE -> [Word16BE]
$cenumFromThen :: Word16BE -> Word16BE -> [Word16BE]
enumFromThen :: Word16BE -> Word16BE -> [Word16BE]
$cenumFromTo :: Word16BE -> Word16BE -> [Word16BE]
enumFromTo :: Word16BE -> Word16BE -> [Word16BE]
$cenumFromThenTo :: Word16BE -> Word16BE -> Word16BE -> [Word16BE]
enumFromThenTo :: Word16BE -> Word16BE -> Word16BE -> [Word16BE]
Enum, Integer -> Word16BE
Word16BE -> Word16BE
Word16BE -> Word16BE -> Word16BE
(Word16BE -> Word16BE -> Word16BE)
-> (Word16BE -> Word16BE -> Word16BE)
-> (Word16BE -> Word16BE -> Word16BE)
-> (Word16BE -> Word16BE)
-> (Word16BE -> Word16BE)
-> (Word16BE -> Word16BE)
-> (Integer -> Word16BE)
-> Num Word16BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Word16BE -> Word16BE -> Word16BE
+ :: Word16BE -> Word16BE -> Word16BE
$c- :: Word16BE -> Word16BE -> Word16BE
- :: Word16BE -> Word16BE -> Word16BE
$c* :: Word16BE -> Word16BE -> Word16BE
* :: Word16BE -> Word16BE -> Word16BE
$cnegate :: Word16BE -> Word16BE
negate :: Word16BE -> Word16BE
$cabs :: Word16BE -> Word16BE
abs :: Word16BE -> Word16BE
$csignum :: Word16BE -> Word16BE
signum :: Word16BE -> Word16BE
$cfromInteger :: Integer -> Word16BE
fromInteger :: Integer -> Word16BE
Num, Num Word16BE
Ord Word16BE
(Num Word16BE, Ord Word16BE) =>
(Word16BE -> Rational) -> Real Word16BE
Word16BE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Word16BE -> Rational
toRational :: Word16BE -> Rational
Real, Enum Word16BE
Real Word16BE
(Real Word16BE, Enum Word16BE) =>
(Word16BE -> Word16BE -> Word16BE)
-> (Word16BE -> Word16BE -> Word16BE)
-> (Word16BE -> Word16BE -> Word16BE)
-> (Word16BE -> Word16BE -> Word16BE)
-> (Word16BE -> Word16BE -> (Word16BE, Word16BE))
-> (Word16BE -> Word16BE -> (Word16BE, Word16BE))
-> (Word16BE -> Integer)
-> Integral Word16BE
Word16BE -> Integer
Word16BE -> Word16BE -> (Word16BE, Word16BE)
Word16BE -> Word16BE -> Word16BE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Word16BE -> Word16BE -> Word16BE
quot :: Word16BE -> Word16BE -> Word16BE
$crem :: Word16BE -> Word16BE -> Word16BE
rem :: Word16BE -> Word16BE -> Word16BE
$cdiv :: Word16BE -> Word16BE -> Word16BE
div :: Word16BE -> Word16BE -> Word16BE
$cmod :: Word16BE -> Word16BE -> Word16BE
mod :: Word16BE -> Word16BE -> Word16BE
$cquotRem :: Word16BE -> Word16BE -> (Word16BE, Word16BE)
quotRem :: Word16BE -> Word16BE -> (Word16BE, Word16BE)
$cdivMod :: Word16BE -> Word16BE -> (Word16BE, Word16BE)
divMod :: Word16BE -> Word16BE -> (Word16BE, Word16BE)
$ctoInteger :: Word16BE -> Integer
toInteger :: Word16BE -> Integer
Integral, Word16BE
Word16BE -> Default Word16BE
forall a. a -> Default a
$cdef :: Word16BE
def :: Word16BE
Default, Eq Word16BE
Word16BE
Eq Word16BE =>
(Word16BE -> Word16BE -> Word16BE)
-> (Word16BE -> Word16BE -> Word16BE)
-> (Word16BE -> Word16BE -> Word16BE)
-> (Word16BE -> Word16BE)
-> (Word16BE -> Int -> Word16BE)
-> (Word16BE -> Int -> Word16BE)
-> Word16BE
-> (Int -> Word16BE)
-> (Word16BE -> Int -> Word16BE)
-> (Word16BE -> Int -> Word16BE)
-> (Word16BE -> Int -> Word16BE)
-> (Word16BE -> Int -> Bool)
-> (Word16BE -> Maybe Int)
-> (Word16BE -> Int)
-> (Word16BE -> Bool)
-> (Word16BE -> Int -> Word16BE)
-> (Word16BE -> Int -> Word16BE)
-> (Word16BE -> Int -> Word16BE)
-> (Word16BE -> Int -> Word16BE)
-> (Word16BE -> Int -> Word16BE)
-> (Word16BE -> Int -> Word16BE)
-> (Word16BE -> Int)
-> Bits Word16BE
Int -> Word16BE
Word16BE -> Bool
Word16BE -> Int
Word16BE -> Maybe Int
Word16BE -> Word16BE
Word16BE -> Int -> Bool
Word16BE -> Int -> Word16BE
Word16BE -> Word16BE -> Word16BE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Word16BE -> Word16BE -> Word16BE
.&. :: Word16BE -> Word16BE -> Word16BE
$c.|. :: Word16BE -> Word16BE -> Word16BE
.|. :: Word16BE -> Word16BE -> Word16BE
$cxor :: Word16BE -> Word16BE -> Word16BE
xor :: Word16BE -> Word16BE -> Word16BE
$ccomplement :: Word16BE -> Word16BE
complement :: Word16BE -> Word16BE
$cshift :: Word16BE -> Int -> Word16BE
shift :: Word16BE -> Int -> Word16BE
$crotate :: Word16BE -> Int -> Word16BE
rotate :: Word16BE -> Int -> Word16BE
$czeroBits :: Word16BE
zeroBits :: Word16BE
$cbit :: Int -> Word16BE
bit :: Int -> Word16BE
$csetBit :: Word16BE -> Int -> Word16BE
setBit :: Word16BE -> Int -> Word16BE
$cclearBit :: Word16BE -> Int -> Word16BE
clearBit :: Word16BE -> Int -> Word16BE
$ccomplementBit :: Word16BE -> Int -> Word16BE
complementBit :: Word16BE -> Int -> Word16BE
$ctestBit :: Word16BE -> Int -> Bool
testBit :: Word16BE -> Int -> Bool
$cbitSizeMaybe :: Word16BE -> Maybe Int
bitSizeMaybe :: Word16BE -> Maybe Int
$cbitSize :: Word16BE -> Int
bitSize :: Word16BE -> Int
$cisSigned :: Word16BE -> Bool
isSigned :: Word16BE -> Bool
$cshiftL :: Word16BE -> Int -> Word16BE
shiftL :: Word16BE -> Int -> Word16BE
$cunsafeShiftL :: Word16BE -> Int -> Word16BE
unsafeShiftL :: Word16BE -> Int -> Word16BE
$cshiftR :: Word16BE -> Int -> Word16BE
shiftR :: Word16BE -> Int -> Word16BE
$cunsafeShiftR :: Word16BE -> Int -> Word16BE
unsafeShiftR :: Word16BE -> Int -> Word16BE
$crotateL :: Word16BE -> Int -> Word16BE
rotateL :: Word16BE -> Int -> Word16BE
$crotateR :: Word16BE -> Int -> Word16BE
rotateR :: Word16BE -> Int -> Word16BE
$cpopCount :: Word16BE -> Int
popCount :: Word16BE -> Int
Bits, Bits Word16BE
Bits Word16BE =>
(Word16BE -> Int)
-> (Word16BE -> Int) -> (Word16BE -> Int) -> FiniteBits Word16BE
Word16BE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Word16BE -> Int
finiteBitSize :: Word16BE -> Int
$ccountLeadingZeros :: Word16BE -> Int
countLeadingZeros :: Word16BE -> Int
$ccountTrailingZeros :: Word16BE -> Int
countTrailingZeros :: Word16BE -> Int
FiniteBits, Word16BE
Word16BE -> Word16BE -> Bounded Word16BE
forall a. a -> a -> Bounded a
$cminBound :: Word16BE
minBound :: Word16BE
$cmaxBound :: Word16BE
maxBound :: Word16BE
Bounded)
  deriving (Addr# -> Int# -> Word16BE
ByteArray# -> Int# -> Word16BE
Proxy Word16BE -> Int#
Word16BE -> Int#
(Proxy Word16BE -> Int#)
-> (Word16BE -> Int#)
-> (Proxy Word16BE -> Int#)
-> (Word16BE -> Int#)
-> (ByteArray# -> Int# -> Word16BE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word16BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word16BE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Word16BE -> State# s -> State# s)
-> (Addr# -> Int# -> Word16BE)
-> (forall s.
    Addr# -> Int# -> State# s -> (# State# s, Word16BE #))
-> (forall s. Addr# -> Int# -> Word16BE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Word16BE -> State# s -> State# s)
-> Prim Word16BE
forall s. Addr# -> Int# -> Int# -> Word16BE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Word16BE #)
forall s. Addr# -> Int# -> Word16BE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Word16BE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16BE #)
forall s.
MutableByteArray# s -> Int# -> Word16BE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Word16BE -> Int#
sizeOfType# :: Proxy Word16BE -> Int#
$csizeOf# :: Word16BE -> Int#
sizeOf# :: Word16BE -> Int#
$calignmentOfType# :: Proxy Word16BE -> Int#
alignmentOfType# :: Proxy Word16BE -> Int#
$calignment# :: Word16BE -> Int#
alignment# :: Word16BE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Word16BE
indexByteArray# :: ByteArray# -> Int# -> Word16BE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16BE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16BE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word16BE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word16BE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word16BE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word16BE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Word16BE
indexOffAddr# :: Addr# -> Int# -> Word16BE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word16BE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word16BE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Word16BE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Word16BE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word16BE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word16BE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Word16BE
(ByteArray# -> Int# -> Word16BE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word16BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word16BE -> State# s -> State# s)
-> PrimUnaligned Word16BE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16BE #)
forall s.
MutableByteArray# s -> Int# -> Word16BE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Word16BE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Word16BE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16BE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word16BE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word16BE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word16BE -> State# s -> State# s
PrimUnaligned) via (ViaSwapEndian Word16 Word16BE)

newtype Word24BE = Word24BE {Word24BE -> Word24
unWord24BE :: Word24}
  deriving stock (Int -> Word24BE -> ShowS
[Word24BE] -> ShowS
Word24BE -> String
(Int -> Word24BE -> ShowS)
-> (Word24BE -> String) -> ([Word24BE] -> ShowS) -> Show Word24BE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Word24BE -> ShowS
showsPrec :: Int -> Word24BE -> ShowS
$cshow :: Word24BE -> String
show :: Word24BE -> String
$cshowList :: [Word24BE] -> ShowS
showList :: [Word24BE] -> ShowS
Show)
  deriving newtype (Word24BE -> Word24BE -> Bool
(Word24BE -> Word24BE -> Bool)
-> (Word24BE -> Word24BE -> Bool) -> Eq Word24BE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Word24BE -> Word24BE -> Bool
== :: Word24BE -> Word24BE -> Bool
$c/= :: Word24BE -> Word24BE -> Bool
/= :: Word24BE -> Word24BE -> Bool
Eq, Eq Word24BE
Eq Word24BE =>
(Word24BE -> Word24BE -> Ordering)
-> (Word24BE -> Word24BE -> Bool)
-> (Word24BE -> Word24BE -> Bool)
-> (Word24BE -> Word24BE -> Bool)
-> (Word24BE -> Word24BE -> Bool)
-> (Word24BE -> Word24BE -> Word24BE)
-> (Word24BE -> Word24BE -> Word24BE)
-> Ord Word24BE
Word24BE -> Word24BE -> Bool
Word24BE -> Word24BE -> Ordering
Word24BE -> Word24BE -> Word24BE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Word24BE -> Word24BE -> Ordering
compare :: Word24BE -> Word24BE -> Ordering
$c< :: Word24BE -> Word24BE -> Bool
< :: Word24BE -> Word24BE -> Bool
$c<= :: Word24BE -> Word24BE -> Bool
<= :: Word24BE -> Word24BE -> Bool
$c> :: Word24BE -> Word24BE -> Bool
> :: Word24BE -> Word24BE -> Bool
$c>= :: Word24BE -> Word24BE -> Bool
>= :: Word24BE -> Word24BE -> Bool
$cmax :: Word24BE -> Word24BE -> Word24BE
max :: Word24BE -> Word24BE -> Word24BE
$cmin :: Word24BE -> Word24BE -> Word24BE
min :: Word24BE -> Word24BE -> Word24BE
Ord, Int -> Word24BE
Word24BE -> Int
Word24BE -> [Word24BE]
Word24BE -> Word24BE
Word24BE -> Word24BE -> [Word24BE]
Word24BE -> Word24BE -> Word24BE -> [Word24BE]
(Word24BE -> Word24BE)
-> (Word24BE -> Word24BE)
-> (Int -> Word24BE)
-> (Word24BE -> Int)
-> (Word24BE -> [Word24BE])
-> (Word24BE -> Word24BE -> [Word24BE])
-> (Word24BE -> Word24BE -> [Word24BE])
-> (Word24BE -> Word24BE -> Word24BE -> [Word24BE])
-> Enum Word24BE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Word24BE -> Word24BE
succ :: Word24BE -> Word24BE
$cpred :: Word24BE -> Word24BE
pred :: Word24BE -> Word24BE
$ctoEnum :: Int -> Word24BE
toEnum :: Int -> Word24BE
$cfromEnum :: Word24BE -> Int
fromEnum :: Word24BE -> Int
$cenumFrom :: Word24BE -> [Word24BE]
enumFrom :: Word24BE -> [Word24BE]
$cenumFromThen :: Word24BE -> Word24BE -> [Word24BE]
enumFromThen :: Word24BE -> Word24BE -> [Word24BE]
$cenumFromTo :: Word24BE -> Word24BE -> [Word24BE]
enumFromTo :: Word24BE -> Word24BE -> [Word24BE]
$cenumFromThenTo :: Word24BE -> Word24BE -> Word24BE -> [Word24BE]
enumFromThenTo :: Word24BE -> Word24BE -> Word24BE -> [Word24BE]
Enum, Integer -> Word24BE
Word24BE -> Word24BE
Word24BE -> Word24BE -> Word24BE
(Word24BE -> Word24BE -> Word24BE)
-> (Word24BE -> Word24BE -> Word24BE)
-> (Word24BE -> Word24BE -> Word24BE)
-> (Word24BE -> Word24BE)
-> (Word24BE -> Word24BE)
-> (Word24BE -> Word24BE)
-> (Integer -> Word24BE)
-> Num Word24BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Word24BE -> Word24BE -> Word24BE
+ :: Word24BE -> Word24BE -> Word24BE
$c- :: Word24BE -> Word24BE -> Word24BE
- :: Word24BE -> Word24BE -> Word24BE
$c* :: Word24BE -> Word24BE -> Word24BE
* :: Word24BE -> Word24BE -> Word24BE
$cnegate :: Word24BE -> Word24BE
negate :: Word24BE -> Word24BE
$cabs :: Word24BE -> Word24BE
abs :: Word24BE -> Word24BE
$csignum :: Word24BE -> Word24BE
signum :: Word24BE -> Word24BE
$cfromInteger :: Integer -> Word24BE
fromInteger :: Integer -> Word24BE
Num, Num Word24BE
Ord Word24BE
(Num Word24BE, Ord Word24BE) =>
(Word24BE -> Rational) -> Real Word24BE
Word24BE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Word24BE -> Rational
toRational :: Word24BE -> Rational
Real, Enum Word24BE
Real Word24BE
(Real Word24BE, Enum Word24BE) =>
(Word24BE -> Word24BE -> Word24BE)
-> (Word24BE -> Word24BE -> Word24BE)
-> (Word24BE -> Word24BE -> Word24BE)
-> (Word24BE -> Word24BE -> Word24BE)
-> (Word24BE -> Word24BE -> (Word24BE, Word24BE))
-> (Word24BE -> Word24BE -> (Word24BE, Word24BE))
-> (Word24BE -> Integer)
-> Integral Word24BE
Word24BE -> Integer
Word24BE -> Word24BE -> (Word24BE, Word24BE)
Word24BE -> Word24BE -> Word24BE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Word24BE -> Word24BE -> Word24BE
quot :: Word24BE -> Word24BE -> Word24BE
$crem :: Word24BE -> Word24BE -> Word24BE
rem :: Word24BE -> Word24BE -> Word24BE
$cdiv :: Word24BE -> Word24BE -> Word24BE
div :: Word24BE -> Word24BE -> Word24BE
$cmod :: Word24BE -> Word24BE -> Word24BE
mod :: Word24BE -> Word24BE -> Word24BE
$cquotRem :: Word24BE -> Word24BE -> (Word24BE, Word24BE)
quotRem :: Word24BE -> Word24BE -> (Word24BE, Word24BE)
$cdivMod :: Word24BE -> Word24BE -> (Word24BE, Word24BE)
divMod :: Word24BE -> Word24BE -> (Word24BE, Word24BE)
$ctoInteger :: Word24BE -> Integer
toInteger :: Word24BE -> Integer
Integral, Word24BE
Word24BE -> Default Word24BE
forall a. a -> Default a
$cdef :: Word24BE
def :: Word24BE
Default, Eq Word24BE
Word24BE
Eq Word24BE =>
(Word24BE -> Word24BE -> Word24BE)
-> (Word24BE -> Word24BE -> Word24BE)
-> (Word24BE -> Word24BE -> Word24BE)
-> (Word24BE -> Word24BE)
-> (Word24BE -> Int -> Word24BE)
-> (Word24BE -> Int -> Word24BE)
-> Word24BE
-> (Int -> Word24BE)
-> (Word24BE -> Int -> Word24BE)
-> (Word24BE -> Int -> Word24BE)
-> (Word24BE -> Int -> Word24BE)
-> (Word24BE -> Int -> Bool)
-> (Word24BE -> Maybe Int)
-> (Word24BE -> Int)
-> (Word24BE -> Bool)
-> (Word24BE -> Int -> Word24BE)
-> (Word24BE -> Int -> Word24BE)
-> (Word24BE -> Int -> Word24BE)
-> (Word24BE -> Int -> Word24BE)
-> (Word24BE -> Int -> Word24BE)
-> (Word24BE -> Int -> Word24BE)
-> (Word24BE -> Int)
-> Bits Word24BE
Int -> Word24BE
Word24BE -> Bool
Word24BE -> Int
Word24BE -> Maybe Int
Word24BE -> Word24BE
Word24BE -> Int -> Bool
Word24BE -> Int -> Word24BE
Word24BE -> Word24BE -> Word24BE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Word24BE -> Word24BE -> Word24BE
.&. :: Word24BE -> Word24BE -> Word24BE
$c.|. :: Word24BE -> Word24BE -> Word24BE
.|. :: Word24BE -> Word24BE -> Word24BE
$cxor :: Word24BE -> Word24BE -> Word24BE
xor :: Word24BE -> Word24BE -> Word24BE
$ccomplement :: Word24BE -> Word24BE
complement :: Word24BE -> Word24BE
$cshift :: Word24BE -> Int -> Word24BE
shift :: Word24BE -> Int -> Word24BE
$crotate :: Word24BE -> Int -> Word24BE
rotate :: Word24BE -> Int -> Word24BE
$czeroBits :: Word24BE
zeroBits :: Word24BE
$cbit :: Int -> Word24BE
bit :: Int -> Word24BE
$csetBit :: Word24BE -> Int -> Word24BE
setBit :: Word24BE -> Int -> Word24BE
$cclearBit :: Word24BE -> Int -> Word24BE
clearBit :: Word24BE -> Int -> Word24BE
$ccomplementBit :: Word24BE -> Int -> Word24BE
complementBit :: Word24BE -> Int -> Word24BE
$ctestBit :: Word24BE -> Int -> Bool
testBit :: Word24BE -> Int -> Bool
$cbitSizeMaybe :: Word24BE -> Maybe Int
bitSizeMaybe :: Word24BE -> Maybe Int
$cbitSize :: Word24BE -> Int
bitSize :: Word24BE -> Int
$cisSigned :: Word24BE -> Bool
isSigned :: Word24BE -> Bool
$cshiftL :: Word24BE -> Int -> Word24BE
shiftL :: Word24BE -> Int -> Word24BE
$cunsafeShiftL :: Word24BE -> Int -> Word24BE
unsafeShiftL :: Word24BE -> Int -> Word24BE
$cshiftR :: Word24BE -> Int -> Word24BE
shiftR :: Word24BE -> Int -> Word24BE
$cunsafeShiftR :: Word24BE -> Int -> Word24BE
unsafeShiftR :: Word24BE -> Int -> Word24BE
$crotateL :: Word24BE -> Int -> Word24BE
rotateL :: Word24BE -> Int -> Word24BE
$crotateR :: Word24BE -> Int -> Word24BE
rotateR :: Word24BE -> Int -> Word24BE
$cpopCount :: Word24BE -> Int
popCount :: Word24BE -> Int
Bits, Bits Word24BE
Bits Word24BE =>
(Word24BE -> Int)
-> (Word24BE -> Int) -> (Word24BE -> Int) -> FiniteBits Word24BE
Word24BE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Word24BE -> Int
finiteBitSize :: Word24BE -> Int
$ccountLeadingZeros :: Word24BE -> Int
countLeadingZeros :: Word24BE -> Int
$ccountTrailingZeros :: Word24BE -> Int
countTrailingZeros :: Word24BE -> Int
FiniteBits, Word24BE
Word24BE -> Word24BE -> Bounded Word24BE
forall a. a -> a -> Bounded a
$cminBound :: Word24BE
minBound :: Word24BE
$cmaxBound :: Word24BE
maxBound :: Word24BE
Bounded)
  deriving (Addr# -> Int# -> Word24BE
ByteArray# -> Int# -> Word24BE
Proxy Word24BE -> Int#
Word24BE -> Int#
(Proxy Word24BE -> Int#)
-> (Word24BE -> Int#)
-> (Proxy Word24BE -> Int#)
-> (Word24BE -> Int#)
-> (ByteArray# -> Int# -> Word24BE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word24BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word24BE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Word24BE -> State# s -> State# s)
-> (Addr# -> Int# -> Word24BE)
-> (forall s.
    Addr# -> Int# -> State# s -> (# State# s, Word24BE #))
-> (forall s. Addr# -> Int# -> Word24BE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Word24BE -> State# s -> State# s)
-> Prim Word24BE
forall s. Addr# -> Int# -> Int# -> Word24BE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Word24BE #)
forall s. Addr# -> Int# -> Word24BE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Word24BE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24BE #)
forall s.
MutableByteArray# s -> Int# -> Word24BE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Word24BE -> Int#
sizeOfType# :: Proxy Word24BE -> Int#
$csizeOf# :: Word24BE -> Int#
sizeOf# :: Word24BE -> Int#
$calignmentOfType# :: Proxy Word24BE -> Int#
alignmentOfType# :: Proxy Word24BE -> Int#
$calignment# :: Word24BE -> Int#
alignment# :: Word24BE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Word24BE
indexByteArray# :: ByteArray# -> Int# -> Word24BE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24BE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24BE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word24BE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word24BE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word24BE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word24BE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Word24BE
indexOffAddr# :: Addr# -> Int# -> Word24BE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word24BE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word24BE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Word24BE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Word24BE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word24BE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word24BE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Word24BE
(ByteArray# -> Int# -> Word24BE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word24BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word24BE -> State# s -> State# s)
-> PrimUnaligned Word24BE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24BE #)
forall s.
MutableByteArray# s -> Int# -> Word24BE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Word24BE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Word24BE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24BE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word24BE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word24BE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word24BE -> State# s -> State# s
PrimUnaligned) via (ViaSwapEndian Word24 Word24BE)

newtype Word32BE = Word32BE {Word32BE -> Word32
unWord32BE :: Word32}
  deriving stock (Int -> Word32BE -> ShowS
[Word32BE] -> ShowS
Word32BE -> String
(Int -> Word32BE -> ShowS)
-> (Word32BE -> String) -> ([Word32BE] -> ShowS) -> Show Word32BE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Word32BE -> ShowS
showsPrec :: Int -> Word32BE -> ShowS
$cshow :: Word32BE -> String
show :: Word32BE -> String
$cshowList :: [Word32BE] -> ShowS
showList :: [Word32BE] -> ShowS
Show)
  deriving newtype (Word32BE -> Word32BE -> Bool
(Word32BE -> Word32BE -> Bool)
-> (Word32BE -> Word32BE -> Bool) -> Eq Word32BE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Word32BE -> Word32BE -> Bool
== :: Word32BE -> Word32BE -> Bool
$c/= :: Word32BE -> Word32BE -> Bool
/= :: Word32BE -> Word32BE -> Bool
Eq, Eq Word32BE
Eq Word32BE =>
(Word32BE -> Word32BE -> Ordering)
-> (Word32BE -> Word32BE -> Bool)
-> (Word32BE -> Word32BE -> Bool)
-> (Word32BE -> Word32BE -> Bool)
-> (Word32BE -> Word32BE -> Bool)
-> (Word32BE -> Word32BE -> Word32BE)
-> (Word32BE -> Word32BE -> Word32BE)
-> Ord Word32BE
Word32BE -> Word32BE -> Bool
Word32BE -> Word32BE -> Ordering
Word32BE -> Word32BE -> Word32BE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Word32BE -> Word32BE -> Ordering
compare :: Word32BE -> Word32BE -> Ordering
$c< :: Word32BE -> Word32BE -> Bool
< :: Word32BE -> Word32BE -> Bool
$c<= :: Word32BE -> Word32BE -> Bool
<= :: Word32BE -> Word32BE -> Bool
$c> :: Word32BE -> Word32BE -> Bool
> :: Word32BE -> Word32BE -> Bool
$c>= :: Word32BE -> Word32BE -> Bool
>= :: Word32BE -> Word32BE -> Bool
$cmax :: Word32BE -> Word32BE -> Word32BE
max :: Word32BE -> Word32BE -> Word32BE
$cmin :: Word32BE -> Word32BE -> Word32BE
min :: Word32BE -> Word32BE -> Word32BE
Ord, Int -> Word32BE
Word32BE -> Int
Word32BE -> [Word32BE]
Word32BE -> Word32BE
Word32BE -> Word32BE -> [Word32BE]
Word32BE -> Word32BE -> Word32BE -> [Word32BE]
(Word32BE -> Word32BE)
-> (Word32BE -> Word32BE)
-> (Int -> Word32BE)
-> (Word32BE -> Int)
-> (Word32BE -> [Word32BE])
-> (Word32BE -> Word32BE -> [Word32BE])
-> (Word32BE -> Word32BE -> [Word32BE])
-> (Word32BE -> Word32BE -> Word32BE -> [Word32BE])
-> Enum Word32BE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Word32BE -> Word32BE
succ :: Word32BE -> Word32BE
$cpred :: Word32BE -> Word32BE
pred :: Word32BE -> Word32BE
$ctoEnum :: Int -> Word32BE
toEnum :: Int -> Word32BE
$cfromEnum :: Word32BE -> Int
fromEnum :: Word32BE -> Int
$cenumFrom :: Word32BE -> [Word32BE]
enumFrom :: Word32BE -> [Word32BE]
$cenumFromThen :: Word32BE -> Word32BE -> [Word32BE]
enumFromThen :: Word32BE -> Word32BE -> [Word32BE]
$cenumFromTo :: Word32BE -> Word32BE -> [Word32BE]
enumFromTo :: Word32BE -> Word32BE -> [Word32BE]
$cenumFromThenTo :: Word32BE -> Word32BE -> Word32BE -> [Word32BE]
enumFromThenTo :: Word32BE -> Word32BE -> Word32BE -> [Word32BE]
Enum, Integer -> Word32BE
Word32BE -> Word32BE
Word32BE -> Word32BE -> Word32BE
(Word32BE -> Word32BE -> Word32BE)
-> (Word32BE -> Word32BE -> Word32BE)
-> (Word32BE -> Word32BE -> Word32BE)
-> (Word32BE -> Word32BE)
-> (Word32BE -> Word32BE)
-> (Word32BE -> Word32BE)
-> (Integer -> Word32BE)
-> Num Word32BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Word32BE -> Word32BE -> Word32BE
+ :: Word32BE -> Word32BE -> Word32BE
$c- :: Word32BE -> Word32BE -> Word32BE
- :: Word32BE -> Word32BE -> Word32BE
$c* :: Word32BE -> Word32BE -> Word32BE
* :: Word32BE -> Word32BE -> Word32BE
$cnegate :: Word32BE -> Word32BE
negate :: Word32BE -> Word32BE
$cabs :: Word32BE -> Word32BE
abs :: Word32BE -> Word32BE
$csignum :: Word32BE -> Word32BE
signum :: Word32BE -> Word32BE
$cfromInteger :: Integer -> Word32BE
fromInteger :: Integer -> Word32BE
Num, Num Word32BE
Ord Word32BE
(Num Word32BE, Ord Word32BE) =>
(Word32BE -> Rational) -> Real Word32BE
Word32BE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Word32BE -> Rational
toRational :: Word32BE -> Rational
Real, Enum Word32BE
Real Word32BE
(Real Word32BE, Enum Word32BE) =>
(Word32BE -> Word32BE -> Word32BE)
-> (Word32BE -> Word32BE -> Word32BE)
-> (Word32BE -> Word32BE -> Word32BE)
-> (Word32BE -> Word32BE -> Word32BE)
-> (Word32BE -> Word32BE -> (Word32BE, Word32BE))
-> (Word32BE -> Word32BE -> (Word32BE, Word32BE))
-> (Word32BE -> Integer)
-> Integral Word32BE
Word32BE -> Integer
Word32BE -> Word32BE -> (Word32BE, Word32BE)
Word32BE -> Word32BE -> Word32BE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Word32BE -> Word32BE -> Word32BE
quot :: Word32BE -> Word32BE -> Word32BE
$crem :: Word32BE -> Word32BE -> Word32BE
rem :: Word32BE -> Word32BE -> Word32BE
$cdiv :: Word32BE -> Word32BE -> Word32BE
div :: Word32BE -> Word32BE -> Word32BE
$cmod :: Word32BE -> Word32BE -> Word32BE
mod :: Word32BE -> Word32BE -> Word32BE
$cquotRem :: Word32BE -> Word32BE -> (Word32BE, Word32BE)
quotRem :: Word32BE -> Word32BE -> (Word32BE, Word32BE)
$cdivMod :: Word32BE -> Word32BE -> (Word32BE, Word32BE)
divMod :: Word32BE -> Word32BE -> (Word32BE, Word32BE)
$ctoInteger :: Word32BE -> Integer
toInteger :: Word32BE -> Integer
Integral, Word32BE
Word32BE -> Default Word32BE
forall a. a -> Default a
$cdef :: Word32BE
def :: Word32BE
Default, Eq Word32BE
Word32BE
Eq Word32BE =>
(Word32BE -> Word32BE -> Word32BE)
-> (Word32BE -> Word32BE -> Word32BE)
-> (Word32BE -> Word32BE -> Word32BE)
-> (Word32BE -> Word32BE)
-> (Word32BE -> Int -> Word32BE)
-> (Word32BE -> Int -> Word32BE)
-> Word32BE
-> (Int -> Word32BE)
-> (Word32BE -> Int -> Word32BE)
-> (Word32BE -> Int -> Word32BE)
-> (Word32BE -> Int -> Word32BE)
-> (Word32BE -> Int -> Bool)
-> (Word32BE -> Maybe Int)
-> (Word32BE -> Int)
-> (Word32BE -> Bool)
-> (Word32BE -> Int -> Word32BE)
-> (Word32BE -> Int -> Word32BE)
-> (Word32BE -> Int -> Word32BE)
-> (Word32BE -> Int -> Word32BE)
-> (Word32BE -> Int -> Word32BE)
-> (Word32BE -> Int -> Word32BE)
-> (Word32BE -> Int)
-> Bits Word32BE
Int -> Word32BE
Word32BE -> Bool
Word32BE -> Int
Word32BE -> Maybe Int
Word32BE -> Word32BE
Word32BE -> Int -> Bool
Word32BE -> Int -> Word32BE
Word32BE -> Word32BE -> Word32BE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Word32BE -> Word32BE -> Word32BE
.&. :: Word32BE -> Word32BE -> Word32BE
$c.|. :: Word32BE -> Word32BE -> Word32BE
.|. :: Word32BE -> Word32BE -> Word32BE
$cxor :: Word32BE -> Word32BE -> Word32BE
xor :: Word32BE -> Word32BE -> Word32BE
$ccomplement :: Word32BE -> Word32BE
complement :: Word32BE -> Word32BE
$cshift :: Word32BE -> Int -> Word32BE
shift :: Word32BE -> Int -> Word32BE
$crotate :: Word32BE -> Int -> Word32BE
rotate :: Word32BE -> Int -> Word32BE
$czeroBits :: Word32BE
zeroBits :: Word32BE
$cbit :: Int -> Word32BE
bit :: Int -> Word32BE
$csetBit :: Word32BE -> Int -> Word32BE
setBit :: Word32BE -> Int -> Word32BE
$cclearBit :: Word32BE -> Int -> Word32BE
clearBit :: Word32BE -> Int -> Word32BE
$ccomplementBit :: Word32BE -> Int -> Word32BE
complementBit :: Word32BE -> Int -> Word32BE
$ctestBit :: Word32BE -> Int -> Bool
testBit :: Word32BE -> Int -> Bool
$cbitSizeMaybe :: Word32BE -> Maybe Int
bitSizeMaybe :: Word32BE -> Maybe Int
$cbitSize :: Word32BE -> Int
bitSize :: Word32BE -> Int
$cisSigned :: Word32BE -> Bool
isSigned :: Word32BE -> Bool
$cshiftL :: Word32BE -> Int -> Word32BE
shiftL :: Word32BE -> Int -> Word32BE
$cunsafeShiftL :: Word32BE -> Int -> Word32BE
unsafeShiftL :: Word32BE -> Int -> Word32BE
$cshiftR :: Word32BE -> Int -> Word32BE
shiftR :: Word32BE -> Int -> Word32BE
$cunsafeShiftR :: Word32BE -> Int -> Word32BE
unsafeShiftR :: Word32BE -> Int -> Word32BE
$crotateL :: Word32BE -> Int -> Word32BE
rotateL :: Word32BE -> Int -> Word32BE
$crotateR :: Word32BE -> Int -> Word32BE
rotateR :: Word32BE -> Int -> Word32BE
$cpopCount :: Word32BE -> Int
popCount :: Word32BE -> Int
Bits, Bits Word32BE
Bits Word32BE =>
(Word32BE -> Int)
-> (Word32BE -> Int) -> (Word32BE -> Int) -> FiniteBits Word32BE
Word32BE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Word32BE -> Int
finiteBitSize :: Word32BE -> Int
$ccountLeadingZeros :: Word32BE -> Int
countLeadingZeros :: Word32BE -> Int
$ccountTrailingZeros :: Word32BE -> Int
countTrailingZeros :: Word32BE -> Int
FiniteBits, Word32BE
Word32BE -> Word32BE -> Bounded Word32BE
forall a. a -> a -> Bounded a
$cminBound :: Word32BE
minBound :: Word32BE
$cmaxBound :: Word32BE
maxBound :: Word32BE
Bounded)
  deriving (Addr# -> Int# -> Word32BE
ByteArray# -> Int# -> Word32BE
Proxy Word32BE -> Int#
Word32BE -> Int#
(Proxy Word32BE -> Int#)
-> (Word32BE -> Int#)
-> (Proxy Word32BE -> Int#)
-> (Word32BE -> Int#)
-> (ByteArray# -> Int# -> Word32BE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word32BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word32BE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Word32BE -> State# s -> State# s)
-> (Addr# -> Int# -> Word32BE)
-> (forall s.
    Addr# -> Int# -> State# s -> (# State# s, Word32BE #))
-> (forall s. Addr# -> Int# -> Word32BE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Word32BE -> State# s -> State# s)
-> Prim Word32BE
forall s. Addr# -> Int# -> Int# -> Word32BE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Word32BE #)
forall s. Addr# -> Int# -> Word32BE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Word32BE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32BE #)
forall s.
MutableByteArray# s -> Int# -> Word32BE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Word32BE -> Int#
sizeOfType# :: Proxy Word32BE -> Int#
$csizeOf# :: Word32BE -> Int#
sizeOf# :: Word32BE -> Int#
$calignmentOfType# :: Proxy Word32BE -> Int#
alignmentOfType# :: Proxy Word32BE -> Int#
$calignment# :: Word32BE -> Int#
alignment# :: Word32BE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Word32BE
indexByteArray# :: ByteArray# -> Int# -> Word32BE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32BE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32BE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word32BE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word32BE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word32BE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word32BE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Word32BE
indexOffAddr# :: Addr# -> Int# -> Word32BE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word32BE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word32BE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Word32BE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Word32BE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word32BE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word32BE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Word32BE
(ByteArray# -> Int# -> Word32BE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word32BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word32BE -> State# s -> State# s)
-> PrimUnaligned Word32BE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32BE #)
forall s.
MutableByteArray# s -> Int# -> Word32BE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Word32BE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Word32BE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32BE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word32BE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word32BE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word32BE -> State# s -> State# s
PrimUnaligned) via (ViaSwapEndian Word32 Word32BE)

newtype Word64BE = Word64BE {Word64BE -> Word64
unWord64BE :: Word64}
  deriving stock (Int -> Word64BE -> ShowS
[Word64BE] -> ShowS
Word64BE -> String
(Int -> Word64BE -> ShowS)
-> (Word64BE -> String) -> ([Word64BE] -> ShowS) -> Show Word64BE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Word64BE -> ShowS
showsPrec :: Int -> Word64BE -> ShowS
$cshow :: Word64BE -> String
show :: Word64BE -> String
$cshowList :: [Word64BE] -> ShowS
showList :: [Word64BE] -> ShowS
Show)
  deriving newtype (Word64BE -> Word64BE -> Bool
(Word64BE -> Word64BE -> Bool)
-> (Word64BE -> Word64BE -> Bool) -> Eq Word64BE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Word64BE -> Word64BE -> Bool
== :: Word64BE -> Word64BE -> Bool
$c/= :: Word64BE -> Word64BE -> Bool
/= :: Word64BE -> Word64BE -> Bool
Eq, Eq Word64BE
Eq Word64BE =>
(Word64BE -> Word64BE -> Ordering)
-> (Word64BE -> Word64BE -> Bool)
-> (Word64BE -> Word64BE -> Bool)
-> (Word64BE -> Word64BE -> Bool)
-> (Word64BE -> Word64BE -> Bool)
-> (Word64BE -> Word64BE -> Word64BE)
-> (Word64BE -> Word64BE -> Word64BE)
-> Ord Word64BE
Word64BE -> Word64BE -> Bool
Word64BE -> Word64BE -> Ordering
Word64BE -> Word64BE -> Word64BE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Word64BE -> Word64BE -> Ordering
compare :: Word64BE -> Word64BE -> Ordering
$c< :: Word64BE -> Word64BE -> Bool
< :: Word64BE -> Word64BE -> Bool
$c<= :: Word64BE -> Word64BE -> Bool
<= :: Word64BE -> Word64BE -> Bool
$c> :: Word64BE -> Word64BE -> Bool
> :: Word64BE -> Word64BE -> Bool
$c>= :: Word64BE -> Word64BE -> Bool
>= :: Word64BE -> Word64BE -> Bool
$cmax :: Word64BE -> Word64BE -> Word64BE
max :: Word64BE -> Word64BE -> Word64BE
$cmin :: Word64BE -> Word64BE -> Word64BE
min :: Word64BE -> Word64BE -> Word64BE
Ord, Int -> Word64BE
Word64BE -> Int
Word64BE -> [Word64BE]
Word64BE -> Word64BE
Word64BE -> Word64BE -> [Word64BE]
Word64BE -> Word64BE -> Word64BE -> [Word64BE]
(Word64BE -> Word64BE)
-> (Word64BE -> Word64BE)
-> (Int -> Word64BE)
-> (Word64BE -> Int)
-> (Word64BE -> [Word64BE])
-> (Word64BE -> Word64BE -> [Word64BE])
-> (Word64BE -> Word64BE -> [Word64BE])
-> (Word64BE -> Word64BE -> Word64BE -> [Word64BE])
-> Enum Word64BE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Word64BE -> Word64BE
succ :: Word64BE -> Word64BE
$cpred :: Word64BE -> Word64BE
pred :: Word64BE -> Word64BE
$ctoEnum :: Int -> Word64BE
toEnum :: Int -> Word64BE
$cfromEnum :: Word64BE -> Int
fromEnum :: Word64BE -> Int
$cenumFrom :: Word64BE -> [Word64BE]
enumFrom :: Word64BE -> [Word64BE]
$cenumFromThen :: Word64BE -> Word64BE -> [Word64BE]
enumFromThen :: Word64BE -> Word64BE -> [Word64BE]
$cenumFromTo :: Word64BE -> Word64BE -> [Word64BE]
enumFromTo :: Word64BE -> Word64BE -> [Word64BE]
$cenumFromThenTo :: Word64BE -> Word64BE -> Word64BE -> [Word64BE]
enumFromThenTo :: Word64BE -> Word64BE -> Word64BE -> [Word64BE]
Enum, Integer -> Word64BE
Word64BE -> Word64BE
Word64BE -> Word64BE -> Word64BE
(Word64BE -> Word64BE -> Word64BE)
-> (Word64BE -> Word64BE -> Word64BE)
-> (Word64BE -> Word64BE -> Word64BE)
-> (Word64BE -> Word64BE)
-> (Word64BE -> Word64BE)
-> (Word64BE -> Word64BE)
-> (Integer -> Word64BE)
-> Num Word64BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Word64BE -> Word64BE -> Word64BE
+ :: Word64BE -> Word64BE -> Word64BE
$c- :: Word64BE -> Word64BE -> Word64BE
- :: Word64BE -> Word64BE -> Word64BE
$c* :: Word64BE -> Word64BE -> Word64BE
* :: Word64BE -> Word64BE -> Word64BE
$cnegate :: Word64BE -> Word64BE
negate :: Word64BE -> Word64BE
$cabs :: Word64BE -> Word64BE
abs :: Word64BE -> Word64BE
$csignum :: Word64BE -> Word64BE
signum :: Word64BE -> Word64BE
$cfromInteger :: Integer -> Word64BE
fromInteger :: Integer -> Word64BE
Num, Num Word64BE
Ord Word64BE
(Num Word64BE, Ord Word64BE) =>
(Word64BE -> Rational) -> Real Word64BE
Word64BE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Word64BE -> Rational
toRational :: Word64BE -> Rational
Real, Enum Word64BE
Real Word64BE
(Real Word64BE, Enum Word64BE) =>
(Word64BE -> Word64BE -> Word64BE)
-> (Word64BE -> Word64BE -> Word64BE)
-> (Word64BE -> Word64BE -> Word64BE)
-> (Word64BE -> Word64BE -> Word64BE)
-> (Word64BE -> Word64BE -> (Word64BE, Word64BE))
-> (Word64BE -> Word64BE -> (Word64BE, Word64BE))
-> (Word64BE -> Integer)
-> Integral Word64BE
Word64BE -> Integer
Word64BE -> Word64BE -> (Word64BE, Word64BE)
Word64BE -> Word64BE -> Word64BE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Word64BE -> Word64BE -> Word64BE
quot :: Word64BE -> Word64BE -> Word64BE
$crem :: Word64BE -> Word64BE -> Word64BE
rem :: Word64BE -> Word64BE -> Word64BE
$cdiv :: Word64BE -> Word64BE -> Word64BE
div :: Word64BE -> Word64BE -> Word64BE
$cmod :: Word64BE -> Word64BE -> Word64BE
mod :: Word64BE -> Word64BE -> Word64BE
$cquotRem :: Word64BE -> Word64BE -> (Word64BE, Word64BE)
quotRem :: Word64BE -> Word64BE -> (Word64BE, Word64BE)
$cdivMod :: Word64BE -> Word64BE -> (Word64BE, Word64BE)
divMod :: Word64BE -> Word64BE -> (Word64BE, Word64BE)
$ctoInteger :: Word64BE -> Integer
toInteger :: Word64BE -> Integer
Integral, Word64BE
Word64BE -> Default Word64BE
forall a. a -> Default a
$cdef :: Word64BE
def :: Word64BE
Default, Eq Word64BE
Word64BE
Eq Word64BE =>
(Word64BE -> Word64BE -> Word64BE)
-> (Word64BE -> Word64BE -> Word64BE)
-> (Word64BE -> Word64BE -> Word64BE)
-> (Word64BE -> Word64BE)
-> (Word64BE -> Int -> Word64BE)
-> (Word64BE -> Int -> Word64BE)
-> Word64BE
-> (Int -> Word64BE)
-> (Word64BE -> Int -> Word64BE)
-> (Word64BE -> Int -> Word64BE)
-> (Word64BE -> Int -> Word64BE)
-> (Word64BE -> Int -> Bool)
-> (Word64BE -> Maybe Int)
-> (Word64BE -> Int)
-> (Word64BE -> Bool)
-> (Word64BE -> Int -> Word64BE)
-> (Word64BE -> Int -> Word64BE)
-> (Word64BE -> Int -> Word64BE)
-> (Word64BE -> Int -> Word64BE)
-> (Word64BE -> Int -> Word64BE)
-> (Word64BE -> Int -> Word64BE)
-> (Word64BE -> Int)
-> Bits Word64BE
Int -> Word64BE
Word64BE -> Bool
Word64BE -> Int
Word64BE -> Maybe Int
Word64BE -> Word64BE
Word64BE -> Int -> Bool
Word64BE -> Int -> Word64BE
Word64BE -> Word64BE -> Word64BE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Word64BE -> Word64BE -> Word64BE
.&. :: Word64BE -> Word64BE -> Word64BE
$c.|. :: Word64BE -> Word64BE -> Word64BE
.|. :: Word64BE -> Word64BE -> Word64BE
$cxor :: Word64BE -> Word64BE -> Word64BE
xor :: Word64BE -> Word64BE -> Word64BE
$ccomplement :: Word64BE -> Word64BE
complement :: Word64BE -> Word64BE
$cshift :: Word64BE -> Int -> Word64BE
shift :: Word64BE -> Int -> Word64BE
$crotate :: Word64BE -> Int -> Word64BE
rotate :: Word64BE -> Int -> Word64BE
$czeroBits :: Word64BE
zeroBits :: Word64BE
$cbit :: Int -> Word64BE
bit :: Int -> Word64BE
$csetBit :: Word64BE -> Int -> Word64BE
setBit :: Word64BE -> Int -> Word64BE
$cclearBit :: Word64BE -> Int -> Word64BE
clearBit :: Word64BE -> Int -> Word64BE
$ccomplementBit :: Word64BE -> Int -> Word64BE
complementBit :: Word64BE -> Int -> Word64BE
$ctestBit :: Word64BE -> Int -> Bool
testBit :: Word64BE -> Int -> Bool
$cbitSizeMaybe :: Word64BE -> Maybe Int
bitSizeMaybe :: Word64BE -> Maybe Int
$cbitSize :: Word64BE -> Int
bitSize :: Word64BE -> Int
$cisSigned :: Word64BE -> Bool
isSigned :: Word64BE -> Bool
$cshiftL :: Word64BE -> Int -> Word64BE
shiftL :: Word64BE -> Int -> Word64BE
$cunsafeShiftL :: Word64BE -> Int -> Word64BE
unsafeShiftL :: Word64BE -> Int -> Word64BE
$cshiftR :: Word64BE -> Int -> Word64BE
shiftR :: Word64BE -> Int -> Word64BE
$cunsafeShiftR :: Word64BE -> Int -> Word64BE
unsafeShiftR :: Word64BE -> Int -> Word64BE
$crotateL :: Word64BE -> Int -> Word64BE
rotateL :: Word64BE -> Int -> Word64BE
$crotateR :: Word64BE -> Int -> Word64BE
rotateR :: Word64BE -> Int -> Word64BE
$cpopCount :: Word64BE -> Int
popCount :: Word64BE -> Int
Bits, Bits Word64BE
Bits Word64BE =>
(Word64BE -> Int)
-> (Word64BE -> Int) -> (Word64BE -> Int) -> FiniteBits Word64BE
Word64BE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Word64BE -> Int
finiteBitSize :: Word64BE -> Int
$ccountLeadingZeros :: Word64BE -> Int
countLeadingZeros :: Word64BE -> Int
$ccountTrailingZeros :: Word64BE -> Int
countTrailingZeros :: Word64BE -> Int
FiniteBits, Word64BE
Word64BE -> Word64BE -> Bounded Word64BE
forall a. a -> a -> Bounded a
$cminBound :: Word64BE
minBound :: Word64BE
$cmaxBound :: Word64BE
maxBound :: Word64BE
Bounded)
  deriving (Addr# -> Int# -> Word64BE
ByteArray# -> Int# -> Word64BE
Proxy Word64BE -> Int#
Word64BE -> Int#
(Proxy Word64BE -> Int#)
-> (Word64BE -> Int#)
-> (Proxy Word64BE -> Int#)
-> (Word64BE -> Int#)
-> (ByteArray# -> Int# -> Word64BE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word64BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word64BE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Word64BE -> State# s -> State# s)
-> (Addr# -> Int# -> Word64BE)
-> (forall s.
    Addr# -> Int# -> State# s -> (# State# s, Word64BE #))
-> (forall s. Addr# -> Int# -> Word64BE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Word64BE -> State# s -> State# s)
-> Prim Word64BE
forall s. Addr# -> Int# -> Int# -> Word64BE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Word64BE #)
forall s. Addr# -> Int# -> Word64BE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Word64BE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64BE #)
forall s.
MutableByteArray# s -> Int# -> Word64BE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Word64BE -> Int#
sizeOfType# :: Proxy Word64BE -> Int#
$csizeOf# :: Word64BE -> Int#
sizeOf# :: Word64BE -> Int#
$calignmentOfType# :: Proxy Word64BE -> Int#
alignmentOfType# :: Proxy Word64BE -> Int#
$calignment# :: Word64BE -> Int#
alignment# :: Word64BE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Word64BE
indexByteArray# :: ByteArray# -> Int# -> Word64BE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64BE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64BE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word64BE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word64BE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word64BE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Word64BE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Word64BE
indexOffAddr# :: Addr# -> Int# -> Word64BE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word64BE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Word64BE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Word64BE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Word64BE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word64BE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Word64BE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Word64BE
(ByteArray# -> Int# -> Word64BE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, Word64BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Word64BE -> State# s -> State# s)
-> PrimUnaligned Word64BE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64BE #)
forall s.
MutableByteArray# s -> Int# -> Word64BE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Word64BE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Word64BE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64BE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Word64BE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word64BE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Word64BE -> State# s -> State# s
PrimUnaligned) via (ViaSwapEndian Word64 Word64BE)

newtype Int16BE = Int16BE {Int16BE -> Int16
unInt16BE :: Int16}
  deriving stock (Int -> Int16BE -> ShowS
[Int16BE] -> ShowS
Int16BE -> String
(Int -> Int16BE -> ShowS)
-> (Int16BE -> String) -> ([Int16BE] -> ShowS) -> Show Int16BE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Int16BE -> ShowS
showsPrec :: Int -> Int16BE -> ShowS
$cshow :: Int16BE -> String
show :: Int16BE -> String
$cshowList :: [Int16BE] -> ShowS
showList :: [Int16BE] -> ShowS
Show)
  deriving newtype (Int16BE -> Int16BE -> Bool
(Int16BE -> Int16BE -> Bool)
-> (Int16BE -> Int16BE -> Bool) -> Eq Int16BE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Int16BE -> Int16BE -> Bool
== :: Int16BE -> Int16BE -> Bool
$c/= :: Int16BE -> Int16BE -> Bool
/= :: Int16BE -> Int16BE -> Bool
Eq, Eq Int16BE
Eq Int16BE =>
(Int16BE -> Int16BE -> Ordering)
-> (Int16BE -> Int16BE -> Bool)
-> (Int16BE -> Int16BE -> Bool)
-> (Int16BE -> Int16BE -> Bool)
-> (Int16BE -> Int16BE -> Bool)
-> (Int16BE -> Int16BE -> Int16BE)
-> (Int16BE -> Int16BE -> Int16BE)
-> Ord Int16BE
Int16BE -> Int16BE -> Bool
Int16BE -> Int16BE -> Ordering
Int16BE -> Int16BE -> Int16BE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Int16BE -> Int16BE -> Ordering
compare :: Int16BE -> Int16BE -> Ordering
$c< :: Int16BE -> Int16BE -> Bool
< :: Int16BE -> Int16BE -> Bool
$c<= :: Int16BE -> Int16BE -> Bool
<= :: Int16BE -> Int16BE -> Bool
$c> :: Int16BE -> Int16BE -> Bool
> :: Int16BE -> Int16BE -> Bool
$c>= :: Int16BE -> Int16BE -> Bool
>= :: Int16BE -> Int16BE -> Bool
$cmax :: Int16BE -> Int16BE -> Int16BE
max :: Int16BE -> Int16BE -> Int16BE
$cmin :: Int16BE -> Int16BE -> Int16BE
min :: Int16BE -> Int16BE -> Int16BE
Ord, Int -> Int16BE
Int16BE -> Int
Int16BE -> [Int16BE]
Int16BE -> Int16BE
Int16BE -> Int16BE -> [Int16BE]
Int16BE -> Int16BE -> Int16BE -> [Int16BE]
(Int16BE -> Int16BE)
-> (Int16BE -> Int16BE)
-> (Int -> Int16BE)
-> (Int16BE -> Int)
-> (Int16BE -> [Int16BE])
-> (Int16BE -> Int16BE -> [Int16BE])
-> (Int16BE -> Int16BE -> [Int16BE])
-> (Int16BE -> Int16BE -> Int16BE -> [Int16BE])
-> Enum Int16BE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Int16BE -> Int16BE
succ :: Int16BE -> Int16BE
$cpred :: Int16BE -> Int16BE
pred :: Int16BE -> Int16BE
$ctoEnum :: Int -> Int16BE
toEnum :: Int -> Int16BE
$cfromEnum :: Int16BE -> Int
fromEnum :: Int16BE -> Int
$cenumFrom :: Int16BE -> [Int16BE]
enumFrom :: Int16BE -> [Int16BE]
$cenumFromThen :: Int16BE -> Int16BE -> [Int16BE]
enumFromThen :: Int16BE -> Int16BE -> [Int16BE]
$cenumFromTo :: Int16BE -> Int16BE -> [Int16BE]
enumFromTo :: Int16BE -> Int16BE -> [Int16BE]
$cenumFromThenTo :: Int16BE -> Int16BE -> Int16BE -> [Int16BE]
enumFromThenTo :: Int16BE -> Int16BE -> Int16BE -> [Int16BE]
Enum, Integer -> Int16BE
Int16BE -> Int16BE
Int16BE -> Int16BE -> Int16BE
(Int16BE -> Int16BE -> Int16BE)
-> (Int16BE -> Int16BE -> Int16BE)
-> (Int16BE -> Int16BE -> Int16BE)
-> (Int16BE -> Int16BE)
-> (Int16BE -> Int16BE)
-> (Int16BE -> Int16BE)
-> (Integer -> Int16BE)
-> Num Int16BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Int16BE -> Int16BE -> Int16BE
+ :: Int16BE -> Int16BE -> Int16BE
$c- :: Int16BE -> Int16BE -> Int16BE
- :: Int16BE -> Int16BE -> Int16BE
$c* :: Int16BE -> Int16BE -> Int16BE
* :: Int16BE -> Int16BE -> Int16BE
$cnegate :: Int16BE -> Int16BE
negate :: Int16BE -> Int16BE
$cabs :: Int16BE -> Int16BE
abs :: Int16BE -> Int16BE
$csignum :: Int16BE -> Int16BE
signum :: Int16BE -> Int16BE
$cfromInteger :: Integer -> Int16BE
fromInteger :: Integer -> Int16BE
Num, Num Int16BE
Ord Int16BE
(Num Int16BE, Ord Int16BE) => (Int16BE -> Rational) -> Real Int16BE
Int16BE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Int16BE -> Rational
toRational :: Int16BE -> Rational
Real, Enum Int16BE
Real Int16BE
(Real Int16BE, Enum Int16BE) =>
(Int16BE -> Int16BE -> Int16BE)
-> (Int16BE -> Int16BE -> Int16BE)
-> (Int16BE -> Int16BE -> Int16BE)
-> (Int16BE -> Int16BE -> Int16BE)
-> (Int16BE -> Int16BE -> (Int16BE, Int16BE))
-> (Int16BE -> Int16BE -> (Int16BE, Int16BE))
-> (Int16BE -> Integer)
-> Integral Int16BE
Int16BE -> Integer
Int16BE -> Int16BE -> (Int16BE, Int16BE)
Int16BE -> Int16BE -> Int16BE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Int16BE -> Int16BE -> Int16BE
quot :: Int16BE -> Int16BE -> Int16BE
$crem :: Int16BE -> Int16BE -> Int16BE
rem :: Int16BE -> Int16BE -> Int16BE
$cdiv :: Int16BE -> Int16BE -> Int16BE
div :: Int16BE -> Int16BE -> Int16BE
$cmod :: Int16BE -> Int16BE -> Int16BE
mod :: Int16BE -> Int16BE -> Int16BE
$cquotRem :: Int16BE -> Int16BE -> (Int16BE, Int16BE)
quotRem :: Int16BE -> Int16BE -> (Int16BE, Int16BE)
$cdivMod :: Int16BE -> Int16BE -> (Int16BE, Int16BE)
divMod :: Int16BE -> Int16BE -> (Int16BE, Int16BE)
$ctoInteger :: Int16BE -> Integer
toInteger :: Int16BE -> Integer
Integral, Int16BE
Int16BE -> Default Int16BE
forall a. a -> Default a
$cdef :: Int16BE
def :: Int16BE
Default, Eq Int16BE
Int16BE
Eq Int16BE =>
(Int16BE -> Int16BE -> Int16BE)
-> (Int16BE -> Int16BE -> Int16BE)
-> (Int16BE -> Int16BE -> Int16BE)
-> (Int16BE -> Int16BE)
-> (Int16BE -> Int -> Int16BE)
-> (Int16BE -> Int -> Int16BE)
-> Int16BE
-> (Int -> Int16BE)
-> (Int16BE -> Int -> Int16BE)
-> (Int16BE -> Int -> Int16BE)
-> (Int16BE -> Int -> Int16BE)
-> (Int16BE -> Int -> Bool)
-> (Int16BE -> Maybe Int)
-> (Int16BE -> Int)
-> (Int16BE -> Bool)
-> (Int16BE -> Int -> Int16BE)
-> (Int16BE -> Int -> Int16BE)
-> (Int16BE -> Int -> Int16BE)
-> (Int16BE -> Int -> Int16BE)
-> (Int16BE -> Int -> Int16BE)
-> (Int16BE -> Int -> Int16BE)
-> (Int16BE -> Int)
-> Bits Int16BE
Int -> Int16BE
Int16BE -> Bool
Int16BE -> Int
Int16BE -> Maybe Int
Int16BE -> Int16BE
Int16BE -> Int -> Bool
Int16BE -> Int -> Int16BE
Int16BE -> Int16BE -> Int16BE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Int16BE -> Int16BE -> Int16BE
.&. :: Int16BE -> Int16BE -> Int16BE
$c.|. :: Int16BE -> Int16BE -> Int16BE
.|. :: Int16BE -> Int16BE -> Int16BE
$cxor :: Int16BE -> Int16BE -> Int16BE
xor :: Int16BE -> Int16BE -> Int16BE
$ccomplement :: Int16BE -> Int16BE
complement :: Int16BE -> Int16BE
$cshift :: Int16BE -> Int -> Int16BE
shift :: Int16BE -> Int -> Int16BE
$crotate :: Int16BE -> Int -> Int16BE
rotate :: Int16BE -> Int -> Int16BE
$czeroBits :: Int16BE
zeroBits :: Int16BE
$cbit :: Int -> Int16BE
bit :: Int -> Int16BE
$csetBit :: Int16BE -> Int -> Int16BE
setBit :: Int16BE -> Int -> Int16BE
$cclearBit :: Int16BE -> Int -> Int16BE
clearBit :: Int16BE -> Int -> Int16BE
$ccomplementBit :: Int16BE -> Int -> Int16BE
complementBit :: Int16BE -> Int -> Int16BE
$ctestBit :: Int16BE -> Int -> Bool
testBit :: Int16BE -> Int -> Bool
$cbitSizeMaybe :: Int16BE -> Maybe Int
bitSizeMaybe :: Int16BE -> Maybe Int
$cbitSize :: Int16BE -> Int
bitSize :: Int16BE -> Int
$cisSigned :: Int16BE -> Bool
isSigned :: Int16BE -> Bool
$cshiftL :: Int16BE -> Int -> Int16BE
shiftL :: Int16BE -> Int -> Int16BE
$cunsafeShiftL :: Int16BE -> Int -> Int16BE
unsafeShiftL :: Int16BE -> Int -> Int16BE
$cshiftR :: Int16BE -> Int -> Int16BE
shiftR :: Int16BE -> Int -> Int16BE
$cunsafeShiftR :: Int16BE -> Int -> Int16BE
unsafeShiftR :: Int16BE -> Int -> Int16BE
$crotateL :: Int16BE -> Int -> Int16BE
rotateL :: Int16BE -> Int -> Int16BE
$crotateR :: Int16BE -> Int -> Int16BE
rotateR :: Int16BE -> Int -> Int16BE
$cpopCount :: Int16BE -> Int
popCount :: Int16BE -> Int
Bits, Bits Int16BE
Bits Int16BE =>
(Int16BE -> Int)
-> (Int16BE -> Int) -> (Int16BE -> Int) -> FiniteBits Int16BE
Int16BE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Int16BE -> Int
finiteBitSize :: Int16BE -> Int
$ccountLeadingZeros :: Int16BE -> Int
countLeadingZeros :: Int16BE -> Int
$ccountTrailingZeros :: Int16BE -> Int
countTrailingZeros :: Int16BE -> Int
FiniteBits, Int16BE
Int16BE -> Int16BE -> Bounded Int16BE
forall a. a -> a -> Bounded a
$cminBound :: Int16BE
minBound :: Int16BE
$cmaxBound :: Int16BE
maxBound :: Int16BE
Bounded)
  deriving (Addr# -> Int# -> Int16BE
ByteArray# -> Int# -> Int16BE
Proxy Int16BE -> Int#
Int16BE -> Int#
(Proxy Int16BE -> Int#)
-> (Int16BE -> Int#)
-> (Proxy Int16BE -> Int#)
-> (Int16BE -> Int#)
-> (ByteArray# -> Int# -> Int16BE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int16BE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Int16BE -> State# s -> State# s)
-> (Addr# -> Int# -> Int16BE)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, Int16BE #))
-> (forall s. Addr# -> Int# -> Int16BE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Int16BE -> State# s -> State# s)
-> Prim Int16BE
forall s. Addr# -> Int# -> Int# -> Int16BE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Int16BE #)
forall s. Addr# -> Int# -> Int16BE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Int16BE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16BE #)
forall s.
MutableByteArray# s -> Int# -> Int16BE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Int16BE -> Int#
sizeOfType# :: Proxy Int16BE -> Int#
$csizeOf# :: Int16BE -> Int#
sizeOf# :: Int16BE -> Int#
$calignmentOfType# :: Proxy Int16BE -> Int#
alignmentOfType# :: Proxy Int16BE -> Int#
$calignment# :: Int16BE -> Int#
alignment# :: Int16BE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Int16BE
indexByteArray# :: ByteArray# -> Int# -> Int16BE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16BE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16BE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int16BE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int16BE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int16BE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int16BE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Int16BE
indexOffAddr# :: Addr# -> Int# -> Int16BE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int16BE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int16BE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Int16BE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Int16BE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int16BE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int16BE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Int16BE
(ByteArray# -> Int# -> Int16BE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int16BE -> State# s -> State# s)
-> PrimUnaligned Int16BE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16BE #)
forall s.
MutableByteArray# s -> Int# -> Int16BE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Int16BE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Int16BE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16BE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int16BE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int16BE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int16BE -> State# s -> State# s
PrimUnaligned) via (ViaSwapEndian Int16 Int16BE)

newtype Int24BE = Int24BE {Int24BE -> Int24
unInt24BE :: Int24}
  deriving stock (Int -> Int24BE -> ShowS
[Int24BE] -> ShowS
Int24BE -> String
(Int -> Int24BE -> ShowS)
-> (Int24BE -> String) -> ([Int24BE] -> ShowS) -> Show Int24BE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Int24BE -> ShowS
showsPrec :: Int -> Int24BE -> ShowS
$cshow :: Int24BE -> String
show :: Int24BE -> String
$cshowList :: [Int24BE] -> ShowS
showList :: [Int24BE] -> ShowS
Show)
  deriving newtype (Int24BE -> Int24BE -> Bool
(Int24BE -> Int24BE -> Bool)
-> (Int24BE -> Int24BE -> Bool) -> Eq Int24BE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Int24BE -> Int24BE -> Bool
== :: Int24BE -> Int24BE -> Bool
$c/= :: Int24BE -> Int24BE -> Bool
/= :: Int24BE -> Int24BE -> Bool
Eq, Eq Int24BE
Eq Int24BE =>
(Int24BE -> Int24BE -> Ordering)
-> (Int24BE -> Int24BE -> Bool)
-> (Int24BE -> Int24BE -> Bool)
-> (Int24BE -> Int24BE -> Bool)
-> (Int24BE -> Int24BE -> Bool)
-> (Int24BE -> Int24BE -> Int24BE)
-> (Int24BE -> Int24BE -> Int24BE)
-> Ord Int24BE
Int24BE -> Int24BE -> Bool
Int24BE -> Int24BE -> Ordering
Int24BE -> Int24BE -> Int24BE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Int24BE -> Int24BE -> Ordering
compare :: Int24BE -> Int24BE -> Ordering
$c< :: Int24BE -> Int24BE -> Bool
< :: Int24BE -> Int24BE -> Bool
$c<= :: Int24BE -> Int24BE -> Bool
<= :: Int24BE -> Int24BE -> Bool
$c> :: Int24BE -> Int24BE -> Bool
> :: Int24BE -> Int24BE -> Bool
$c>= :: Int24BE -> Int24BE -> Bool
>= :: Int24BE -> Int24BE -> Bool
$cmax :: Int24BE -> Int24BE -> Int24BE
max :: Int24BE -> Int24BE -> Int24BE
$cmin :: Int24BE -> Int24BE -> Int24BE
min :: Int24BE -> Int24BE -> Int24BE
Ord, Int -> Int24BE
Int24BE -> Int
Int24BE -> [Int24BE]
Int24BE -> Int24BE
Int24BE -> Int24BE -> [Int24BE]
Int24BE -> Int24BE -> Int24BE -> [Int24BE]
(Int24BE -> Int24BE)
-> (Int24BE -> Int24BE)
-> (Int -> Int24BE)
-> (Int24BE -> Int)
-> (Int24BE -> [Int24BE])
-> (Int24BE -> Int24BE -> [Int24BE])
-> (Int24BE -> Int24BE -> [Int24BE])
-> (Int24BE -> Int24BE -> Int24BE -> [Int24BE])
-> Enum Int24BE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Int24BE -> Int24BE
succ :: Int24BE -> Int24BE
$cpred :: Int24BE -> Int24BE
pred :: Int24BE -> Int24BE
$ctoEnum :: Int -> Int24BE
toEnum :: Int -> Int24BE
$cfromEnum :: Int24BE -> Int
fromEnum :: Int24BE -> Int
$cenumFrom :: Int24BE -> [Int24BE]
enumFrom :: Int24BE -> [Int24BE]
$cenumFromThen :: Int24BE -> Int24BE -> [Int24BE]
enumFromThen :: Int24BE -> Int24BE -> [Int24BE]
$cenumFromTo :: Int24BE -> Int24BE -> [Int24BE]
enumFromTo :: Int24BE -> Int24BE -> [Int24BE]
$cenumFromThenTo :: Int24BE -> Int24BE -> Int24BE -> [Int24BE]
enumFromThenTo :: Int24BE -> Int24BE -> Int24BE -> [Int24BE]
Enum, Integer -> Int24BE
Int24BE -> Int24BE
Int24BE -> Int24BE -> Int24BE
(Int24BE -> Int24BE -> Int24BE)
-> (Int24BE -> Int24BE -> Int24BE)
-> (Int24BE -> Int24BE -> Int24BE)
-> (Int24BE -> Int24BE)
-> (Int24BE -> Int24BE)
-> (Int24BE -> Int24BE)
-> (Integer -> Int24BE)
-> Num Int24BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Int24BE -> Int24BE -> Int24BE
+ :: Int24BE -> Int24BE -> Int24BE
$c- :: Int24BE -> Int24BE -> Int24BE
- :: Int24BE -> Int24BE -> Int24BE
$c* :: Int24BE -> Int24BE -> Int24BE
* :: Int24BE -> Int24BE -> Int24BE
$cnegate :: Int24BE -> Int24BE
negate :: Int24BE -> Int24BE
$cabs :: Int24BE -> Int24BE
abs :: Int24BE -> Int24BE
$csignum :: Int24BE -> Int24BE
signum :: Int24BE -> Int24BE
$cfromInteger :: Integer -> Int24BE
fromInteger :: Integer -> Int24BE
Num, Num Int24BE
Ord Int24BE
(Num Int24BE, Ord Int24BE) => (Int24BE -> Rational) -> Real Int24BE
Int24BE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Int24BE -> Rational
toRational :: Int24BE -> Rational
Real, Enum Int24BE
Real Int24BE
(Real Int24BE, Enum Int24BE) =>
(Int24BE -> Int24BE -> Int24BE)
-> (Int24BE -> Int24BE -> Int24BE)
-> (Int24BE -> Int24BE -> Int24BE)
-> (Int24BE -> Int24BE -> Int24BE)
-> (Int24BE -> Int24BE -> (Int24BE, Int24BE))
-> (Int24BE -> Int24BE -> (Int24BE, Int24BE))
-> (Int24BE -> Integer)
-> Integral Int24BE
Int24BE -> Integer
Int24BE -> Int24BE -> (Int24BE, Int24BE)
Int24BE -> Int24BE -> Int24BE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Int24BE -> Int24BE -> Int24BE
quot :: Int24BE -> Int24BE -> Int24BE
$crem :: Int24BE -> Int24BE -> Int24BE
rem :: Int24BE -> Int24BE -> Int24BE
$cdiv :: Int24BE -> Int24BE -> Int24BE
div :: Int24BE -> Int24BE -> Int24BE
$cmod :: Int24BE -> Int24BE -> Int24BE
mod :: Int24BE -> Int24BE -> Int24BE
$cquotRem :: Int24BE -> Int24BE -> (Int24BE, Int24BE)
quotRem :: Int24BE -> Int24BE -> (Int24BE, Int24BE)
$cdivMod :: Int24BE -> Int24BE -> (Int24BE, Int24BE)
divMod :: Int24BE -> Int24BE -> (Int24BE, Int24BE)
$ctoInteger :: Int24BE -> Integer
toInteger :: Int24BE -> Integer
Integral, Int24BE
Int24BE -> Default Int24BE
forall a. a -> Default a
$cdef :: Int24BE
def :: Int24BE
Default, Eq Int24BE
Int24BE
Eq Int24BE =>
(Int24BE -> Int24BE -> Int24BE)
-> (Int24BE -> Int24BE -> Int24BE)
-> (Int24BE -> Int24BE -> Int24BE)
-> (Int24BE -> Int24BE)
-> (Int24BE -> Int -> Int24BE)
-> (Int24BE -> Int -> Int24BE)
-> Int24BE
-> (Int -> Int24BE)
-> (Int24BE -> Int -> Int24BE)
-> (Int24BE -> Int -> Int24BE)
-> (Int24BE -> Int -> Int24BE)
-> (Int24BE -> Int -> Bool)
-> (Int24BE -> Maybe Int)
-> (Int24BE -> Int)
-> (Int24BE -> Bool)
-> (Int24BE -> Int -> Int24BE)
-> (Int24BE -> Int -> Int24BE)
-> (Int24BE -> Int -> Int24BE)
-> (Int24BE -> Int -> Int24BE)
-> (Int24BE -> Int -> Int24BE)
-> (Int24BE -> Int -> Int24BE)
-> (Int24BE -> Int)
-> Bits Int24BE
Int -> Int24BE
Int24BE -> Bool
Int24BE -> Int
Int24BE -> Maybe Int
Int24BE -> Int24BE
Int24BE -> Int -> Bool
Int24BE -> Int -> Int24BE
Int24BE -> Int24BE -> Int24BE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Int24BE -> Int24BE -> Int24BE
.&. :: Int24BE -> Int24BE -> Int24BE
$c.|. :: Int24BE -> Int24BE -> Int24BE
.|. :: Int24BE -> Int24BE -> Int24BE
$cxor :: Int24BE -> Int24BE -> Int24BE
xor :: Int24BE -> Int24BE -> Int24BE
$ccomplement :: Int24BE -> Int24BE
complement :: Int24BE -> Int24BE
$cshift :: Int24BE -> Int -> Int24BE
shift :: Int24BE -> Int -> Int24BE
$crotate :: Int24BE -> Int -> Int24BE
rotate :: Int24BE -> Int -> Int24BE
$czeroBits :: Int24BE
zeroBits :: Int24BE
$cbit :: Int -> Int24BE
bit :: Int -> Int24BE
$csetBit :: Int24BE -> Int -> Int24BE
setBit :: Int24BE -> Int -> Int24BE
$cclearBit :: Int24BE -> Int -> Int24BE
clearBit :: Int24BE -> Int -> Int24BE
$ccomplementBit :: Int24BE -> Int -> Int24BE
complementBit :: Int24BE -> Int -> Int24BE
$ctestBit :: Int24BE -> Int -> Bool
testBit :: Int24BE -> Int -> Bool
$cbitSizeMaybe :: Int24BE -> Maybe Int
bitSizeMaybe :: Int24BE -> Maybe Int
$cbitSize :: Int24BE -> Int
bitSize :: Int24BE -> Int
$cisSigned :: Int24BE -> Bool
isSigned :: Int24BE -> Bool
$cshiftL :: Int24BE -> Int -> Int24BE
shiftL :: Int24BE -> Int -> Int24BE
$cunsafeShiftL :: Int24BE -> Int -> Int24BE
unsafeShiftL :: Int24BE -> Int -> Int24BE
$cshiftR :: Int24BE -> Int -> Int24BE
shiftR :: Int24BE -> Int -> Int24BE
$cunsafeShiftR :: Int24BE -> Int -> Int24BE
unsafeShiftR :: Int24BE -> Int -> Int24BE
$crotateL :: Int24BE -> Int -> Int24BE
rotateL :: Int24BE -> Int -> Int24BE
$crotateR :: Int24BE -> Int -> Int24BE
rotateR :: Int24BE -> Int -> Int24BE
$cpopCount :: Int24BE -> Int
popCount :: Int24BE -> Int
Bits, Bits Int24BE
Bits Int24BE =>
(Int24BE -> Int)
-> (Int24BE -> Int) -> (Int24BE -> Int) -> FiniteBits Int24BE
Int24BE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Int24BE -> Int
finiteBitSize :: Int24BE -> Int
$ccountLeadingZeros :: Int24BE -> Int
countLeadingZeros :: Int24BE -> Int
$ccountTrailingZeros :: Int24BE -> Int
countTrailingZeros :: Int24BE -> Int
FiniteBits, Int24BE
Int24BE -> Int24BE -> Bounded Int24BE
forall a. a -> a -> Bounded a
$cminBound :: Int24BE
minBound :: Int24BE
$cmaxBound :: Int24BE
maxBound :: Int24BE
Bounded)
  deriving (Addr# -> Int# -> Int24BE
ByteArray# -> Int# -> Int24BE
Proxy Int24BE -> Int#
Int24BE -> Int#
(Proxy Int24BE -> Int#)
-> (Int24BE -> Int#)
-> (Proxy Int24BE -> Int#)
-> (Int24BE -> Int#)
-> (ByteArray# -> Int# -> Int24BE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int24BE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Int24BE -> State# s -> State# s)
-> (Addr# -> Int# -> Int24BE)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, Int24BE #))
-> (forall s. Addr# -> Int# -> Int24BE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Int24BE -> State# s -> State# s)
-> Prim Int24BE
forall s. Addr# -> Int# -> Int# -> Int24BE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Int24BE #)
forall s. Addr# -> Int# -> Int24BE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Int24BE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24BE #)
forall s.
MutableByteArray# s -> Int# -> Int24BE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Int24BE -> Int#
sizeOfType# :: Proxy Int24BE -> Int#
$csizeOf# :: Int24BE -> Int#
sizeOf# :: Int24BE -> Int#
$calignmentOfType# :: Proxy Int24BE -> Int#
alignmentOfType# :: Proxy Int24BE -> Int#
$calignment# :: Int24BE -> Int#
alignment# :: Int24BE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Int24BE
indexByteArray# :: ByteArray# -> Int# -> Int24BE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24BE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24BE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int24BE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int24BE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int24BE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int24BE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Int24BE
indexOffAddr# :: Addr# -> Int# -> Int24BE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int24BE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int24BE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Int24BE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Int24BE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int24BE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int24BE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Int24BE
(ByteArray# -> Int# -> Int24BE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int24BE -> State# s -> State# s)
-> PrimUnaligned Int24BE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24BE #)
forall s.
MutableByteArray# s -> Int# -> Int24BE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Int24BE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Int24BE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24BE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int24BE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int24BE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int24BE -> State# s -> State# s
PrimUnaligned) via (ViaSwapEndian Int24 Int24BE)

newtype Int32BE = Int32BE {Int32BE -> Int32
unInt32BE :: Int32}
  deriving stock (Int -> Int32BE -> ShowS
[Int32BE] -> ShowS
Int32BE -> String
(Int -> Int32BE -> ShowS)
-> (Int32BE -> String) -> ([Int32BE] -> ShowS) -> Show Int32BE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Int32BE -> ShowS
showsPrec :: Int -> Int32BE -> ShowS
$cshow :: Int32BE -> String
show :: Int32BE -> String
$cshowList :: [Int32BE] -> ShowS
showList :: [Int32BE] -> ShowS
Show)
  deriving newtype (Int32BE -> Int32BE -> Bool
(Int32BE -> Int32BE -> Bool)
-> (Int32BE -> Int32BE -> Bool) -> Eq Int32BE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Int32BE -> Int32BE -> Bool
== :: Int32BE -> Int32BE -> Bool
$c/= :: Int32BE -> Int32BE -> Bool
/= :: Int32BE -> Int32BE -> Bool
Eq, Eq Int32BE
Eq Int32BE =>
(Int32BE -> Int32BE -> Ordering)
-> (Int32BE -> Int32BE -> Bool)
-> (Int32BE -> Int32BE -> Bool)
-> (Int32BE -> Int32BE -> Bool)
-> (Int32BE -> Int32BE -> Bool)
-> (Int32BE -> Int32BE -> Int32BE)
-> (Int32BE -> Int32BE -> Int32BE)
-> Ord Int32BE
Int32BE -> Int32BE -> Bool
Int32BE -> Int32BE -> Ordering
Int32BE -> Int32BE -> Int32BE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Int32BE -> Int32BE -> Ordering
compare :: Int32BE -> Int32BE -> Ordering
$c< :: Int32BE -> Int32BE -> Bool
< :: Int32BE -> Int32BE -> Bool
$c<= :: Int32BE -> Int32BE -> Bool
<= :: Int32BE -> Int32BE -> Bool
$c> :: Int32BE -> Int32BE -> Bool
> :: Int32BE -> Int32BE -> Bool
$c>= :: Int32BE -> Int32BE -> Bool
>= :: Int32BE -> Int32BE -> Bool
$cmax :: Int32BE -> Int32BE -> Int32BE
max :: Int32BE -> Int32BE -> Int32BE
$cmin :: Int32BE -> Int32BE -> Int32BE
min :: Int32BE -> Int32BE -> Int32BE
Ord, Int -> Int32BE
Int32BE -> Int
Int32BE -> [Int32BE]
Int32BE -> Int32BE
Int32BE -> Int32BE -> [Int32BE]
Int32BE -> Int32BE -> Int32BE -> [Int32BE]
(Int32BE -> Int32BE)
-> (Int32BE -> Int32BE)
-> (Int -> Int32BE)
-> (Int32BE -> Int)
-> (Int32BE -> [Int32BE])
-> (Int32BE -> Int32BE -> [Int32BE])
-> (Int32BE -> Int32BE -> [Int32BE])
-> (Int32BE -> Int32BE -> Int32BE -> [Int32BE])
-> Enum Int32BE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Int32BE -> Int32BE
succ :: Int32BE -> Int32BE
$cpred :: Int32BE -> Int32BE
pred :: Int32BE -> Int32BE
$ctoEnum :: Int -> Int32BE
toEnum :: Int -> Int32BE
$cfromEnum :: Int32BE -> Int
fromEnum :: Int32BE -> Int
$cenumFrom :: Int32BE -> [Int32BE]
enumFrom :: Int32BE -> [Int32BE]
$cenumFromThen :: Int32BE -> Int32BE -> [Int32BE]
enumFromThen :: Int32BE -> Int32BE -> [Int32BE]
$cenumFromTo :: Int32BE -> Int32BE -> [Int32BE]
enumFromTo :: Int32BE -> Int32BE -> [Int32BE]
$cenumFromThenTo :: Int32BE -> Int32BE -> Int32BE -> [Int32BE]
enumFromThenTo :: Int32BE -> Int32BE -> Int32BE -> [Int32BE]
Enum, Integer -> Int32BE
Int32BE -> Int32BE
Int32BE -> Int32BE -> Int32BE
(Int32BE -> Int32BE -> Int32BE)
-> (Int32BE -> Int32BE -> Int32BE)
-> (Int32BE -> Int32BE -> Int32BE)
-> (Int32BE -> Int32BE)
-> (Int32BE -> Int32BE)
-> (Int32BE -> Int32BE)
-> (Integer -> Int32BE)
-> Num Int32BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Int32BE -> Int32BE -> Int32BE
+ :: Int32BE -> Int32BE -> Int32BE
$c- :: Int32BE -> Int32BE -> Int32BE
- :: Int32BE -> Int32BE -> Int32BE
$c* :: Int32BE -> Int32BE -> Int32BE
* :: Int32BE -> Int32BE -> Int32BE
$cnegate :: Int32BE -> Int32BE
negate :: Int32BE -> Int32BE
$cabs :: Int32BE -> Int32BE
abs :: Int32BE -> Int32BE
$csignum :: Int32BE -> Int32BE
signum :: Int32BE -> Int32BE
$cfromInteger :: Integer -> Int32BE
fromInteger :: Integer -> Int32BE
Num, Num Int32BE
Ord Int32BE
(Num Int32BE, Ord Int32BE) => (Int32BE -> Rational) -> Real Int32BE
Int32BE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Int32BE -> Rational
toRational :: Int32BE -> Rational
Real, Enum Int32BE
Real Int32BE
(Real Int32BE, Enum Int32BE) =>
(Int32BE -> Int32BE -> Int32BE)
-> (Int32BE -> Int32BE -> Int32BE)
-> (Int32BE -> Int32BE -> Int32BE)
-> (Int32BE -> Int32BE -> Int32BE)
-> (Int32BE -> Int32BE -> (Int32BE, Int32BE))
-> (Int32BE -> Int32BE -> (Int32BE, Int32BE))
-> (Int32BE -> Integer)
-> Integral Int32BE
Int32BE -> Integer
Int32BE -> Int32BE -> (Int32BE, Int32BE)
Int32BE -> Int32BE -> Int32BE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Int32BE -> Int32BE -> Int32BE
quot :: Int32BE -> Int32BE -> Int32BE
$crem :: Int32BE -> Int32BE -> Int32BE
rem :: Int32BE -> Int32BE -> Int32BE
$cdiv :: Int32BE -> Int32BE -> Int32BE
div :: Int32BE -> Int32BE -> Int32BE
$cmod :: Int32BE -> Int32BE -> Int32BE
mod :: Int32BE -> Int32BE -> Int32BE
$cquotRem :: Int32BE -> Int32BE -> (Int32BE, Int32BE)
quotRem :: Int32BE -> Int32BE -> (Int32BE, Int32BE)
$cdivMod :: Int32BE -> Int32BE -> (Int32BE, Int32BE)
divMod :: Int32BE -> Int32BE -> (Int32BE, Int32BE)
$ctoInteger :: Int32BE -> Integer
toInteger :: Int32BE -> Integer
Integral, Int32BE
Int32BE -> Default Int32BE
forall a. a -> Default a
$cdef :: Int32BE
def :: Int32BE
Default, Eq Int32BE
Int32BE
Eq Int32BE =>
(Int32BE -> Int32BE -> Int32BE)
-> (Int32BE -> Int32BE -> Int32BE)
-> (Int32BE -> Int32BE -> Int32BE)
-> (Int32BE -> Int32BE)
-> (Int32BE -> Int -> Int32BE)
-> (Int32BE -> Int -> Int32BE)
-> Int32BE
-> (Int -> Int32BE)
-> (Int32BE -> Int -> Int32BE)
-> (Int32BE -> Int -> Int32BE)
-> (Int32BE -> Int -> Int32BE)
-> (Int32BE -> Int -> Bool)
-> (Int32BE -> Maybe Int)
-> (Int32BE -> Int)
-> (Int32BE -> Bool)
-> (Int32BE -> Int -> Int32BE)
-> (Int32BE -> Int -> Int32BE)
-> (Int32BE -> Int -> Int32BE)
-> (Int32BE -> Int -> Int32BE)
-> (Int32BE -> Int -> Int32BE)
-> (Int32BE -> Int -> Int32BE)
-> (Int32BE -> Int)
-> Bits Int32BE
Int -> Int32BE
Int32BE -> Bool
Int32BE -> Int
Int32BE -> Maybe Int
Int32BE -> Int32BE
Int32BE -> Int -> Bool
Int32BE -> Int -> Int32BE
Int32BE -> Int32BE -> Int32BE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Int32BE -> Int32BE -> Int32BE
.&. :: Int32BE -> Int32BE -> Int32BE
$c.|. :: Int32BE -> Int32BE -> Int32BE
.|. :: Int32BE -> Int32BE -> Int32BE
$cxor :: Int32BE -> Int32BE -> Int32BE
xor :: Int32BE -> Int32BE -> Int32BE
$ccomplement :: Int32BE -> Int32BE
complement :: Int32BE -> Int32BE
$cshift :: Int32BE -> Int -> Int32BE
shift :: Int32BE -> Int -> Int32BE
$crotate :: Int32BE -> Int -> Int32BE
rotate :: Int32BE -> Int -> Int32BE
$czeroBits :: Int32BE
zeroBits :: Int32BE
$cbit :: Int -> Int32BE
bit :: Int -> Int32BE
$csetBit :: Int32BE -> Int -> Int32BE
setBit :: Int32BE -> Int -> Int32BE
$cclearBit :: Int32BE -> Int -> Int32BE
clearBit :: Int32BE -> Int -> Int32BE
$ccomplementBit :: Int32BE -> Int -> Int32BE
complementBit :: Int32BE -> Int -> Int32BE
$ctestBit :: Int32BE -> Int -> Bool
testBit :: Int32BE -> Int -> Bool
$cbitSizeMaybe :: Int32BE -> Maybe Int
bitSizeMaybe :: Int32BE -> Maybe Int
$cbitSize :: Int32BE -> Int
bitSize :: Int32BE -> Int
$cisSigned :: Int32BE -> Bool
isSigned :: Int32BE -> Bool
$cshiftL :: Int32BE -> Int -> Int32BE
shiftL :: Int32BE -> Int -> Int32BE
$cunsafeShiftL :: Int32BE -> Int -> Int32BE
unsafeShiftL :: Int32BE -> Int -> Int32BE
$cshiftR :: Int32BE -> Int -> Int32BE
shiftR :: Int32BE -> Int -> Int32BE
$cunsafeShiftR :: Int32BE -> Int -> Int32BE
unsafeShiftR :: Int32BE -> Int -> Int32BE
$crotateL :: Int32BE -> Int -> Int32BE
rotateL :: Int32BE -> Int -> Int32BE
$crotateR :: Int32BE -> Int -> Int32BE
rotateR :: Int32BE -> Int -> Int32BE
$cpopCount :: Int32BE -> Int
popCount :: Int32BE -> Int
Bits, Bits Int32BE
Bits Int32BE =>
(Int32BE -> Int)
-> (Int32BE -> Int) -> (Int32BE -> Int) -> FiniteBits Int32BE
Int32BE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Int32BE -> Int
finiteBitSize :: Int32BE -> Int
$ccountLeadingZeros :: Int32BE -> Int
countLeadingZeros :: Int32BE -> Int
$ccountTrailingZeros :: Int32BE -> Int
countTrailingZeros :: Int32BE -> Int
FiniteBits, Int32BE
Int32BE -> Int32BE -> Bounded Int32BE
forall a. a -> a -> Bounded a
$cminBound :: Int32BE
minBound :: Int32BE
$cmaxBound :: Int32BE
maxBound :: Int32BE
Bounded)
  deriving (Addr# -> Int# -> Int32BE
ByteArray# -> Int# -> Int32BE
Proxy Int32BE -> Int#
Int32BE -> Int#
(Proxy Int32BE -> Int#)
-> (Int32BE -> Int#)
-> (Proxy Int32BE -> Int#)
-> (Int32BE -> Int#)
-> (ByteArray# -> Int# -> Int32BE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int32BE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Int32BE -> State# s -> State# s)
-> (Addr# -> Int# -> Int32BE)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, Int32BE #))
-> (forall s. Addr# -> Int# -> Int32BE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Int32BE -> State# s -> State# s)
-> Prim Int32BE
forall s. Addr# -> Int# -> Int# -> Int32BE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Int32BE #)
forall s. Addr# -> Int# -> Int32BE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Int32BE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32BE #)
forall s.
MutableByteArray# s -> Int# -> Int32BE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Int32BE -> Int#
sizeOfType# :: Proxy Int32BE -> Int#
$csizeOf# :: Int32BE -> Int#
sizeOf# :: Int32BE -> Int#
$calignmentOfType# :: Proxy Int32BE -> Int#
alignmentOfType# :: Proxy Int32BE -> Int#
$calignment# :: Int32BE -> Int#
alignment# :: Int32BE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Int32BE
indexByteArray# :: ByteArray# -> Int# -> Int32BE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32BE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32BE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int32BE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int32BE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int32BE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int32BE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Int32BE
indexOffAddr# :: Addr# -> Int# -> Int32BE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int32BE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int32BE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Int32BE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Int32BE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int32BE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int32BE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Int32BE
(ByteArray# -> Int# -> Int32BE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int32BE -> State# s -> State# s)
-> PrimUnaligned Int32BE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32BE #)
forall s.
MutableByteArray# s -> Int# -> Int32BE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Int32BE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Int32BE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32BE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int32BE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int32BE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int32BE -> State# s -> State# s
PrimUnaligned) via (ViaSwapEndian Int32 Int32BE)

newtype Int64BE = Int64BE {Int64BE -> Int64
unInt64BE :: Int64}
  deriving stock (Int -> Int64BE -> ShowS
[Int64BE] -> ShowS
Int64BE -> String
(Int -> Int64BE -> ShowS)
-> (Int64BE -> String) -> ([Int64BE] -> ShowS) -> Show Int64BE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> Int64BE -> ShowS
showsPrec :: Int -> Int64BE -> ShowS
$cshow :: Int64BE -> String
show :: Int64BE -> String
$cshowList :: [Int64BE] -> ShowS
showList :: [Int64BE] -> ShowS
Show)
  deriving newtype (Int64BE -> Int64BE -> Bool
(Int64BE -> Int64BE -> Bool)
-> (Int64BE -> Int64BE -> Bool) -> Eq Int64BE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Int64BE -> Int64BE -> Bool
== :: Int64BE -> Int64BE -> Bool
$c/= :: Int64BE -> Int64BE -> Bool
/= :: Int64BE -> Int64BE -> Bool
Eq, Eq Int64BE
Eq Int64BE =>
(Int64BE -> Int64BE -> Ordering)
-> (Int64BE -> Int64BE -> Bool)
-> (Int64BE -> Int64BE -> Bool)
-> (Int64BE -> Int64BE -> Bool)
-> (Int64BE -> Int64BE -> Bool)
-> (Int64BE -> Int64BE -> Int64BE)
-> (Int64BE -> Int64BE -> Int64BE)
-> Ord Int64BE
Int64BE -> Int64BE -> Bool
Int64BE -> Int64BE -> Ordering
Int64BE -> Int64BE -> Int64BE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: Int64BE -> Int64BE -> Ordering
compare :: Int64BE -> Int64BE -> Ordering
$c< :: Int64BE -> Int64BE -> Bool
< :: Int64BE -> Int64BE -> Bool
$c<= :: Int64BE -> Int64BE -> Bool
<= :: Int64BE -> Int64BE -> Bool
$c> :: Int64BE -> Int64BE -> Bool
> :: Int64BE -> Int64BE -> Bool
$c>= :: Int64BE -> Int64BE -> Bool
>= :: Int64BE -> Int64BE -> Bool
$cmax :: Int64BE -> Int64BE -> Int64BE
max :: Int64BE -> Int64BE -> Int64BE
$cmin :: Int64BE -> Int64BE -> Int64BE
min :: Int64BE -> Int64BE -> Int64BE
Ord, Int -> Int64BE
Int64BE -> Int
Int64BE -> [Int64BE]
Int64BE -> Int64BE
Int64BE -> Int64BE -> [Int64BE]
Int64BE -> Int64BE -> Int64BE -> [Int64BE]
(Int64BE -> Int64BE)
-> (Int64BE -> Int64BE)
-> (Int -> Int64BE)
-> (Int64BE -> Int)
-> (Int64BE -> [Int64BE])
-> (Int64BE -> Int64BE -> [Int64BE])
-> (Int64BE -> Int64BE -> [Int64BE])
-> (Int64BE -> Int64BE -> Int64BE -> [Int64BE])
-> Enum Int64BE
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: Int64BE -> Int64BE
succ :: Int64BE -> Int64BE
$cpred :: Int64BE -> Int64BE
pred :: Int64BE -> Int64BE
$ctoEnum :: Int -> Int64BE
toEnum :: Int -> Int64BE
$cfromEnum :: Int64BE -> Int
fromEnum :: Int64BE -> Int
$cenumFrom :: Int64BE -> [Int64BE]
enumFrom :: Int64BE -> [Int64BE]
$cenumFromThen :: Int64BE -> Int64BE -> [Int64BE]
enumFromThen :: Int64BE -> Int64BE -> [Int64BE]
$cenumFromTo :: Int64BE -> Int64BE -> [Int64BE]
enumFromTo :: Int64BE -> Int64BE -> [Int64BE]
$cenumFromThenTo :: Int64BE -> Int64BE -> Int64BE -> [Int64BE]
enumFromThenTo :: Int64BE -> Int64BE -> Int64BE -> [Int64BE]
Enum, Integer -> Int64BE
Int64BE -> Int64BE
Int64BE -> Int64BE -> Int64BE
(Int64BE -> Int64BE -> Int64BE)
-> (Int64BE -> Int64BE -> Int64BE)
-> (Int64BE -> Int64BE -> Int64BE)
-> (Int64BE -> Int64BE)
-> (Int64BE -> Int64BE)
-> (Int64BE -> Int64BE)
-> (Integer -> Int64BE)
-> Num Int64BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: Int64BE -> Int64BE -> Int64BE
+ :: Int64BE -> Int64BE -> Int64BE
$c- :: Int64BE -> Int64BE -> Int64BE
- :: Int64BE -> Int64BE -> Int64BE
$c* :: Int64BE -> Int64BE -> Int64BE
* :: Int64BE -> Int64BE -> Int64BE
$cnegate :: Int64BE -> Int64BE
negate :: Int64BE -> Int64BE
$cabs :: Int64BE -> Int64BE
abs :: Int64BE -> Int64BE
$csignum :: Int64BE -> Int64BE
signum :: Int64BE -> Int64BE
$cfromInteger :: Integer -> Int64BE
fromInteger :: Integer -> Int64BE
Num, Num Int64BE
Ord Int64BE
(Num Int64BE, Ord Int64BE) => (Int64BE -> Rational) -> Real Int64BE
Int64BE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: Int64BE -> Rational
toRational :: Int64BE -> Rational
Real, Enum Int64BE
Real Int64BE
(Real Int64BE, Enum Int64BE) =>
(Int64BE -> Int64BE -> Int64BE)
-> (Int64BE -> Int64BE -> Int64BE)
-> (Int64BE -> Int64BE -> Int64BE)
-> (Int64BE -> Int64BE -> Int64BE)
-> (Int64BE -> Int64BE -> (Int64BE, Int64BE))
-> (Int64BE -> Int64BE -> (Int64BE, Int64BE))
-> (Int64BE -> Integer)
-> Integral Int64BE
Int64BE -> Integer
Int64BE -> Int64BE -> (Int64BE, Int64BE)
Int64BE -> Int64BE -> Int64BE
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: Int64BE -> Int64BE -> Int64BE
quot :: Int64BE -> Int64BE -> Int64BE
$crem :: Int64BE -> Int64BE -> Int64BE
rem :: Int64BE -> Int64BE -> Int64BE
$cdiv :: Int64BE -> Int64BE -> Int64BE
div :: Int64BE -> Int64BE -> Int64BE
$cmod :: Int64BE -> Int64BE -> Int64BE
mod :: Int64BE -> Int64BE -> Int64BE
$cquotRem :: Int64BE -> Int64BE -> (Int64BE, Int64BE)
quotRem :: Int64BE -> Int64BE -> (Int64BE, Int64BE)
$cdivMod :: Int64BE -> Int64BE -> (Int64BE, Int64BE)
divMod :: Int64BE -> Int64BE -> (Int64BE, Int64BE)
$ctoInteger :: Int64BE -> Integer
toInteger :: Int64BE -> Integer
Integral, Int64BE
Int64BE -> Default Int64BE
forall a. a -> Default a
$cdef :: Int64BE
def :: Int64BE
Default, Eq Int64BE
Int64BE
Eq Int64BE =>
(Int64BE -> Int64BE -> Int64BE)
-> (Int64BE -> Int64BE -> Int64BE)
-> (Int64BE -> Int64BE -> Int64BE)
-> (Int64BE -> Int64BE)
-> (Int64BE -> Int -> Int64BE)
-> (Int64BE -> Int -> Int64BE)
-> Int64BE
-> (Int -> Int64BE)
-> (Int64BE -> Int -> Int64BE)
-> (Int64BE -> Int -> Int64BE)
-> (Int64BE -> Int -> Int64BE)
-> (Int64BE -> Int -> Bool)
-> (Int64BE -> Maybe Int)
-> (Int64BE -> Int)
-> (Int64BE -> Bool)
-> (Int64BE -> Int -> Int64BE)
-> (Int64BE -> Int -> Int64BE)
-> (Int64BE -> Int -> Int64BE)
-> (Int64BE -> Int -> Int64BE)
-> (Int64BE -> Int -> Int64BE)
-> (Int64BE -> Int -> Int64BE)
-> (Int64BE -> Int)
-> Bits Int64BE
Int -> Int64BE
Int64BE -> Bool
Int64BE -> Int
Int64BE -> Maybe Int
Int64BE -> Int64BE
Int64BE -> Int -> Bool
Int64BE -> Int -> Int64BE
Int64BE -> Int64BE -> Int64BE
forall a.
Eq a =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> a
-> (Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> Bool)
-> (a -> Maybe Int)
-> (a -> Int)
-> (a -> Bool)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int -> a)
-> (a -> Int)
-> Bits a
$c.&. :: Int64BE -> Int64BE -> Int64BE
.&. :: Int64BE -> Int64BE -> Int64BE
$c.|. :: Int64BE -> Int64BE -> Int64BE
.|. :: Int64BE -> Int64BE -> Int64BE
$cxor :: Int64BE -> Int64BE -> Int64BE
xor :: Int64BE -> Int64BE -> Int64BE
$ccomplement :: Int64BE -> Int64BE
complement :: Int64BE -> Int64BE
$cshift :: Int64BE -> Int -> Int64BE
shift :: Int64BE -> Int -> Int64BE
$crotate :: Int64BE -> Int -> Int64BE
rotate :: Int64BE -> Int -> Int64BE
$czeroBits :: Int64BE
zeroBits :: Int64BE
$cbit :: Int -> Int64BE
bit :: Int -> Int64BE
$csetBit :: Int64BE -> Int -> Int64BE
setBit :: Int64BE -> Int -> Int64BE
$cclearBit :: Int64BE -> Int -> Int64BE
clearBit :: Int64BE -> Int -> Int64BE
$ccomplementBit :: Int64BE -> Int -> Int64BE
complementBit :: Int64BE -> Int -> Int64BE
$ctestBit :: Int64BE -> Int -> Bool
testBit :: Int64BE -> Int -> Bool
$cbitSizeMaybe :: Int64BE -> Maybe Int
bitSizeMaybe :: Int64BE -> Maybe Int
$cbitSize :: Int64BE -> Int
bitSize :: Int64BE -> Int
$cisSigned :: Int64BE -> Bool
isSigned :: Int64BE -> Bool
$cshiftL :: Int64BE -> Int -> Int64BE
shiftL :: Int64BE -> Int -> Int64BE
$cunsafeShiftL :: Int64BE -> Int -> Int64BE
unsafeShiftL :: Int64BE -> Int -> Int64BE
$cshiftR :: Int64BE -> Int -> Int64BE
shiftR :: Int64BE -> Int -> Int64BE
$cunsafeShiftR :: Int64BE -> Int -> Int64BE
unsafeShiftR :: Int64BE -> Int -> Int64BE
$crotateL :: Int64BE -> Int -> Int64BE
rotateL :: Int64BE -> Int -> Int64BE
$crotateR :: Int64BE -> Int -> Int64BE
rotateR :: Int64BE -> Int -> Int64BE
$cpopCount :: Int64BE -> Int
popCount :: Int64BE -> Int
Bits, Bits Int64BE
Bits Int64BE =>
(Int64BE -> Int)
-> (Int64BE -> Int) -> (Int64BE -> Int) -> FiniteBits Int64BE
Int64BE -> Int
forall b.
Bits b =>
(b -> Int) -> (b -> Int) -> (b -> Int) -> FiniteBits b
$cfiniteBitSize :: Int64BE -> Int
finiteBitSize :: Int64BE -> Int
$ccountLeadingZeros :: Int64BE -> Int
countLeadingZeros :: Int64BE -> Int
$ccountTrailingZeros :: Int64BE -> Int
countTrailingZeros :: Int64BE -> Int
FiniteBits, Int64BE
Int64BE -> Int64BE -> Bounded Int64BE
forall a. a -> a -> Bounded a
$cminBound :: Int64BE
minBound :: Int64BE
$cmaxBound :: Int64BE
maxBound :: Int64BE
Bounded)
  deriving (Addr# -> Int# -> Int64BE
ByteArray# -> Int# -> Int64BE
Proxy Int64BE -> Int#
Int64BE -> Int#
(Proxy Int64BE -> Int#)
-> (Int64BE -> Int#)
-> (Proxy Int64BE -> Int#)
-> (Int64BE -> Int#)
-> (ByteArray# -> Int# -> Int64BE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int64BE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> Int64BE -> State# s -> State# s)
-> (Addr# -> Int# -> Int64BE)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, Int64BE #))
-> (forall s. Addr# -> Int# -> Int64BE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> Int64BE -> State# s -> State# s)
-> Prim Int64BE
forall s. Addr# -> Int# -> Int# -> Int64BE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, Int64BE #)
forall s. Addr# -> Int# -> Int64BE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> Int64BE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64BE #)
forall s.
MutableByteArray# s -> Int# -> Int64BE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy Int64BE -> Int#
sizeOfType# :: Proxy Int64BE -> Int#
$csizeOf# :: Int64BE -> Int#
sizeOf# :: Int64BE -> Int#
$calignmentOfType# :: Proxy Int64BE -> Int#
alignmentOfType# :: Proxy Int64BE -> Int#
$calignment# :: Int64BE -> Int#
alignment# :: Int64BE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> Int64BE
indexByteArray# :: ByteArray# -> Int# -> Int64BE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64BE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64BE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int64BE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int64BE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int64BE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> Int64BE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> Int64BE
indexOffAddr# :: Addr# -> Int# -> Int64BE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int64BE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, Int64BE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> Int64BE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> Int64BE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int64BE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> Int64BE -> State# s -> State# s
Prim, ByteArray# -> Int# -> Int64BE
(ByteArray# -> Int# -> Int64BE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64BE #))
-> (forall s.
    MutableByteArray# s -> Int# -> Int64BE -> State# s -> State# s)
-> PrimUnaligned Int64BE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64BE #)
forall s.
MutableByteArray# s -> Int# -> Int64BE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> Int64BE
indexUnalignedByteArray# :: ByteArray# -> Int# -> Int64BE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64BE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, Int64BE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int64BE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> Int64BE -> State# s -> State# s
PrimUnaligned) via (ViaSwapEndian Int64 Int64BE)

newtype FloatBE = FloatBE {FloatBE -> Float
unFloatBE :: Float}
  deriving stock (Int -> FloatBE -> ShowS
[FloatBE] -> ShowS
FloatBE -> String
(Int -> FloatBE -> ShowS)
-> (FloatBE -> String) -> ([FloatBE] -> ShowS) -> Show FloatBE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> FloatBE -> ShowS
showsPrec :: Int -> FloatBE -> ShowS
$cshow :: FloatBE -> String
show :: FloatBE -> String
$cshowList :: [FloatBE] -> ShowS
showList :: [FloatBE] -> ShowS
Show)
  deriving newtype (FloatBE -> FloatBE -> Bool
(FloatBE -> FloatBE -> Bool)
-> (FloatBE -> FloatBE -> Bool) -> Eq FloatBE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: FloatBE -> FloatBE -> Bool
== :: FloatBE -> FloatBE -> Bool
$c/= :: FloatBE -> FloatBE -> Bool
/= :: FloatBE -> FloatBE -> Bool
Eq, Eq FloatBE
Eq FloatBE =>
(FloatBE -> FloatBE -> Ordering)
-> (FloatBE -> FloatBE -> Bool)
-> (FloatBE -> FloatBE -> Bool)
-> (FloatBE -> FloatBE -> Bool)
-> (FloatBE -> FloatBE -> Bool)
-> (FloatBE -> FloatBE -> FloatBE)
-> (FloatBE -> FloatBE -> FloatBE)
-> Ord FloatBE
FloatBE -> FloatBE -> Bool
FloatBE -> FloatBE -> Ordering
FloatBE -> FloatBE -> FloatBE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: FloatBE -> FloatBE -> Ordering
compare :: FloatBE -> FloatBE -> Ordering
$c< :: FloatBE -> FloatBE -> Bool
< :: FloatBE -> FloatBE -> Bool
$c<= :: FloatBE -> FloatBE -> Bool
<= :: FloatBE -> FloatBE -> Bool
$c> :: FloatBE -> FloatBE -> Bool
> :: FloatBE -> FloatBE -> Bool
$c>= :: FloatBE -> FloatBE -> Bool
>= :: FloatBE -> FloatBE -> Bool
$cmax :: FloatBE -> FloatBE -> FloatBE
max :: FloatBE -> FloatBE -> FloatBE
$cmin :: FloatBE -> FloatBE -> FloatBE
min :: FloatBE -> FloatBE -> FloatBE
Ord, Integer -> FloatBE
FloatBE -> FloatBE
FloatBE -> FloatBE -> FloatBE
(FloatBE -> FloatBE -> FloatBE)
-> (FloatBE -> FloatBE -> FloatBE)
-> (FloatBE -> FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (Integer -> FloatBE)
-> Num FloatBE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: FloatBE -> FloatBE -> FloatBE
+ :: FloatBE -> FloatBE -> FloatBE
$c- :: FloatBE -> FloatBE -> FloatBE
- :: FloatBE -> FloatBE -> FloatBE
$c* :: FloatBE -> FloatBE -> FloatBE
* :: FloatBE -> FloatBE -> FloatBE
$cnegate :: FloatBE -> FloatBE
negate :: FloatBE -> FloatBE
$cabs :: FloatBE -> FloatBE
abs :: FloatBE -> FloatBE
$csignum :: FloatBE -> FloatBE
signum :: FloatBE -> FloatBE
$cfromInteger :: Integer -> FloatBE
fromInteger :: Integer -> FloatBE
Num, Num FloatBE
Ord FloatBE
(Num FloatBE, Ord FloatBE) => (FloatBE -> Rational) -> Real FloatBE
FloatBE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: FloatBE -> Rational
toRational :: FloatBE -> Rational
Real, Num FloatBE
Num FloatBE =>
(FloatBE -> FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (Rational -> FloatBE)
-> Fractional FloatBE
Rational -> FloatBE
FloatBE -> FloatBE
FloatBE -> FloatBE -> FloatBE
forall a.
Num a =>
(a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
$c/ :: FloatBE -> FloatBE -> FloatBE
/ :: FloatBE -> FloatBE -> FloatBE
$crecip :: FloatBE -> FloatBE
recip :: FloatBE -> FloatBE
$cfromRational :: Rational -> FloatBE
fromRational :: Rational -> FloatBE
Fractional, Fractional FloatBE
FloatBE
Fractional FloatBE =>
FloatBE
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE -> FloatBE)
-> (FloatBE -> FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> (FloatBE -> FloatBE)
-> Floating FloatBE
FloatBE -> FloatBE
FloatBE -> FloatBE -> FloatBE
forall a.
Fractional a =>
a
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> Floating a
$cpi :: FloatBE
pi :: FloatBE
$cexp :: FloatBE -> FloatBE
exp :: FloatBE -> FloatBE
$clog :: FloatBE -> FloatBE
log :: FloatBE -> FloatBE
$csqrt :: FloatBE -> FloatBE
sqrt :: FloatBE -> FloatBE
$c** :: FloatBE -> FloatBE -> FloatBE
** :: FloatBE -> FloatBE -> FloatBE
$clogBase :: FloatBE -> FloatBE -> FloatBE
logBase :: FloatBE -> FloatBE -> FloatBE
$csin :: FloatBE -> FloatBE
sin :: FloatBE -> FloatBE
$ccos :: FloatBE -> FloatBE
cos :: FloatBE -> FloatBE
$ctan :: FloatBE -> FloatBE
tan :: FloatBE -> FloatBE
$casin :: FloatBE -> FloatBE
asin :: FloatBE -> FloatBE
$cacos :: FloatBE -> FloatBE
acos :: FloatBE -> FloatBE
$catan :: FloatBE -> FloatBE
atan :: FloatBE -> FloatBE
$csinh :: FloatBE -> FloatBE
sinh :: FloatBE -> FloatBE
$ccosh :: FloatBE -> FloatBE
cosh :: FloatBE -> FloatBE
$ctanh :: FloatBE -> FloatBE
tanh :: FloatBE -> FloatBE
$casinh :: FloatBE -> FloatBE
asinh :: FloatBE -> FloatBE
$cacosh :: FloatBE -> FloatBE
acosh :: FloatBE -> FloatBE
$catanh :: FloatBE -> FloatBE
atanh :: FloatBE -> FloatBE
$clog1p :: FloatBE -> FloatBE
log1p :: FloatBE -> FloatBE
$cexpm1 :: FloatBE -> FloatBE
expm1 :: FloatBE -> FloatBE
$clog1pexp :: FloatBE -> FloatBE
log1pexp :: FloatBE -> FloatBE
$clog1mexp :: FloatBE -> FloatBE
log1mexp :: FloatBE -> FloatBE
Floating, Fractional FloatBE
Real FloatBE
(Real FloatBE, Fractional FloatBE) =>
(forall b. Integral b => FloatBE -> (b, FloatBE))
-> (forall b. Integral b => FloatBE -> b)
-> (forall b. Integral b => FloatBE -> b)
-> (forall b. Integral b => FloatBE -> b)
-> (forall b. Integral b => FloatBE -> b)
-> RealFrac FloatBE
forall b. Integral b => FloatBE -> b
forall b. Integral b => FloatBE -> (b, FloatBE)
forall a.
(Real a, Fractional a) =>
(forall b. Integral b => a -> (b, a))
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> RealFrac a
$cproperFraction :: forall b. Integral b => FloatBE -> (b, FloatBE)
properFraction :: forall b. Integral b => FloatBE -> (b, FloatBE)
$ctruncate :: forall b. Integral b => FloatBE -> b
truncate :: forall b. Integral b => FloatBE -> b
$cround :: forall b. Integral b => FloatBE -> b
round :: forall b. Integral b => FloatBE -> b
$cceiling :: forall b. Integral b => FloatBE -> b
ceiling :: forall b. Integral b => FloatBE -> b
$cfloor :: forall b. Integral b => FloatBE -> b
floor :: forall b. Integral b => FloatBE -> b
RealFrac, FloatBE
FloatBE -> Default FloatBE
forall a. a -> Default a
$cdef :: FloatBE
def :: FloatBE
Default)
  deriving (Addr# -> Int# -> FloatBE
ByteArray# -> Int# -> FloatBE
Proxy FloatBE -> Int#
FloatBE -> Int#
(Proxy FloatBE -> Int#)
-> (FloatBE -> Int#)
-> (Proxy FloatBE -> Int#)
-> (FloatBE -> Int#)
-> (ByteArray# -> Int# -> FloatBE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatBE #))
-> (forall s.
    MutableByteArray# s -> Int# -> FloatBE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> FloatBE -> State# s -> State# s)
-> (Addr# -> Int# -> FloatBE)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, FloatBE #))
-> (forall s. Addr# -> Int# -> FloatBE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> FloatBE -> State# s -> State# s)
-> Prim FloatBE
forall s. Addr# -> Int# -> Int# -> FloatBE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, FloatBE #)
forall s. Addr# -> Int# -> FloatBE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> FloatBE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatBE #)
forall s.
MutableByteArray# s -> Int# -> FloatBE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy FloatBE -> Int#
sizeOfType# :: Proxy FloatBE -> Int#
$csizeOf# :: FloatBE -> Int#
sizeOf# :: FloatBE -> Int#
$calignmentOfType# :: Proxy FloatBE -> Int#
alignmentOfType# :: Proxy FloatBE -> Int#
$calignment# :: FloatBE -> Int#
alignment# :: FloatBE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> FloatBE
indexByteArray# :: ByteArray# -> Int# -> FloatBE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatBE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatBE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> FloatBE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> FloatBE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> FloatBE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> FloatBE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> FloatBE
indexOffAddr# :: Addr# -> Int# -> FloatBE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, FloatBE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, FloatBE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> FloatBE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> FloatBE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> FloatBE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> FloatBE -> State# s -> State# s
Prim, ByteArray# -> Int# -> FloatBE
(ByteArray# -> Int# -> FloatBE)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatBE #))
-> (forall s.
    MutableByteArray# s -> Int# -> FloatBE -> State# s -> State# s)
-> PrimUnaligned FloatBE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatBE #)
forall s.
MutableByteArray# s -> Int# -> FloatBE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> FloatBE
indexUnalignedByteArray# :: ByteArray# -> Int# -> FloatBE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatBE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, FloatBE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> FloatBE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> FloatBE -> State# s -> State# s
PrimUnaligned) via (ViaSwapEndian Float FloatBE)

newtype DoubleBE = DoubleBE {DoubleBE -> Double
unDoubleBE :: Double}
  deriving stock (Int -> DoubleBE -> ShowS
[DoubleBE] -> ShowS
DoubleBE -> String
(Int -> DoubleBE -> ShowS)
-> (DoubleBE -> String) -> ([DoubleBE] -> ShowS) -> Show DoubleBE
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: Int -> DoubleBE -> ShowS
showsPrec :: Int -> DoubleBE -> ShowS
$cshow :: DoubleBE -> String
show :: DoubleBE -> String
$cshowList :: [DoubleBE] -> ShowS
showList :: [DoubleBE] -> ShowS
Show)
  deriving newtype (DoubleBE -> DoubleBE -> Bool
(DoubleBE -> DoubleBE -> Bool)
-> (DoubleBE -> DoubleBE -> Bool) -> Eq DoubleBE
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: DoubleBE -> DoubleBE -> Bool
== :: DoubleBE -> DoubleBE -> Bool
$c/= :: DoubleBE -> DoubleBE -> Bool
/= :: DoubleBE -> DoubleBE -> Bool
Eq, Eq DoubleBE
Eq DoubleBE =>
(DoubleBE -> DoubleBE -> Ordering)
-> (DoubleBE -> DoubleBE -> Bool)
-> (DoubleBE -> DoubleBE -> Bool)
-> (DoubleBE -> DoubleBE -> Bool)
-> (DoubleBE -> DoubleBE -> Bool)
-> (DoubleBE -> DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE -> DoubleBE)
-> Ord DoubleBE
DoubleBE -> DoubleBE -> Bool
DoubleBE -> DoubleBE -> Ordering
DoubleBE -> DoubleBE -> DoubleBE
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
$ccompare :: DoubleBE -> DoubleBE -> Ordering
compare :: DoubleBE -> DoubleBE -> Ordering
$c< :: DoubleBE -> DoubleBE -> Bool
< :: DoubleBE -> DoubleBE -> Bool
$c<= :: DoubleBE -> DoubleBE -> Bool
<= :: DoubleBE -> DoubleBE -> Bool
$c> :: DoubleBE -> DoubleBE -> Bool
> :: DoubleBE -> DoubleBE -> Bool
$c>= :: DoubleBE -> DoubleBE -> Bool
>= :: DoubleBE -> DoubleBE -> Bool
$cmax :: DoubleBE -> DoubleBE -> DoubleBE
max :: DoubleBE -> DoubleBE -> DoubleBE
$cmin :: DoubleBE -> DoubleBE -> DoubleBE
min :: DoubleBE -> DoubleBE -> DoubleBE
Ord, Integer -> DoubleBE
DoubleBE -> DoubleBE
DoubleBE -> DoubleBE -> DoubleBE
(DoubleBE -> DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (Integer -> DoubleBE)
-> Num DoubleBE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: DoubleBE -> DoubleBE -> DoubleBE
+ :: DoubleBE -> DoubleBE -> DoubleBE
$c- :: DoubleBE -> DoubleBE -> DoubleBE
- :: DoubleBE -> DoubleBE -> DoubleBE
$c* :: DoubleBE -> DoubleBE -> DoubleBE
* :: DoubleBE -> DoubleBE -> DoubleBE
$cnegate :: DoubleBE -> DoubleBE
negate :: DoubleBE -> DoubleBE
$cabs :: DoubleBE -> DoubleBE
abs :: DoubleBE -> DoubleBE
$csignum :: DoubleBE -> DoubleBE
signum :: DoubleBE -> DoubleBE
$cfromInteger :: Integer -> DoubleBE
fromInteger :: Integer -> DoubleBE
Num, Num DoubleBE
Ord DoubleBE
(Num DoubleBE, Ord DoubleBE) =>
(DoubleBE -> Rational) -> Real DoubleBE
DoubleBE -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
$ctoRational :: DoubleBE -> Rational
toRational :: DoubleBE -> Rational
Real, Num DoubleBE
Num DoubleBE =>
(DoubleBE -> DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (Rational -> DoubleBE)
-> Fractional DoubleBE
Rational -> DoubleBE
DoubleBE -> DoubleBE
DoubleBE -> DoubleBE -> DoubleBE
forall a.
Num a =>
(a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
$c/ :: DoubleBE -> DoubleBE -> DoubleBE
/ :: DoubleBE -> DoubleBE -> DoubleBE
$crecip :: DoubleBE -> DoubleBE
recip :: DoubleBE -> DoubleBE
$cfromRational :: Rational -> DoubleBE
fromRational :: Rational -> DoubleBE
Fractional, Fractional DoubleBE
DoubleBE
Fractional DoubleBE =>
DoubleBE
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> (DoubleBE -> DoubleBE)
-> Floating DoubleBE
DoubleBE -> DoubleBE
DoubleBE -> DoubleBE -> DoubleBE
forall a.
Fractional a =>
a
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> Floating a
$cpi :: DoubleBE
pi :: DoubleBE
$cexp :: DoubleBE -> DoubleBE
exp :: DoubleBE -> DoubleBE
$clog :: DoubleBE -> DoubleBE
log :: DoubleBE -> DoubleBE
$csqrt :: DoubleBE -> DoubleBE
sqrt :: DoubleBE -> DoubleBE
$c** :: DoubleBE -> DoubleBE -> DoubleBE
** :: DoubleBE -> DoubleBE -> DoubleBE
$clogBase :: DoubleBE -> DoubleBE -> DoubleBE
logBase :: DoubleBE -> DoubleBE -> DoubleBE
$csin :: DoubleBE -> DoubleBE
sin :: DoubleBE -> DoubleBE
$ccos :: DoubleBE -> DoubleBE
cos :: DoubleBE -> DoubleBE
$ctan :: DoubleBE -> DoubleBE
tan :: DoubleBE -> DoubleBE
$casin :: DoubleBE -> DoubleBE
asin :: DoubleBE -> DoubleBE
$cacos :: DoubleBE -> DoubleBE
acos :: DoubleBE -> DoubleBE
$catan :: DoubleBE -> DoubleBE
atan :: DoubleBE -> DoubleBE
$csinh :: DoubleBE -> DoubleBE
sinh :: DoubleBE -> DoubleBE
$ccosh :: DoubleBE -> DoubleBE
cosh :: DoubleBE -> DoubleBE
$ctanh :: DoubleBE -> DoubleBE
tanh :: DoubleBE -> DoubleBE
$casinh :: DoubleBE -> DoubleBE
asinh :: DoubleBE -> DoubleBE
$cacosh :: DoubleBE -> DoubleBE
acosh :: DoubleBE -> DoubleBE
$catanh :: DoubleBE -> DoubleBE
atanh :: DoubleBE -> DoubleBE
$clog1p :: DoubleBE -> DoubleBE
log1p :: DoubleBE -> DoubleBE
$cexpm1 :: DoubleBE -> DoubleBE
expm1 :: DoubleBE -> DoubleBE
$clog1pexp :: DoubleBE -> DoubleBE
log1pexp :: DoubleBE -> DoubleBE
$clog1mexp :: DoubleBE -> DoubleBE
log1mexp :: DoubleBE -> DoubleBE
Floating, Fractional DoubleBE
Real DoubleBE
(Real DoubleBE, Fractional DoubleBE) =>
(forall b. Integral b => DoubleBE -> (b, DoubleBE))
-> (forall b. Integral b => DoubleBE -> b)
-> (forall b. Integral b => DoubleBE -> b)
-> (forall b. Integral b => DoubleBE -> b)
-> (forall b. Integral b => DoubleBE -> b)
-> RealFrac DoubleBE
forall b. Integral b => DoubleBE -> b
forall b. Integral b => DoubleBE -> (b, DoubleBE)
forall a.
(Real a, Fractional a) =>
(forall b. Integral b => a -> (b, a))
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> (forall b. Integral b => a -> b)
-> RealFrac a
$cproperFraction :: forall b. Integral b => DoubleBE -> (b, DoubleBE)
properFraction :: forall b. Integral b => DoubleBE -> (b, DoubleBE)
$ctruncate :: forall b. Integral b => DoubleBE -> b
truncate :: forall b. Integral b => DoubleBE -> b
$cround :: forall b. Integral b => DoubleBE -> b
round :: forall b. Integral b => DoubleBE -> b
$cceiling :: forall b. Integral b => DoubleBE -> b
ceiling :: forall b. Integral b => DoubleBE -> b
$cfloor :: forall b. Integral b => DoubleBE -> b
floor :: forall b. Integral b => DoubleBE -> b
RealFrac, DoubleBE
DoubleBE -> Default DoubleBE
forall a. a -> Default a
$cdef :: DoubleBE
def :: DoubleBE
Default)
  deriving (Addr# -> Int# -> DoubleBE
ByteArray# -> Int# -> DoubleBE
Proxy DoubleBE -> Int#
DoubleBE -> Int#
(Proxy DoubleBE -> Int#)
-> (DoubleBE -> Int#)
-> (Proxy DoubleBE -> Int#)
-> (DoubleBE -> Int#)
-> (ByteArray# -> Int# -> DoubleBE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, DoubleBE #))
-> (forall s.
    MutableByteArray# s -> Int# -> DoubleBE -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s
    -> Int# -> Int# -> DoubleBE -> State# s -> State# s)
-> (Addr# -> Int# -> DoubleBE)
-> (forall s.
    Addr# -> Int# -> State# s -> (# State# s, DoubleBE #))
-> (forall s. Addr# -> Int# -> DoubleBE -> State# s -> State# s)
-> (forall s.
    Addr# -> Int# -> Int# -> DoubleBE -> State# s -> State# s)
-> Prim DoubleBE
forall s. Addr# -> Int# -> Int# -> DoubleBE -> State# s -> State# s
forall s. Addr# -> Int# -> State# s -> (# State# s, DoubleBE #)
forall s. Addr# -> Int# -> DoubleBE -> State# s -> State# s
forall s.
MutableByteArray# s
-> Int# -> Int# -> DoubleBE -> State# s -> State# s
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleBE #)
forall s.
MutableByteArray# s -> Int# -> DoubleBE -> State# s -> State# s
forall a.
(Proxy a -> Int#)
-> (a -> Int#)
-> (Proxy a -> Int#)
-> (a -> Int#)
-> (ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> (forall s.
    MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s)
-> (Addr# -> Int# -> a)
-> (forall s. Addr# -> Int# -> State# s -> (# State# s, a #))
-> (forall s. Addr# -> Int# -> a -> State# s -> State# s)
-> (forall s. Addr# -> Int# -> Int# -> a -> State# s -> State# s)
-> Prim a
$csizeOfType# :: Proxy DoubleBE -> Int#
sizeOfType# :: Proxy DoubleBE -> Int#
$csizeOf# :: DoubleBE -> Int#
sizeOf# :: DoubleBE -> Int#
$calignmentOfType# :: Proxy DoubleBE -> Int#
alignmentOfType# :: Proxy DoubleBE -> Int#
$calignment# :: DoubleBE -> Int#
alignment# :: DoubleBE -> Int#
$cindexByteArray# :: ByteArray# -> Int# -> DoubleBE
indexByteArray# :: ByteArray# -> Int# -> DoubleBE
$creadByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleBE #)
readByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleBE #)
$cwriteByteArray# :: forall s.
MutableByteArray# s -> Int# -> DoubleBE -> State# s -> State# s
writeByteArray# :: forall s.
MutableByteArray# s -> Int# -> DoubleBE -> State# s -> State# s
$csetByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> DoubleBE -> State# s -> State# s
setByteArray# :: forall s.
MutableByteArray# s
-> Int# -> Int# -> DoubleBE -> State# s -> State# s
$cindexOffAddr# :: Addr# -> Int# -> DoubleBE
indexOffAddr# :: Addr# -> Int# -> DoubleBE
$creadOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, DoubleBE #)
readOffAddr# :: forall s. Addr# -> Int# -> State# s -> (# State# s, DoubleBE #)
$cwriteOffAddr# :: forall s. Addr# -> Int# -> DoubleBE -> State# s -> State# s
writeOffAddr# :: forall s. Addr# -> Int# -> DoubleBE -> State# s -> State# s
$csetOffAddr# :: forall s. Addr# -> Int# -> Int# -> DoubleBE -> State# s -> State# s
setOffAddr# :: forall s. Addr# -> Int# -> Int# -> DoubleBE -> State# s -> State# s
Prim, ByteArray# -> Int# -> DoubleBE
(ByteArray# -> Int# -> DoubleBE)
-> (forall s.
    MutableByteArray# s
    -> Int# -> State# s -> (# State# s, DoubleBE #))
-> (forall s.
    MutableByteArray# s -> Int# -> DoubleBE -> State# s -> State# s)
-> PrimUnaligned DoubleBE
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleBE #)
forall s.
MutableByteArray# s -> Int# -> DoubleBE -> State# s -> State# s
forall a.
(ByteArray# -> Int# -> a)
-> (forall s.
    MutableByteArray# s -> Int# -> State# s -> (# State# s, a #))
-> (forall s.
    MutableByteArray# s -> Int# -> a -> State# s -> State# s)
-> PrimUnaligned a
$cindexUnalignedByteArray# :: ByteArray# -> Int# -> DoubleBE
indexUnalignedByteArray# :: ByteArray# -> Int# -> DoubleBE
$creadUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleBE #)
readUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, DoubleBE #)
$cwriteUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> DoubleBE -> State# s -> State# s
writeUnalignedByteArray# :: forall s.
MutableByteArray# s -> Int# -> DoubleBE -> State# s -> State# s
PrimUnaligned) via (ViaSwapEndian Double DoubleBE)

byteSwap24 :: Word24 -> Word24
byteSwap24 :: Word24 -> Word24
byteSwap24 = Word32 -> Word24
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Word24) -> (Word24 -> Word32) -> Word24 -> Word24
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word32 -> Int -> Word32) -> Int -> Word32 -> Word32
forall a b c. (a -> b -> c) -> b -> a -> c
flip Word32 -> Int -> Word32
forall a. Bits a => a -> Int -> a
shiftR Int
8 (Word32 -> Word32) -> (Word24 -> Word32) -> Word24 -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Word32
byteSwap32 (Word32 -> Word32) -> (Word24 -> Word32) -> Word24 -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word24 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE byteSwap24 #-}

class (Coercible le x, Coercible be x) => SwapEndian x le be | x -> le be, le -> x be, be -> x le where
  swapEndian :: x -> x

instance SwapEndian Word8 Word8 Word8 where
  swapEndian :: Word8 -> Word8
swapEndian = Word8 -> Word8
forall a. a -> a
id

instance SwapEndian Int8 Int8 Int8 where
  swapEndian :: Int8 -> Int8
swapEndian = Int8 -> Int8
forall a. a -> a
id

instance SwapEndian Word16 Word16LE Word16BE where
  swapEndian :: Word16 -> Word16
swapEndian = Word16 -> Word16
byteSwap16

instance SwapEndian Int16 Int16LE Int16BE where
  swapEndian :: Int16 -> Int16
swapEndian = Word16 -> Int16
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word16 -> Int16) -> (Int16 -> Word16) -> Int16 -> Int16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16 -> Word16
byteSwap16 (Word16 -> Word16) -> (Int16 -> Word16) -> Int16 -> Word16
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16 -> Word16
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance SwapEndian Word24 Word24LE Word24BE where
  swapEndian :: Word24 -> Word24
swapEndian = Word24 -> Word24
byteSwap24

instance SwapEndian Int24 Int24LE Int24BE where
  swapEndian :: Int24 -> Int24
swapEndian = Word24 -> Int24
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word24 -> Int24) -> (Int24 -> Word24) -> Int24 -> Int24
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word24 -> Word24
byteSwap24 (Word24 -> Word24) -> (Int24 -> Word24) -> Int24 -> Word24
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int24 -> Word24
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance SwapEndian Word32 Word32LE Word32BE where
  swapEndian :: Word32 -> Word32
swapEndian = Word32 -> Word32
byteSwap32

instance SwapEndian Int32 Int32LE Int32BE where
  swapEndian :: Int32 -> Int32
swapEndian = Word32 -> Int32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word32 -> Int32) -> (Int32 -> Word32) -> Int32 -> Int32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Word32
byteSwap32 (Word32 -> Word32) -> (Int32 -> Word32) -> Int32 -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32 -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance SwapEndian Word64 Word64LE Word64BE where
  swapEndian :: Word64 -> Word64
swapEndian = Word64 -> Word64
byteSwap64

instance SwapEndian Int64 Int64LE Int64BE where
  swapEndian :: Int64 -> Int64
swapEndian = Word64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Word64 -> Int64) -> (Int64 -> Word64) -> Int64 -> Int64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Word64
byteSwap64 (Word64 -> Word64) -> (Int64 -> Word64) -> Int64 -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64 -> Word64
forall a b. (Integral a, Num b) => a -> b
fromIntegral

instance SwapEndian Float FloatLE FloatBE where
  swapEndian :: Float -> Float
swapEndian = Word32 -> Float
castWord32ToFloat (Word32 -> Float) -> (Float -> Word32) -> Float -> Float
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32 -> Word32
byteSwap32 (Word32 -> Word32) -> (Float -> Word32) -> Float -> Word32
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Float -> Word32
castFloatToWord32

instance SwapEndian Double DoubleLE DoubleBE where
  swapEndian :: Double -> Double
swapEndian = Word64 -> Double
castWord64ToDouble (Word64 -> Double) -> (Double -> Word64) -> Double -> Double
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64 -> Word64
byteSwap64 (Word64 -> Word64) -> (Double -> Word64) -> Double -> Word64
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Double -> Word64
castDoubleToWord64

newtype ViaSwapEndian x be = ViaSwapEndian {forall x be. ViaSwapEndian x be -> be
unViaSwapEndian :: be}

instance (Prim x, SwapEndian x le be) => Prim (ViaSwapEndian x be) where
  sizeOfType# :: Proxy (ViaSwapEndian x be) -> Int#
sizeOfType# Proxy (ViaSwapEndian x be)
_ = Proxy x -> Int#
forall a. Prim a => Proxy a -> Int#
sizeOfType# (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @x)
  sizeOf# :: ViaSwapEndian x be -> Int#
sizeOf# ViaSwapEndian x be
_ = x -> Int#
forall a. Prim a => a -> Int#
sizeOf# (x
forall a. HasCallStack => a
undefined :: x)
  alignmentOfType# :: Proxy (ViaSwapEndian x be) -> Int#
alignmentOfType# Proxy (ViaSwapEndian x be)
_ = Proxy x -> Int#
forall a. Prim a => Proxy a -> Int#
alignmentOfType# (forall t. Proxy t
forall {k} (t :: k). Proxy t
Proxy @x)
  alignment# :: ViaSwapEndian x be -> Int#
alignment# ViaSwapEndian x be
_ = x -> Int#
forall a. Prim a => a -> Int#
alignment# (x
forall a. HasCallStack => a
undefined :: x)
  indexByteArray# :: ByteArray# -> Int# -> ViaSwapEndian x be
indexByteArray# ByteArray#
ba Int#
i = be -> ViaSwapEndian x be
forall x be. be -> ViaSwapEndian x be
ViaSwapEndian (forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @x @be (x -> x
forall x le be. SwapEndian x le be => x -> x
swapEndian (ByteArray# -> Int# -> x
forall a. Prim a => ByteArray# -> Int# -> a
indexByteArray# ByteArray#
ba Int#
i)))
  readByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, ViaSwapEndian x be #)
readByteArray# MutableByteArray# s
ba Int#
i State# s
s =
    let !(# State# s
s', x
x #) = MutableByteArray# s -> Int# -> State# s -> (# State# s, x #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, x #)
forall a s.
Prim a =>
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
readByteArray# MutableByteArray# s
ba Int#
i State# s
s
    in  (# State# s
s', be -> ViaSwapEndian x be
forall x be. be -> ViaSwapEndian x be
ViaSwapEndian (forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @x @be (x -> x
forall x le be. SwapEndian x le be => x -> x
swapEndian x
x)) #)
  writeByteArray# :: forall s.
MutableByteArray# s
-> Int# -> ViaSwapEndian x be -> State# s -> State# s
writeByteArray# MutableByteArray# s
ba Int#
i (ViaSwapEndian be
be) = MutableByteArray# s -> Int# -> x -> State# s -> State# s
forall s. MutableByteArray# s -> Int# -> x -> State# s -> State# s
forall a s.
Prim a =>
MutableByteArray# s -> Int# -> a -> State# s -> State# s
writeByteArray# MutableByteArray# s
ba Int#
i (x -> x
forall x le be. SwapEndian x le be => x -> x
swapEndian (forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @be @x be
be))
  indexOffAddr# :: Addr# -> Int# -> ViaSwapEndian x be
indexOffAddr# Addr#
addr Int#
i = be -> ViaSwapEndian x be
forall x be. be -> ViaSwapEndian x be
ViaSwapEndian (forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @x @be (x -> x
forall x le be. SwapEndian x le be => x -> x
swapEndian (Addr# -> Int# -> x
forall a. Prim a => Addr# -> Int# -> a
indexOffAddr# Addr#
addr Int#
i)))
  readOffAddr# :: forall s.
Addr# -> Int# -> State# s -> (# State# s, ViaSwapEndian x be #)
readOffAddr# Addr#
addr Int#
i State# s
s =
    let !(# State# s
s', x
x #) = Addr# -> Int# -> State# s -> (# State# s, x #)
forall s. Addr# -> Int# -> State# s -> (# State# s, x #)
forall a s.
Prim a =>
Addr# -> Int# -> State# s -> (# State# s, a #)
readOffAddr# Addr#
addr Int#
i State# s
s
    in  (# State# s
s', be -> ViaSwapEndian x be
forall x be. be -> ViaSwapEndian x be
ViaSwapEndian (forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @x @be (x -> x
forall x le be. SwapEndian x le be => x -> x
swapEndian x
x)) #)
  writeOffAddr# :: forall s.
Addr# -> Int# -> ViaSwapEndian x be -> State# s -> State# s
writeOffAddr# Addr#
addr Int#
i (ViaSwapEndian be
be) =
    Addr# -> Int# -> x -> State# s -> State# s
forall s. Addr# -> Int# -> x -> State# s -> State# s
forall a s. Prim a => Addr# -> Int# -> a -> State# s -> State# s
writeOffAddr# Addr#
addr Int#
i (x -> x
forall x le be. SwapEndian x le be => x -> x
swapEndian (forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @be @x be
be))

instance (PrimUnaligned x, SwapEndian x le be) => PrimUnaligned (ViaSwapEndian x be) where
  indexUnalignedByteArray# :: ByteArray# -> Int# -> ViaSwapEndian x be
indexUnalignedByteArray# ByteArray#
ba Int#
i = be -> ViaSwapEndian x be
forall x be. be -> ViaSwapEndian x be
ViaSwapEndian (forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @x @be (x -> x
forall x le be. SwapEndian x le be => x -> x
swapEndian (ByteArray# -> Int# -> x
forall a. PrimUnaligned a => ByteArray# -> Int# -> a
indexUnalignedByteArray# ByteArray#
ba Int#
i)))
  readUnalignedByteArray# :: forall s.
MutableByteArray# s
-> Int# -> State# s -> (# State# s, ViaSwapEndian x be #)
readUnalignedByteArray# MutableByteArray# s
ba Int#
i State# s
s =
    let !(# State# s
s', x
x #) = MutableByteArray# s -> Int# -> State# s -> (# State# s, x #)
forall s.
MutableByteArray# s -> Int# -> State# s -> (# State# s, x #)
forall a s.
PrimUnaligned a =>
MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
readUnalignedByteArray# MutableByteArray# s
ba Int#
i State# s
s
    in  (# State# s
s', be -> ViaSwapEndian x be
forall x be. be -> ViaSwapEndian x be
ViaSwapEndian (forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @x @be (x -> x
forall x le be. SwapEndian x le be => x -> x
swapEndian x
x)) #)
  writeUnalignedByteArray# :: forall s.
MutableByteArray# s
-> Int# -> ViaSwapEndian x be -> State# s -> State# s
writeUnalignedByteArray# MutableByteArray# s
ba Int#
i (ViaSwapEndian be
be) = MutableByteArray# s -> Int# -> x -> State# s -> State# s
forall s. MutableByteArray# s -> Int# -> x -> State# s -> State# s
forall a s.
PrimUnaligned a =>
MutableByteArray# s -> Int# -> a -> State# s -> State# s
writeUnalignedByteArray# MutableByteArray# s
ba Int#
i (x -> x
forall x le be. SwapEndian x le be => x -> x
swapEndian (forall a b. Coercible a b => a -> b
forall a b. Coercible a b => a -> b
coerce @be @x be
be))