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

-- | Derived instances rely on the host system being little-endian.
-- If it's not, well... some CPP is in order.
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.Internal (EndianPair (..), swapEndian)
import Data.Bits (Bits)
import Data.Default (Default (..))
import Data.Int (Int16, Int32, Int64)
import Data.ShortWord (Int24, Word24)
import Data.Word (Word16, Word32, Word64)

newtype Word16LE = Word16LE {Word16LE -> Word16
unWord16LE :: Word16}
  deriving stock (Int -> Word16LE -> ShowS
[Word16LE] -> ShowS
Word16LE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Word16LE] -> ShowS
$cshowList :: [Word16LE] -> ShowS
show :: Word16LE -> String
$cshow :: Word16LE -> String
showsPrec :: Int -> Word16LE -> ShowS
$cshowsPrec :: Int -> Word16LE -> ShowS
Show)
  deriving newtype (Word16LE -> Word16LE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Word16LE -> Word16LE -> Bool
$c/= :: Word16LE -> Word16LE -> Bool
== :: Word16LE -> Word16LE -> Bool
$c== :: Word16LE -> Word16LE -> Bool
Eq, Eq 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
min :: Word16LE -> Word16LE -> Word16LE
$cmin :: Word16LE -> Word16LE -> Word16LE
max :: Word16LE -> Word16LE -> Word16LE
$cmax :: Word16LE -> Word16LE -> Word16LE
>= :: Word16LE -> Word16LE -> Bool
$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
compare :: Word16LE -> Word16LE -> Ordering
$ccompare :: Word16LE -> Word16LE -> Ordering
Ord, Integer -> Word16LE
Word16LE -> Word16LE
Word16LE -> Word16LE -> Word16LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Word16LE
$cfromInteger :: Integer -> Word16LE
signum :: Word16LE -> Word16LE
$csignum :: Word16LE -> Word16LE
abs :: Word16LE -> Word16LE
$cabs :: Word16LE -> Word16LE
negate :: Word16LE -> Word16LE
$cnegate :: Word16LE -> Word16LE
* :: Word16LE -> Word16LE -> Word16LE
$c* :: Word16LE -> Word16LE -> Word16LE
- :: Word16LE -> Word16LE -> Word16LE
$c- :: Word16LE -> Word16LE -> Word16LE
+ :: Word16LE -> Word16LE -> Word16LE
$c+ :: Word16LE -> Word16LE -> Word16LE
Num, Int -> Word16LE
Word16LE -> Int
Word16LE -> [Word16LE]
Word16LE -> Word16LE
Word16LE -> Word16LE -> [Word16LE]
Word16LE -> Word16LE -> Word16LE -> [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
enumFromThenTo :: Word16LE -> Word16LE -> Word16LE -> [Word16LE]
$cenumFromThenTo :: Word16LE -> Word16LE -> Word16LE -> [Word16LE]
enumFromTo :: Word16LE -> Word16LE -> [Word16LE]
$cenumFromTo :: Word16LE -> Word16LE -> [Word16LE]
enumFromThen :: Word16LE -> Word16LE -> [Word16LE]
$cenumFromThen :: Word16LE -> Word16LE -> [Word16LE]
enumFrom :: Word16LE -> [Word16LE]
$cenumFrom :: Word16LE -> [Word16LE]
fromEnum :: Word16LE -> Int
$cfromEnum :: Word16LE -> Int
toEnum :: Int -> Word16LE
$ctoEnum :: Int -> Word16LE
pred :: Word16LE -> Word16LE
$cpred :: Word16LE -> Word16LE
succ :: Word16LE -> Word16LE
$csucc :: Word16LE -> Word16LE
Enum, Word16LE
forall a. a -> a -> Bounded a
maxBound :: Word16LE
$cmaxBound :: Word16LE
minBound :: Word16LE
$cminBound :: Word16LE
Bounded, Num Word16LE
Ord Word16LE
Word16LE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Word16LE -> Rational
$ctoRational :: Word16LE -> Rational
Real, Enum Word16LE
Real 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
toInteger :: Word16LE -> Integer
$ctoInteger :: Word16LE -> Integer
divMod :: Word16LE -> Word16LE -> (Word16LE, Word16LE)
$cdivMod :: Word16LE -> Word16LE -> (Word16LE, Word16LE)
quotRem :: Word16LE -> Word16LE -> (Word16LE, Word16LE)
$cquotRem :: Word16LE -> Word16LE -> (Word16LE, Word16LE)
mod :: Word16LE -> Word16LE -> Word16LE
$cmod :: Word16LE -> Word16LE -> Word16LE
div :: Word16LE -> Word16LE -> Word16LE
$cdiv :: Word16LE -> Word16LE -> Word16LE
rem :: Word16LE -> Word16LE -> Word16LE
$crem :: Word16LE -> Word16LE -> Word16LE
quot :: Word16LE -> Word16LE -> Word16LE
$cquot :: Word16LE -> Word16LE -> Word16LE
Integral, Eq Word16LE
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
popCount :: Word16LE -> Int
$cpopCount :: Word16LE -> Int
rotateR :: Word16LE -> Int -> Word16LE
$crotateR :: Word16LE -> Int -> Word16LE
rotateL :: Word16LE -> Int -> Word16LE
$crotateL :: Word16LE -> Int -> Word16LE
unsafeShiftR :: Word16LE -> Int -> Word16LE
$cunsafeShiftR :: Word16LE -> Int -> Word16LE
shiftR :: Word16LE -> Int -> Word16LE
$cshiftR :: Word16LE -> Int -> Word16LE
unsafeShiftL :: Word16LE -> Int -> Word16LE
$cunsafeShiftL :: Word16LE -> Int -> Word16LE
shiftL :: Word16LE -> Int -> Word16LE
$cshiftL :: Word16LE -> Int -> Word16LE
isSigned :: Word16LE -> Bool
$cisSigned :: Word16LE -> Bool
bitSize :: Word16LE -> Int
$cbitSize :: Word16LE -> Int
bitSizeMaybe :: Word16LE -> Maybe Int
$cbitSizeMaybe :: Word16LE -> Maybe Int
testBit :: Word16LE -> Int -> Bool
$ctestBit :: Word16LE -> Int -> Bool
complementBit :: Word16LE -> Int -> Word16LE
$ccomplementBit :: Word16LE -> Int -> Word16LE
clearBit :: Word16LE -> Int -> Word16LE
$cclearBit :: Word16LE -> Int -> Word16LE
setBit :: Word16LE -> Int -> Word16LE
$csetBit :: Word16LE -> Int -> Word16LE
bit :: Int -> Word16LE
$cbit :: Int -> Word16LE
zeroBits :: Word16LE
$czeroBits :: Word16LE
rotate :: Word16LE -> Int -> Word16LE
$crotate :: Word16LE -> Int -> Word16LE
shift :: Word16LE -> Int -> Word16LE
$cshift :: Word16LE -> Int -> Word16LE
complement :: Word16LE -> Word16LE
$ccomplement :: Word16LE -> Word16LE
xor :: Word16LE -> Word16LE -> Word16LE
$cxor :: Word16LE -> Word16LE -> Word16LE
.|. :: Word16LE -> Word16LE -> Word16LE
$c.|. :: Word16LE -> Word16LE -> Word16LE
.&. :: Word16LE -> Word16LE -> Word16LE
$c.&. :: Word16LE -> Word16LE -> Word16LE
Bits, Word16LE
forall a. a -> Default a
def :: Word16LE
$cdef :: Word16LE
Default)

newtype Int16LE = Int16LE {Int16LE -> Int16
unInt16LE :: Int16}
  deriving stock (Int -> Int16LE -> ShowS
[Int16LE] -> ShowS
Int16LE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Int16LE] -> ShowS
$cshowList :: [Int16LE] -> ShowS
show :: Int16LE -> String
$cshow :: Int16LE -> String
showsPrec :: Int -> Int16LE -> ShowS
$cshowsPrec :: Int -> Int16LE -> ShowS
Show)
  deriving newtype (Int16LE -> Int16LE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Int16LE -> Int16LE -> Bool
$c/= :: Int16LE -> Int16LE -> Bool
== :: Int16LE -> Int16LE -> Bool
$c== :: Int16LE -> Int16LE -> Bool
Eq, Eq 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
min :: Int16LE -> Int16LE -> Int16LE
$cmin :: Int16LE -> Int16LE -> Int16LE
max :: Int16LE -> Int16LE -> Int16LE
$cmax :: Int16LE -> Int16LE -> Int16LE
>= :: Int16LE -> Int16LE -> Bool
$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
compare :: Int16LE -> Int16LE -> Ordering
$ccompare :: Int16LE -> Int16LE -> Ordering
Ord, Integer -> Int16LE
Int16LE -> Int16LE
Int16LE -> Int16LE -> Int16LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Int16LE
$cfromInteger :: Integer -> Int16LE
signum :: Int16LE -> Int16LE
$csignum :: Int16LE -> Int16LE
abs :: Int16LE -> Int16LE
$cabs :: Int16LE -> Int16LE
negate :: Int16LE -> Int16LE
$cnegate :: Int16LE -> Int16LE
* :: Int16LE -> Int16LE -> Int16LE
$c* :: Int16LE -> Int16LE -> Int16LE
- :: Int16LE -> Int16LE -> Int16LE
$c- :: Int16LE -> Int16LE -> Int16LE
+ :: Int16LE -> Int16LE -> Int16LE
$c+ :: Int16LE -> Int16LE -> Int16LE
Num, Int -> Int16LE
Int16LE -> Int
Int16LE -> [Int16LE]
Int16LE -> Int16LE
Int16LE -> Int16LE -> [Int16LE]
Int16LE -> Int16LE -> Int16LE -> [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
enumFromThenTo :: Int16LE -> Int16LE -> Int16LE -> [Int16LE]
$cenumFromThenTo :: Int16LE -> Int16LE -> Int16LE -> [Int16LE]
enumFromTo :: Int16LE -> Int16LE -> [Int16LE]
$cenumFromTo :: Int16LE -> Int16LE -> [Int16LE]
enumFromThen :: Int16LE -> Int16LE -> [Int16LE]
$cenumFromThen :: Int16LE -> Int16LE -> [Int16LE]
enumFrom :: Int16LE -> [Int16LE]
$cenumFrom :: Int16LE -> [Int16LE]
fromEnum :: Int16LE -> Int
$cfromEnum :: Int16LE -> Int
toEnum :: Int -> Int16LE
$ctoEnum :: Int -> Int16LE
pred :: Int16LE -> Int16LE
$cpred :: Int16LE -> Int16LE
succ :: Int16LE -> Int16LE
$csucc :: Int16LE -> Int16LE
Enum, Int16LE
forall a. a -> a -> Bounded a
maxBound :: Int16LE
$cmaxBound :: Int16LE
minBound :: Int16LE
$cminBound :: Int16LE
Bounded, Num Int16LE
Ord Int16LE
Int16LE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Int16LE -> Rational
$ctoRational :: Int16LE -> Rational
Real, Enum Int16LE
Real 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
toInteger :: Int16LE -> Integer
$ctoInteger :: Int16LE -> Integer
divMod :: Int16LE -> Int16LE -> (Int16LE, Int16LE)
$cdivMod :: Int16LE -> Int16LE -> (Int16LE, Int16LE)
quotRem :: Int16LE -> Int16LE -> (Int16LE, Int16LE)
$cquotRem :: Int16LE -> Int16LE -> (Int16LE, Int16LE)
mod :: Int16LE -> Int16LE -> Int16LE
$cmod :: Int16LE -> Int16LE -> Int16LE
div :: Int16LE -> Int16LE -> Int16LE
$cdiv :: Int16LE -> Int16LE -> Int16LE
rem :: Int16LE -> Int16LE -> Int16LE
$crem :: Int16LE -> Int16LE -> Int16LE
quot :: Int16LE -> Int16LE -> Int16LE
$cquot :: Int16LE -> Int16LE -> Int16LE
Integral, Eq Int16LE
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
popCount :: Int16LE -> Int
$cpopCount :: Int16LE -> Int
rotateR :: Int16LE -> Int -> Int16LE
$crotateR :: Int16LE -> Int -> Int16LE
rotateL :: Int16LE -> Int -> Int16LE
$crotateL :: Int16LE -> Int -> Int16LE
unsafeShiftR :: Int16LE -> Int -> Int16LE
$cunsafeShiftR :: Int16LE -> Int -> Int16LE
shiftR :: Int16LE -> Int -> Int16LE
$cshiftR :: Int16LE -> Int -> Int16LE
unsafeShiftL :: Int16LE -> Int -> Int16LE
$cunsafeShiftL :: Int16LE -> Int -> Int16LE
shiftL :: Int16LE -> Int -> Int16LE
$cshiftL :: Int16LE -> Int -> Int16LE
isSigned :: Int16LE -> Bool
$cisSigned :: Int16LE -> Bool
bitSize :: Int16LE -> Int
$cbitSize :: Int16LE -> Int
bitSizeMaybe :: Int16LE -> Maybe Int
$cbitSizeMaybe :: Int16LE -> Maybe Int
testBit :: Int16LE -> Int -> Bool
$ctestBit :: Int16LE -> Int -> Bool
complementBit :: Int16LE -> Int -> Int16LE
$ccomplementBit :: Int16LE -> Int -> Int16LE
clearBit :: Int16LE -> Int -> Int16LE
$cclearBit :: Int16LE -> Int -> Int16LE
setBit :: Int16LE -> Int -> Int16LE
$csetBit :: Int16LE -> Int -> Int16LE
bit :: Int -> Int16LE
$cbit :: Int -> Int16LE
zeroBits :: Int16LE
$czeroBits :: Int16LE
rotate :: Int16LE -> Int -> Int16LE
$crotate :: Int16LE -> Int -> Int16LE
shift :: Int16LE -> Int -> Int16LE
$cshift :: Int16LE -> Int -> Int16LE
complement :: Int16LE -> Int16LE
$ccomplement :: Int16LE -> Int16LE
xor :: Int16LE -> Int16LE -> Int16LE
$cxor :: Int16LE -> Int16LE -> Int16LE
.|. :: Int16LE -> Int16LE -> Int16LE
$c.|. :: Int16LE -> Int16LE -> Int16LE
.&. :: Int16LE -> Int16LE -> Int16LE
$c.&. :: Int16LE -> Int16LE -> Int16LE
Bits, Int16LE
forall a. a -> Default a
def :: Int16LE
$cdef :: Int16LE
Default)

newtype Word24LE = Word24LE {Word24LE -> Word24
unWord24LE :: Word24}
  deriving stock (Int -> Word24LE -> ShowS
[Word24LE] -> ShowS
Word24LE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Word24LE] -> ShowS
$cshowList :: [Word24LE] -> ShowS
show :: Word24LE -> String
$cshow :: Word24LE -> String
showsPrec :: Int -> Word24LE -> ShowS
$cshowsPrec :: Int -> Word24LE -> ShowS
Show)
  deriving newtype (Word24LE -> Word24LE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Word24LE -> Word24LE -> Bool
$c/= :: Word24LE -> Word24LE -> Bool
== :: Word24LE -> Word24LE -> Bool
$c== :: Word24LE -> Word24LE -> Bool
Eq, Eq 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
min :: Word24LE -> Word24LE -> Word24LE
$cmin :: Word24LE -> Word24LE -> Word24LE
max :: Word24LE -> Word24LE -> Word24LE
$cmax :: Word24LE -> Word24LE -> Word24LE
>= :: Word24LE -> Word24LE -> Bool
$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
compare :: Word24LE -> Word24LE -> Ordering
$ccompare :: Word24LE -> Word24LE -> Ordering
Ord, Integer -> Word24LE
Word24LE -> Word24LE
Word24LE -> Word24LE -> Word24LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Word24LE
$cfromInteger :: Integer -> Word24LE
signum :: Word24LE -> Word24LE
$csignum :: Word24LE -> Word24LE
abs :: Word24LE -> Word24LE
$cabs :: Word24LE -> Word24LE
negate :: Word24LE -> Word24LE
$cnegate :: Word24LE -> Word24LE
* :: Word24LE -> Word24LE -> Word24LE
$c* :: Word24LE -> Word24LE -> Word24LE
- :: Word24LE -> Word24LE -> Word24LE
$c- :: Word24LE -> Word24LE -> Word24LE
+ :: Word24LE -> Word24LE -> Word24LE
$c+ :: Word24LE -> Word24LE -> Word24LE
Num, Int -> Word24LE
Word24LE -> Int
Word24LE -> [Word24LE]
Word24LE -> Word24LE
Word24LE -> Word24LE -> [Word24LE]
Word24LE -> Word24LE -> Word24LE -> [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
enumFromThenTo :: Word24LE -> Word24LE -> Word24LE -> [Word24LE]
$cenumFromThenTo :: Word24LE -> Word24LE -> Word24LE -> [Word24LE]
enumFromTo :: Word24LE -> Word24LE -> [Word24LE]
$cenumFromTo :: Word24LE -> Word24LE -> [Word24LE]
enumFromThen :: Word24LE -> Word24LE -> [Word24LE]
$cenumFromThen :: Word24LE -> Word24LE -> [Word24LE]
enumFrom :: Word24LE -> [Word24LE]
$cenumFrom :: Word24LE -> [Word24LE]
fromEnum :: Word24LE -> Int
$cfromEnum :: Word24LE -> Int
toEnum :: Int -> Word24LE
$ctoEnum :: Int -> Word24LE
pred :: Word24LE -> Word24LE
$cpred :: Word24LE -> Word24LE
succ :: Word24LE -> Word24LE
$csucc :: Word24LE -> Word24LE
Enum, Word24LE
forall a. a -> a -> Bounded a
maxBound :: Word24LE
$cmaxBound :: Word24LE
minBound :: Word24LE
$cminBound :: Word24LE
Bounded, Num Word24LE
Ord Word24LE
Word24LE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Word24LE -> Rational
$ctoRational :: Word24LE -> Rational
Real, Enum Word24LE
Real 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
toInteger :: Word24LE -> Integer
$ctoInteger :: Word24LE -> Integer
divMod :: Word24LE -> Word24LE -> (Word24LE, Word24LE)
$cdivMod :: Word24LE -> Word24LE -> (Word24LE, Word24LE)
quotRem :: Word24LE -> Word24LE -> (Word24LE, Word24LE)
$cquotRem :: Word24LE -> Word24LE -> (Word24LE, Word24LE)
mod :: Word24LE -> Word24LE -> Word24LE
$cmod :: Word24LE -> Word24LE -> Word24LE
div :: Word24LE -> Word24LE -> Word24LE
$cdiv :: Word24LE -> Word24LE -> Word24LE
rem :: Word24LE -> Word24LE -> Word24LE
$crem :: Word24LE -> Word24LE -> Word24LE
quot :: Word24LE -> Word24LE -> Word24LE
$cquot :: Word24LE -> Word24LE -> Word24LE
Integral, Eq Word24LE
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
popCount :: Word24LE -> Int
$cpopCount :: Word24LE -> Int
rotateR :: Word24LE -> Int -> Word24LE
$crotateR :: Word24LE -> Int -> Word24LE
rotateL :: Word24LE -> Int -> Word24LE
$crotateL :: Word24LE -> Int -> Word24LE
unsafeShiftR :: Word24LE -> Int -> Word24LE
$cunsafeShiftR :: Word24LE -> Int -> Word24LE
shiftR :: Word24LE -> Int -> Word24LE
$cshiftR :: Word24LE -> Int -> Word24LE
unsafeShiftL :: Word24LE -> Int -> Word24LE
$cunsafeShiftL :: Word24LE -> Int -> Word24LE
shiftL :: Word24LE -> Int -> Word24LE
$cshiftL :: Word24LE -> Int -> Word24LE
isSigned :: Word24LE -> Bool
$cisSigned :: Word24LE -> Bool
bitSize :: Word24LE -> Int
$cbitSize :: Word24LE -> Int
bitSizeMaybe :: Word24LE -> Maybe Int
$cbitSizeMaybe :: Word24LE -> Maybe Int
testBit :: Word24LE -> Int -> Bool
$ctestBit :: Word24LE -> Int -> Bool
complementBit :: Word24LE -> Int -> Word24LE
$ccomplementBit :: Word24LE -> Int -> Word24LE
clearBit :: Word24LE -> Int -> Word24LE
$cclearBit :: Word24LE -> Int -> Word24LE
setBit :: Word24LE -> Int -> Word24LE
$csetBit :: Word24LE -> Int -> Word24LE
bit :: Int -> Word24LE
$cbit :: Int -> Word24LE
zeroBits :: Word24LE
$czeroBits :: Word24LE
rotate :: Word24LE -> Int -> Word24LE
$crotate :: Word24LE -> Int -> Word24LE
shift :: Word24LE -> Int -> Word24LE
$cshift :: Word24LE -> Int -> Word24LE
complement :: Word24LE -> Word24LE
$ccomplement :: Word24LE -> Word24LE
xor :: Word24LE -> Word24LE -> Word24LE
$cxor :: Word24LE -> Word24LE -> Word24LE
.|. :: Word24LE -> Word24LE -> Word24LE
$c.|. :: Word24LE -> Word24LE -> Word24LE
.&. :: Word24LE -> Word24LE -> Word24LE
$c.&. :: Word24LE -> Word24LE -> Word24LE
Bits)

instance Default Word24LE where
  def :: Word24LE
def = Word24LE
0

newtype Int24LE = Int24LE {Int24LE -> Int24
unInt24LE :: Int24}
  deriving stock (Int -> Int24LE -> ShowS
[Int24LE] -> ShowS
Int24LE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Int24LE] -> ShowS
$cshowList :: [Int24LE] -> ShowS
show :: Int24LE -> String
$cshow :: Int24LE -> String
showsPrec :: Int -> Int24LE -> ShowS
$cshowsPrec :: Int -> Int24LE -> ShowS
Show)
  deriving newtype (Int24LE -> Int24LE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Int24LE -> Int24LE -> Bool
$c/= :: Int24LE -> Int24LE -> Bool
== :: Int24LE -> Int24LE -> Bool
$c== :: Int24LE -> Int24LE -> Bool
Eq, Eq 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
min :: Int24LE -> Int24LE -> Int24LE
$cmin :: Int24LE -> Int24LE -> Int24LE
max :: Int24LE -> Int24LE -> Int24LE
$cmax :: Int24LE -> Int24LE -> Int24LE
>= :: Int24LE -> Int24LE -> Bool
$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
compare :: Int24LE -> Int24LE -> Ordering
$ccompare :: Int24LE -> Int24LE -> Ordering
Ord, Integer -> Int24LE
Int24LE -> Int24LE
Int24LE -> Int24LE -> Int24LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Int24LE
$cfromInteger :: Integer -> Int24LE
signum :: Int24LE -> Int24LE
$csignum :: Int24LE -> Int24LE
abs :: Int24LE -> Int24LE
$cabs :: Int24LE -> Int24LE
negate :: Int24LE -> Int24LE
$cnegate :: Int24LE -> Int24LE
* :: Int24LE -> Int24LE -> Int24LE
$c* :: Int24LE -> Int24LE -> Int24LE
- :: Int24LE -> Int24LE -> Int24LE
$c- :: Int24LE -> Int24LE -> Int24LE
+ :: Int24LE -> Int24LE -> Int24LE
$c+ :: Int24LE -> Int24LE -> Int24LE
Num, Int -> Int24LE
Int24LE -> Int
Int24LE -> [Int24LE]
Int24LE -> Int24LE
Int24LE -> Int24LE -> [Int24LE]
Int24LE -> Int24LE -> Int24LE -> [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
enumFromThenTo :: Int24LE -> Int24LE -> Int24LE -> [Int24LE]
$cenumFromThenTo :: Int24LE -> Int24LE -> Int24LE -> [Int24LE]
enumFromTo :: Int24LE -> Int24LE -> [Int24LE]
$cenumFromTo :: Int24LE -> Int24LE -> [Int24LE]
enumFromThen :: Int24LE -> Int24LE -> [Int24LE]
$cenumFromThen :: Int24LE -> Int24LE -> [Int24LE]
enumFrom :: Int24LE -> [Int24LE]
$cenumFrom :: Int24LE -> [Int24LE]
fromEnum :: Int24LE -> Int
$cfromEnum :: Int24LE -> Int
toEnum :: Int -> Int24LE
$ctoEnum :: Int -> Int24LE
pred :: Int24LE -> Int24LE
$cpred :: Int24LE -> Int24LE
succ :: Int24LE -> Int24LE
$csucc :: Int24LE -> Int24LE
Enum, Int24LE
forall a. a -> a -> Bounded a
maxBound :: Int24LE
$cmaxBound :: Int24LE
minBound :: Int24LE
$cminBound :: Int24LE
Bounded, Num Int24LE
Ord Int24LE
Int24LE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Int24LE -> Rational
$ctoRational :: Int24LE -> Rational
Real, Enum Int24LE
Real 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
toInteger :: Int24LE -> Integer
$ctoInteger :: Int24LE -> Integer
divMod :: Int24LE -> Int24LE -> (Int24LE, Int24LE)
$cdivMod :: Int24LE -> Int24LE -> (Int24LE, Int24LE)
quotRem :: Int24LE -> Int24LE -> (Int24LE, Int24LE)
$cquotRem :: Int24LE -> Int24LE -> (Int24LE, Int24LE)
mod :: Int24LE -> Int24LE -> Int24LE
$cmod :: Int24LE -> Int24LE -> Int24LE
div :: Int24LE -> Int24LE -> Int24LE
$cdiv :: Int24LE -> Int24LE -> Int24LE
rem :: Int24LE -> Int24LE -> Int24LE
$crem :: Int24LE -> Int24LE -> Int24LE
quot :: Int24LE -> Int24LE -> Int24LE
$cquot :: Int24LE -> Int24LE -> Int24LE
Integral, Eq Int24LE
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
popCount :: Int24LE -> Int
$cpopCount :: Int24LE -> Int
rotateR :: Int24LE -> Int -> Int24LE
$crotateR :: Int24LE -> Int -> Int24LE
rotateL :: Int24LE -> Int -> Int24LE
$crotateL :: Int24LE -> Int -> Int24LE
unsafeShiftR :: Int24LE -> Int -> Int24LE
$cunsafeShiftR :: Int24LE -> Int -> Int24LE
shiftR :: Int24LE -> Int -> Int24LE
$cshiftR :: Int24LE -> Int -> Int24LE
unsafeShiftL :: Int24LE -> Int -> Int24LE
$cunsafeShiftL :: Int24LE -> Int -> Int24LE
shiftL :: Int24LE -> Int -> Int24LE
$cshiftL :: Int24LE -> Int -> Int24LE
isSigned :: Int24LE -> Bool
$cisSigned :: Int24LE -> Bool
bitSize :: Int24LE -> Int
$cbitSize :: Int24LE -> Int
bitSizeMaybe :: Int24LE -> Maybe Int
$cbitSizeMaybe :: Int24LE -> Maybe Int
testBit :: Int24LE -> Int -> Bool
$ctestBit :: Int24LE -> Int -> Bool
complementBit :: Int24LE -> Int -> Int24LE
$ccomplementBit :: Int24LE -> Int -> Int24LE
clearBit :: Int24LE -> Int -> Int24LE
$cclearBit :: Int24LE -> Int -> Int24LE
setBit :: Int24LE -> Int -> Int24LE
$csetBit :: Int24LE -> Int -> Int24LE
bit :: Int -> Int24LE
$cbit :: Int -> Int24LE
zeroBits :: Int24LE
$czeroBits :: Int24LE
rotate :: Int24LE -> Int -> Int24LE
$crotate :: Int24LE -> Int -> Int24LE
shift :: Int24LE -> Int -> Int24LE
$cshift :: Int24LE -> Int -> Int24LE
complement :: Int24LE -> Int24LE
$ccomplement :: Int24LE -> Int24LE
xor :: Int24LE -> Int24LE -> Int24LE
$cxor :: Int24LE -> Int24LE -> Int24LE
.|. :: Int24LE -> Int24LE -> Int24LE
$c.|. :: Int24LE -> Int24LE -> Int24LE
.&. :: Int24LE -> Int24LE -> Int24LE
$c.&. :: Int24LE -> Int24LE -> Int24LE
Bits)

instance Default Int24LE where
  def :: Int24LE
def = Int24LE
0

newtype Word32LE = Word32LE {Word32LE -> Word32
unWord32LE :: Word32}
  deriving stock (Int -> Word32LE -> ShowS
[Word32LE] -> ShowS
Word32LE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Word32LE] -> ShowS
$cshowList :: [Word32LE] -> ShowS
show :: Word32LE -> String
$cshow :: Word32LE -> String
showsPrec :: Int -> Word32LE -> ShowS
$cshowsPrec :: Int -> Word32LE -> ShowS
Show)
  deriving newtype (Word32LE -> Word32LE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Word32LE -> Word32LE -> Bool
$c/= :: Word32LE -> Word32LE -> Bool
== :: Word32LE -> Word32LE -> Bool
$c== :: Word32LE -> Word32LE -> Bool
Eq, Eq 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
min :: Word32LE -> Word32LE -> Word32LE
$cmin :: Word32LE -> Word32LE -> Word32LE
max :: Word32LE -> Word32LE -> Word32LE
$cmax :: Word32LE -> Word32LE -> Word32LE
>= :: Word32LE -> Word32LE -> Bool
$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
compare :: Word32LE -> Word32LE -> Ordering
$ccompare :: Word32LE -> Word32LE -> Ordering
Ord, Integer -> Word32LE
Word32LE -> Word32LE
Word32LE -> Word32LE -> Word32LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Word32LE
$cfromInteger :: Integer -> Word32LE
signum :: Word32LE -> Word32LE
$csignum :: Word32LE -> Word32LE
abs :: Word32LE -> Word32LE
$cabs :: Word32LE -> Word32LE
negate :: Word32LE -> Word32LE
$cnegate :: Word32LE -> Word32LE
* :: Word32LE -> Word32LE -> Word32LE
$c* :: Word32LE -> Word32LE -> Word32LE
- :: Word32LE -> Word32LE -> Word32LE
$c- :: Word32LE -> Word32LE -> Word32LE
+ :: Word32LE -> Word32LE -> Word32LE
$c+ :: Word32LE -> Word32LE -> Word32LE
Num, Int -> Word32LE
Word32LE -> Int
Word32LE -> [Word32LE]
Word32LE -> Word32LE
Word32LE -> Word32LE -> [Word32LE]
Word32LE -> Word32LE -> Word32LE -> [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
enumFromThenTo :: Word32LE -> Word32LE -> Word32LE -> [Word32LE]
$cenumFromThenTo :: Word32LE -> Word32LE -> Word32LE -> [Word32LE]
enumFromTo :: Word32LE -> Word32LE -> [Word32LE]
$cenumFromTo :: Word32LE -> Word32LE -> [Word32LE]
enumFromThen :: Word32LE -> Word32LE -> [Word32LE]
$cenumFromThen :: Word32LE -> Word32LE -> [Word32LE]
enumFrom :: Word32LE -> [Word32LE]
$cenumFrom :: Word32LE -> [Word32LE]
fromEnum :: Word32LE -> Int
$cfromEnum :: Word32LE -> Int
toEnum :: Int -> Word32LE
$ctoEnum :: Int -> Word32LE
pred :: Word32LE -> Word32LE
$cpred :: Word32LE -> Word32LE
succ :: Word32LE -> Word32LE
$csucc :: Word32LE -> Word32LE
Enum, Word32LE
forall a. a -> a -> Bounded a
maxBound :: Word32LE
$cmaxBound :: Word32LE
minBound :: Word32LE
$cminBound :: Word32LE
Bounded, Num Word32LE
Ord Word32LE
Word32LE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Word32LE -> Rational
$ctoRational :: Word32LE -> Rational
Real, Enum Word32LE
Real 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
toInteger :: Word32LE -> Integer
$ctoInteger :: Word32LE -> Integer
divMod :: Word32LE -> Word32LE -> (Word32LE, Word32LE)
$cdivMod :: Word32LE -> Word32LE -> (Word32LE, Word32LE)
quotRem :: Word32LE -> Word32LE -> (Word32LE, Word32LE)
$cquotRem :: Word32LE -> Word32LE -> (Word32LE, Word32LE)
mod :: Word32LE -> Word32LE -> Word32LE
$cmod :: Word32LE -> Word32LE -> Word32LE
div :: Word32LE -> Word32LE -> Word32LE
$cdiv :: Word32LE -> Word32LE -> Word32LE
rem :: Word32LE -> Word32LE -> Word32LE
$crem :: Word32LE -> Word32LE -> Word32LE
quot :: Word32LE -> Word32LE -> Word32LE
$cquot :: Word32LE -> Word32LE -> Word32LE
Integral, Eq Word32LE
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
popCount :: Word32LE -> Int
$cpopCount :: Word32LE -> Int
rotateR :: Word32LE -> Int -> Word32LE
$crotateR :: Word32LE -> Int -> Word32LE
rotateL :: Word32LE -> Int -> Word32LE
$crotateL :: Word32LE -> Int -> Word32LE
unsafeShiftR :: Word32LE -> Int -> Word32LE
$cunsafeShiftR :: Word32LE -> Int -> Word32LE
shiftR :: Word32LE -> Int -> Word32LE
$cshiftR :: Word32LE -> Int -> Word32LE
unsafeShiftL :: Word32LE -> Int -> Word32LE
$cunsafeShiftL :: Word32LE -> Int -> Word32LE
shiftL :: Word32LE -> Int -> Word32LE
$cshiftL :: Word32LE -> Int -> Word32LE
isSigned :: Word32LE -> Bool
$cisSigned :: Word32LE -> Bool
bitSize :: Word32LE -> Int
$cbitSize :: Word32LE -> Int
bitSizeMaybe :: Word32LE -> Maybe Int
$cbitSizeMaybe :: Word32LE -> Maybe Int
testBit :: Word32LE -> Int -> Bool
$ctestBit :: Word32LE -> Int -> Bool
complementBit :: Word32LE -> Int -> Word32LE
$ccomplementBit :: Word32LE -> Int -> Word32LE
clearBit :: Word32LE -> Int -> Word32LE
$cclearBit :: Word32LE -> Int -> Word32LE
setBit :: Word32LE -> Int -> Word32LE
$csetBit :: Word32LE -> Int -> Word32LE
bit :: Int -> Word32LE
$cbit :: Int -> Word32LE
zeroBits :: Word32LE
$czeroBits :: Word32LE
rotate :: Word32LE -> Int -> Word32LE
$crotate :: Word32LE -> Int -> Word32LE
shift :: Word32LE -> Int -> Word32LE
$cshift :: Word32LE -> Int -> Word32LE
complement :: Word32LE -> Word32LE
$ccomplement :: Word32LE -> Word32LE
xor :: Word32LE -> Word32LE -> Word32LE
$cxor :: Word32LE -> Word32LE -> Word32LE
.|. :: Word32LE -> Word32LE -> Word32LE
$c.|. :: Word32LE -> Word32LE -> Word32LE
.&. :: Word32LE -> Word32LE -> Word32LE
$c.&. :: Word32LE -> Word32LE -> Word32LE
Bits, Word32LE
forall a. a -> Default a
def :: Word32LE
$cdef :: Word32LE
Default)

newtype Word64LE = Word64LE {Word64LE -> Word64
unWord64LE :: Word64}
  deriving stock (Int -> Word64LE -> ShowS
[Word64LE] -> ShowS
Word64LE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Word64LE] -> ShowS
$cshowList :: [Word64LE] -> ShowS
show :: Word64LE -> String
$cshow :: Word64LE -> String
showsPrec :: Int -> Word64LE -> ShowS
$cshowsPrec :: Int -> Word64LE -> ShowS
Show)
  deriving newtype (Word64LE -> Word64LE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Word64LE -> Word64LE -> Bool
$c/= :: Word64LE -> Word64LE -> Bool
== :: Word64LE -> Word64LE -> Bool
$c== :: Word64LE -> Word64LE -> Bool
Eq, Eq 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
min :: Word64LE -> Word64LE -> Word64LE
$cmin :: Word64LE -> Word64LE -> Word64LE
max :: Word64LE -> Word64LE -> Word64LE
$cmax :: Word64LE -> Word64LE -> Word64LE
>= :: Word64LE -> Word64LE -> Bool
$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
compare :: Word64LE -> Word64LE -> Ordering
$ccompare :: Word64LE -> Word64LE -> Ordering
Ord, Integer -> Word64LE
Word64LE -> Word64LE
Word64LE -> Word64LE -> Word64LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Word64LE
$cfromInteger :: Integer -> Word64LE
signum :: Word64LE -> Word64LE
$csignum :: Word64LE -> Word64LE
abs :: Word64LE -> Word64LE
$cabs :: Word64LE -> Word64LE
negate :: Word64LE -> Word64LE
$cnegate :: Word64LE -> Word64LE
* :: Word64LE -> Word64LE -> Word64LE
$c* :: Word64LE -> Word64LE -> Word64LE
- :: Word64LE -> Word64LE -> Word64LE
$c- :: Word64LE -> Word64LE -> Word64LE
+ :: Word64LE -> Word64LE -> Word64LE
$c+ :: Word64LE -> Word64LE -> Word64LE
Num, Int -> Word64LE
Word64LE -> Int
Word64LE -> [Word64LE]
Word64LE -> Word64LE
Word64LE -> Word64LE -> [Word64LE]
Word64LE -> Word64LE -> Word64LE -> [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
enumFromThenTo :: Word64LE -> Word64LE -> Word64LE -> [Word64LE]
$cenumFromThenTo :: Word64LE -> Word64LE -> Word64LE -> [Word64LE]
enumFromTo :: Word64LE -> Word64LE -> [Word64LE]
$cenumFromTo :: Word64LE -> Word64LE -> [Word64LE]
enumFromThen :: Word64LE -> Word64LE -> [Word64LE]
$cenumFromThen :: Word64LE -> Word64LE -> [Word64LE]
enumFrom :: Word64LE -> [Word64LE]
$cenumFrom :: Word64LE -> [Word64LE]
fromEnum :: Word64LE -> Int
$cfromEnum :: Word64LE -> Int
toEnum :: Int -> Word64LE
$ctoEnum :: Int -> Word64LE
pred :: Word64LE -> Word64LE
$cpred :: Word64LE -> Word64LE
succ :: Word64LE -> Word64LE
$csucc :: Word64LE -> Word64LE
Enum, Word64LE
forall a. a -> a -> Bounded a
maxBound :: Word64LE
$cmaxBound :: Word64LE
minBound :: Word64LE
$cminBound :: Word64LE
Bounded, Num Word64LE
Ord Word64LE
Word64LE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Word64LE -> Rational
$ctoRational :: Word64LE -> Rational
Real, Enum Word64LE
Real 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
toInteger :: Word64LE -> Integer
$ctoInteger :: Word64LE -> Integer
divMod :: Word64LE -> Word64LE -> (Word64LE, Word64LE)
$cdivMod :: Word64LE -> Word64LE -> (Word64LE, Word64LE)
quotRem :: Word64LE -> Word64LE -> (Word64LE, Word64LE)
$cquotRem :: Word64LE -> Word64LE -> (Word64LE, Word64LE)
mod :: Word64LE -> Word64LE -> Word64LE
$cmod :: Word64LE -> Word64LE -> Word64LE
div :: Word64LE -> Word64LE -> Word64LE
$cdiv :: Word64LE -> Word64LE -> Word64LE
rem :: Word64LE -> Word64LE -> Word64LE
$crem :: Word64LE -> Word64LE -> Word64LE
quot :: Word64LE -> Word64LE -> Word64LE
$cquot :: Word64LE -> Word64LE -> Word64LE
Integral, Eq Word64LE
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
popCount :: Word64LE -> Int
$cpopCount :: Word64LE -> Int
rotateR :: Word64LE -> Int -> Word64LE
$crotateR :: Word64LE -> Int -> Word64LE
rotateL :: Word64LE -> Int -> Word64LE
$crotateL :: Word64LE -> Int -> Word64LE
unsafeShiftR :: Word64LE -> Int -> Word64LE
$cunsafeShiftR :: Word64LE -> Int -> Word64LE
shiftR :: Word64LE -> Int -> Word64LE
$cshiftR :: Word64LE -> Int -> Word64LE
unsafeShiftL :: Word64LE -> Int -> Word64LE
$cunsafeShiftL :: Word64LE -> Int -> Word64LE
shiftL :: Word64LE -> Int -> Word64LE
$cshiftL :: Word64LE -> Int -> Word64LE
isSigned :: Word64LE -> Bool
$cisSigned :: Word64LE -> Bool
bitSize :: Word64LE -> Int
$cbitSize :: Word64LE -> Int
bitSizeMaybe :: Word64LE -> Maybe Int
$cbitSizeMaybe :: Word64LE -> Maybe Int
testBit :: Word64LE -> Int -> Bool
$ctestBit :: Word64LE -> Int -> Bool
complementBit :: Word64LE -> Int -> Word64LE
$ccomplementBit :: Word64LE -> Int -> Word64LE
clearBit :: Word64LE -> Int -> Word64LE
$cclearBit :: Word64LE -> Int -> Word64LE
setBit :: Word64LE -> Int -> Word64LE
$csetBit :: Word64LE -> Int -> Word64LE
bit :: Int -> Word64LE
$cbit :: Int -> Word64LE
zeroBits :: Word64LE
$czeroBits :: Word64LE
rotate :: Word64LE -> Int -> Word64LE
$crotate :: Word64LE -> Int -> Word64LE
shift :: Word64LE -> Int -> Word64LE
$cshift :: Word64LE -> Int -> Word64LE
complement :: Word64LE -> Word64LE
$ccomplement :: Word64LE -> Word64LE
xor :: Word64LE -> Word64LE -> Word64LE
$cxor :: Word64LE -> Word64LE -> Word64LE
.|. :: Word64LE -> Word64LE -> Word64LE
$c.|. :: Word64LE -> Word64LE -> Word64LE
.&. :: Word64LE -> Word64LE -> Word64LE
$c.&. :: Word64LE -> Word64LE -> Word64LE
Bits, Word64LE
forall a. a -> Default a
def :: Word64LE
$cdef :: Word64LE
Default)

newtype Int32LE = Int32LE {Int32LE -> Int32
unInt32LE :: Int32}
  deriving stock (Int -> Int32LE -> ShowS
[Int32LE] -> ShowS
Int32LE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Int32LE] -> ShowS
$cshowList :: [Int32LE] -> ShowS
show :: Int32LE -> String
$cshow :: Int32LE -> String
showsPrec :: Int -> Int32LE -> ShowS
$cshowsPrec :: Int -> Int32LE -> ShowS
Show)
  deriving newtype (Int32LE -> Int32LE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Int32LE -> Int32LE -> Bool
$c/= :: Int32LE -> Int32LE -> Bool
== :: Int32LE -> Int32LE -> Bool
$c== :: Int32LE -> Int32LE -> Bool
Eq, Eq 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
min :: Int32LE -> Int32LE -> Int32LE
$cmin :: Int32LE -> Int32LE -> Int32LE
max :: Int32LE -> Int32LE -> Int32LE
$cmax :: Int32LE -> Int32LE -> Int32LE
>= :: Int32LE -> Int32LE -> Bool
$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
compare :: Int32LE -> Int32LE -> Ordering
$ccompare :: Int32LE -> Int32LE -> Ordering
Ord, Integer -> Int32LE
Int32LE -> Int32LE
Int32LE -> Int32LE -> Int32LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Int32LE
$cfromInteger :: Integer -> Int32LE
signum :: Int32LE -> Int32LE
$csignum :: Int32LE -> Int32LE
abs :: Int32LE -> Int32LE
$cabs :: Int32LE -> Int32LE
negate :: Int32LE -> Int32LE
$cnegate :: Int32LE -> Int32LE
* :: Int32LE -> Int32LE -> Int32LE
$c* :: Int32LE -> Int32LE -> Int32LE
- :: Int32LE -> Int32LE -> Int32LE
$c- :: Int32LE -> Int32LE -> Int32LE
+ :: Int32LE -> Int32LE -> Int32LE
$c+ :: Int32LE -> Int32LE -> Int32LE
Num, Int -> Int32LE
Int32LE -> Int
Int32LE -> [Int32LE]
Int32LE -> Int32LE
Int32LE -> Int32LE -> [Int32LE]
Int32LE -> Int32LE -> Int32LE -> [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
enumFromThenTo :: Int32LE -> Int32LE -> Int32LE -> [Int32LE]
$cenumFromThenTo :: Int32LE -> Int32LE -> Int32LE -> [Int32LE]
enumFromTo :: Int32LE -> Int32LE -> [Int32LE]
$cenumFromTo :: Int32LE -> Int32LE -> [Int32LE]
enumFromThen :: Int32LE -> Int32LE -> [Int32LE]
$cenumFromThen :: Int32LE -> Int32LE -> [Int32LE]
enumFrom :: Int32LE -> [Int32LE]
$cenumFrom :: Int32LE -> [Int32LE]
fromEnum :: Int32LE -> Int
$cfromEnum :: Int32LE -> Int
toEnum :: Int -> Int32LE
$ctoEnum :: Int -> Int32LE
pred :: Int32LE -> Int32LE
$cpred :: Int32LE -> Int32LE
succ :: Int32LE -> Int32LE
$csucc :: Int32LE -> Int32LE
Enum, Int32LE
forall a. a -> a -> Bounded a
maxBound :: Int32LE
$cmaxBound :: Int32LE
minBound :: Int32LE
$cminBound :: Int32LE
Bounded, Num Int32LE
Ord Int32LE
Int32LE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Int32LE -> Rational
$ctoRational :: Int32LE -> Rational
Real, Enum Int32LE
Real 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
toInteger :: Int32LE -> Integer
$ctoInteger :: Int32LE -> Integer
divMod :: Int32LE -> Int32LE -> (Int32LE, Int32LE)
$cdivMod :: Int32LE -> Int32LE -> (Int32LE, Int32LE)
quotRem :: Int32LE -> Int32LE -> (Int32LE, Int32LE)
$cquotRem :: Int32LE -> Int32LE -> (Int32LE, Int32LE)
mod :: Int32LE -> Int32LE -> Int32LE
$cmod :: Int32LE -> Int32LE -> Int32LE
div :: Int32LE -> Int32LE -> Int32LE
$cdiv :: Int32LE -> Int32LE -> Int32LE
rem :: Int32LE -> Int32LE -> Int32LE
$crem :: Int32LE -> Int32LE -> Int32LE
quot :: Int32LE -> Int32LE -> Int32LE
$cquot :: Int32LE -> Int32LE -> Int32LE
Integral, Eq Int32LE
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
popCount :: Int32LE -> Int
$cpopCount :: Int32LE -> Int
rotateR :: Int32LE -> Int -> Int32LE
$crotateR :: Int32LE -> Int -> Int32LE
rotateL :: Int32LE -> Int -> Int32LE
$crotateL :: Int32LE -> Int -> Int32LE
unsafeShiftR :: Int32LE -> Int -> Int32LE
$cunsafeShiftR :: Int32LE -> Int -> Int32LE
shiftR :: Int32LE -> Int -> Int32LE
$cshiftR :: Int32LE -> Int -> Int32LE
unsafeShiftL :: Int32LE -> Int -> Int32LE
$cunsafeShiftL :: Int32LE -> Int -> Int32LE
shiftL :: Int32LE -> Int -> Int32LE
$cshiftL :: Int32LE -> Int -> Int32LE
isSigned :: Int32LE -> Bool
$cisSigned :: Int32LE -> Bool
bitSize :: Int32LE -> Int
$cbitSize :: Int32LE -> Int
bitSizeMaybe :: Int32LE -> Maybe Int
$cbitSizeMaybe :: Int32LE -> Maybe Int
testBit :: Int32LE -> Int -> Bool
$ctestBit :: Int32LE -> Int -> Bool
complementBit :: Int32LE -> Int -> Int32LE
$ccomplementBit :: Int32LE -> Int -> Int32LE
clearBit :: Int32LE -> Int -> Int32LE
$cclearBit :: Int32LE -> Int -> Int32LE
setBit :: Int32LE -> Int -> Int32LE
$csetBit :: Int32LE -> Int -> Int32LE
bit :: Int -> Int32LE
$cbit :: Int -> Int32LE
zeroBits :: Int32LE
$czeroBits :: Int32LE
rotate :: Int32LE -> Int -> Int32LE
$crotate :: Int32LE -> Int -> Int32LE
shift :: Int32LE -> Int -> Int32LE
$cshift :: Int32LE -> Int -> Int32LE
complement :: Int32LE -> Int32LE
$ccomplement :: Int32LE -> Int32LE
xor :: Int32LE -> Int32LE -> Int32LE
$cxor :: Int32LE -> Int32LE -> Int32LE
.|. :: Int32LE -> Int32LE -> Int32LE
$c.|. :: Int32LE -> Int32LE -> Int32LE
.&. :: Int32LE -> Int32LE -> Int32LE
$c.&. :: Int32LE -> Int32LE -> Int32LE
Bits, Int32LE
forall a. a -> Default a
def :: Int32LE
$cdef :: Int32LE
Default)

newtype Int64LE = Int64LE {Int64LE -> Int64
unInt64LE :: Int64}
  deriving stock (Int -> Int64LE -> ShowS
[Int64LE] -> ShowS
Int64LE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Int64LE] -> ShowS
$cshowList :: [Int64LE] -> ShowS
show :: Int64LE -> String
$cshow :: Int64LE -> String
showsPrec :: Int -> Int64LE -> ShowS
$cshowsPrec :: Int -> Int64LE -> ShowS
Show)
  deriving newtype (Int64LE -> Int64LE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Int64LE -> Int64LE -> Bool
$c/= :: Int64LE -> Int64LE -> Bool
== :: Int64LE -> Int64LE -> Bool
$c== :: Int64LE -> Int64LE -> Bool
Eq, Eq 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
min :: Int64LE -> Int64LE -> Int64LE
$cmin :: Int64LE -> Int64LE -> Int64LE
max :: Int64LE -> Int64LE -> Int64LE
$cmax :: Int64LE -> Int64LE -> Int64LE
>= :: Int64LE -> Int64LE -> Bool
$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
compare :: Int64LE -> Int64LE -> Ordering
$ccompare :: Int64LE -> Int64LE -> Ordering
Ord, Integer -> Int64LE
Int64LE -> Int64LE
Int64LE -> Int64LE -> Int64LE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Int64LE
$cfromInteger :: Integer -> Int64LE
signum :: Int64LE -> Int64LE
$csignum :: Int64LE -> Int64LE
abs :: Int64LE -> Int64LE
$cabs :: Int64LE -> Int64LE
negate :: Int64LE -> Int64LE
$cnegate :: Int64LE -> Int64LE
* :: Int64LE -> Int64LE -> Int64LE
$c* :: Int64LE -> Int64LE -> Int64LE
- :: Int64LE -> Int64LE -> Int64LE
$c- :: Int64LE -> Int64LE -> Int64LE
+ :: Int64LE -> Int64LE -> Int64LE
$c+ :: Int64LE -> Int64LE -> Int64LE
Num, Int -> Int64LE
Int64LE -> Int
Int64LE -> [Int64LE]
Int64LE -> Int64LE
Int64LE -> Int64LE -> [Int64LE]
Int64LE -> Int64LE -> Int64LE -> [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
enumFromThenTo :: Int64LE -> Int64LE -> Int64LE -> [Int64LE]
$cenumFromThenTo :: Int64LE -> Int64LE -> Int64LE -> [Int64LE]
enumFromTo :: Int64LE -> Int64LE -> [Int64LE]
$cenumFromTo :: Int64LE -> Int64LE -> [Int64LE]
enumFromThen :: Int64LE -> Int64LE -> [Int64LE]
$cenumFromThen :: Int64LE -> Int64LE -> [Int64LE]
enumFrom :: Int64LE -> [Int64LE]
$cenumFrom :: Int64LE -> [Int64LE]
fromEnum :: Int64LE -> Int
$cfromEnum :: Int64LE -> Int
toEnum :: Int -> Int64LE
$ctoEnum :: Int -> Int64LE
pred :: Int64LE -> Int64LE
$cpred :: Int64LE -> Int64LE
succ :: Int64LE -> Int64LE
$csucc :: Int64LE -> Int64LE
Enum, Int64LE
forall a. a -> a -> Bounded a
maxBound :: Int64LE
$cmaxBound :: Int64LE
minBound :: Int64LE
$cminBound :: Int64LE
Bounded, Num Int64LE
Ord Int64LE
Int64LE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Int64LE -> Rational
$ctoRational :: Int64LE -> Rational
Real, Enum Int64LE
Real 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
toInteger :: Int64LE -> Integer
$ctoInteger :: Int64LE -> Integer
divMod :: Int64LE -> Int64LE -> (Int64LE, Int64LE)
$cdivMod :: Int64LE -> Int64LE -> (Int64LE, Int64LE)
quotRem :: Int64LE -> Int64LE -> (Int64LE, Int64LE)
$cquotRem :: Int64LE -> Int64LE -> (Int64LE, Int64LE)
mod :: Int64LE -> Int64LE -> Int64LE
$cmod :: Int64LE -> Int64LE -> Int64LE
div :: Int64LE -> Int64LE -> Int64LE
$cdiv :: Int64LE -> Int64LE -> Int64LE
rem :: Int64LE -> Int64LE -> Int64LE
$crem :: Int64LE -> Int64LE -> Int64LE
quot :: Int64LE -> Int64LE -> Int64LE
$cquot :: Int64LE -> Int64LE -> Int64LE
Integral, Eq Int64LE
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
popCount :: Int64LE -> Int
$cpopCount :: Int64LE -> Int
rotateR :: Int64LE -> Int -> Int64LE
$crotateR :: Int64LE -> Int -> Int64LE
rotateL :: Int64LE -> Int -> Int64LE
$crotateL :: Int64LE -> Int -> Int64LE
unsafeShiftR :: Int64LE -> Int -> Int64LE
$cunsafeShiftR :: Int64LE -> Int -> Int64LE
shiftR :: Int64LE -> Int -> Int64LE
$cshiftR :: Int64LE -> Int -> Int64LE
unsafeShiftL :: Int64LE -> Int -> Int64LE
$cunsafeShiftL :: Int64LE -> Int -> Int64LE
shiftL :: Int64LE -> Int -> Int64LE
$cshiftL :: Int64LE -> Int -> Int64LE
isSigned :: Int64LE -> Bool
$cisSigned :: Int64LE -> Bool
bitSize :: Int64LE -> Int
$cbitSize :: Int64LE -> Int
bitSizeMaybe :: Int64LE -> Maybe Int
$cbitSizeMaybe :: Int64LE -> Maybe Int
testBit :: Int64LE -> Int -> Bool
$ctestBit :: Int64LE -> Int -> Bool
complementBit :: Int64LE -> Int -> Int64LE
$ccomplementBit :: Int64LE -> Int -> Int64LE
clearBit :: Int64LE -> Int -> Int64LE
$cclearBit :: Int64LE -> Int -> Int64LE
setBit :: Int64LE -> Int -> Int64LE
$csetBit :: Int64LE -> Int -> Int64LE
bit :: Int -> Int64LE
$cbit :: Int -> Int64LE
zeroBits :: Int64LE
$czeroBits :: Int64LE
rotate :: Int64LE -> Int -> Int64LE
$crotate :: Int64LE -> Int -> Int64LE
shift :: Int64LE -> Int -> Int64LE
$cshift :: Int64LE -> Int -> Int64LE
complement :: Int64LE -> Int64LE
$ccomplement :: Int64LE -> Int64LE
xor :: Int64LE -> Int64LE -> Int64LE
$cxor :: Int64LE -> Int64LE -> Int64LE
.|. :: Int64LE -> Int64LE -> Int64LE
$c.|. :: Int64LE -> Int64LE -> Int64LE
.&. :: Int64LE -> Int64LE -> Int64LE
$c.&. :: Int64LE -> Int64LE -> Int64LE
Bits, Int64LE
forall a. a -> Default a
def :: Int64LE
$cdef :: Int64LE
Default)

newtype FloatLE = FloatLE {FloatLE -> Float
unFloatLE :: Float}
  deriving stock (Int -> FloatLE -> ShowS
[FloatLE] -> ShowS
FloatLE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FloatLE] -> ShowS
$cshowList :: [FloatLE] -> ShowS
show :: FloatLE -> String
$cshow :: FloatLE -> String
showsPrec :: Int -> FloatLE -> ShowS
$cshowsPrec :: Int -> FloatLE -> ShowS
Show)
  deriving newtype (FloatLE -> FloatLE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FloatLE -> FloatLE -> Bool
$c/= :: FloatLE -> FloatLE -> Bool
== :: FloatLE -> FloatLE -> Bool
$c== :: FloatLE -> FloatLE -> Bool
Eq, Eq 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
min :: FloatLE -> FloatLE -> FloatLE
$cmin :: FloatLE -> FloatLE -> FloatLE
max :: FloatLE -> FloatLE -> FloatLE
$cmax :: FloatLE -> FloatLE -> FloatLE
>= :: FloatLE -> FloatLE -> Bool
$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
compare :: FloatLE -> FloatLE -> Ordering
$ccompare :: FloatLE -> FloatLE -> Ordering
Ord, Integer -> FloatLE
FloatLE -> FloatLE
FloatLE -> FloatLE -> FloatLE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> FloatLE
$cfromInteger :: Integer -> FloatLE
signum :: FloatLE -> FloatLE
$csignum :: FloatLE -> FloatLE
abs :: FloatLE -> FloatLE
$cabs :: FloatLE -> FloatLE
negate :: FloatLE -> FloatLE
$cnegate :: FloatLE -> FloatLE
* :: FloatLE -> FloatLE -> FloatLE
$c* :: FloatLE -> FloatLE -> FloatLE
- :: FloatLE -> FloatLE -> FloatLE
$c- :: FloatLE -> FloatLE -> FloatLE
+ :: FloatLE -> FloatLE -> FloatLE
$c+ :: FloatLE -> FloatLE -> FloatLE
Num, Num FloatLE
Ord FloatLE
FloatLE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: FloatLE -> Rational
$ctoRational :: FloatLE -> Rational
Real, Num FloatLE
Rational -> FloatLE
FloatLE -> FloatLE
FloatLE -> FloatLE -> FloatLE
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> FloatLE
$cfromRational :: Rational -> FloatLE
recip :: FloatLE -> FloatLE
$crecip :: FloatLE -> FloatLE
/ :: FloatLE -> FloatLE -> FloatLE
$c/ :: FloatLE -> FloatLE -> FloatLE
Fractional, Fractional FloatLE
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
log1mexp :: FloatLE -> FloatLE
$clog1mexp :: FloatLE -> FloatLE
log1pexp :: FloatLE -> FloatLE
$clog1pexp :: FloatLE -> FloatLE
expm1 :: FloatLE -> FloatLE
$cexpm1 :: FloatLE -> FloatLE
log1p :: FloatLE -> FloatLE
$clog1p :: FloatLE -> FloatLE
atanh :: FloatLE -> FloatLE
$catanh :: FloatLE -> FloatLE
acosh :: FloatLE -> FloatLE
$cacosh :: FloatLE -> FloatLE
asinh :: FloatLE -> FloatLE
$casinh :: FloatLE -> FloatLE
tanh :: FloatLE -> FloatLE
$ctanh :: FloatLE -> FloatLE
cosh :: FloatLE -> FloatLE
$ccosh :: FloatLE -> FloatLE
sinh :: FloatLE -> FloatLE
$csinh :: FloatLE -> FloatLE
atan :: FloatLE -> FloatLE
$catan :: FloatLE -> FloatLE
acos :: FloatLE -> FloatLE
$cacos :: FloatLE -> FloatLE
asin :: FloatLE -> FloatLE
$casin :: FloatLE -> FloatLE
tan :: FloatLE -> FloatLE
$ctan :: FloatLE -> FloatLE
cos :: FloatLE -> FloatLE
$ccos :: FloatLE -> FloatLE
sin :: FloatLE -> FloatLE
$csin :: FloatLE -> FloatLE
logBase :: FloatLE -> FloatLE -> FloatLE
$clogBase :: FloatLE -> FloatLE -> FloatLE
** :: FloatLE -> FloatLE -> FloatLE
$c** :: FloatLE -> FloatLE -> FloatLE
sqrt :: FloatLE -> FloatLE
$csqrt :: FloatLE -> FloatLE
log :: FloatLE -> FloatLE
$clog :: FloatLE -> FloatLE
exp :: FloatLE -> FloatLE
$cexp :: FloatLE -> FloatLE
pi :: FloatLE
$cpi :: FloatLE
Floating, Fractional FloatLE
Real 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
floor :: forall b. Integral b => FloatLE -> b
$cfloor :: forall b. Integral b => FloatLE -> b
ceiling :: forall b. Integral b => FloatLE -> b
$cceiling :: forall b. Integral b => FloatLE -> b
round :: forall b. Integral b => FloatLE -> b
$cround :: forall b. Integral b => FloatLE -> b
truncate :: forall b. Integral b => FloatLE -> b
$ctruncate :: forall b. Integral b => FloatLE -> b
properFraction :: forall b. Integral b => FloatLE -> (b, FloatLE)
$cproperFraction :: forall b. Integral b => FloatLE -> (b, FloatLE)
RealFrac, FloatLE
forall a. a -> Default a
def :: FloatLE
$cdef :: FloatLE
Default)

newtype DoubleLE = DoubleLE {DoubleLE -> Double
unDoubleLE :: Double}
  deriving stock (Int -> DoubleLE -> ShowS
[DoubleLE] -> ShowS
DoubleLE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DoubleLE] -> ShowS
$cshowList :: [DoubleLE] -> ShowS
show :: DoubleLE -> String
$cshow :: DoubleLE -> String
showsPrec :: Int -> DoubleLE -> ShowS
$cshowsPrec :: Int -> DoubleLE -> ShowS
Show)
  deriving newtype (DoubleLE -> DoubleLE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DoubleLE -> DoubleLE -> Bool
$c/= :: DoubleLE -> DoubleLE -> Bool
== :: DoubleLE -> DoubleLE -> Bool
$c== :: DoubleLE -> DoubleLE -> Bool
Eq, Eq 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
min :: DoubleLE -> DoubleLE -> DoubleLE
$cmin :: DoubleLE -> DoubleLE -> DoubleLE
max :: DoubleLE -> DoubleLE -> DoubleLE
$cmax :: DoubleLE -> DoubleLE -> DoubleLE
>= :: DoubleLE -> DoubleLE -> Bool
$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
compare :: DoubleLE -> DoubleLE -> Ordering
$ccompare :: DoubleLE -> DoubleLE -> Ordering
Ord, Integer -> DoubleLE
DoubleLE -> DoubleLE
DoubleLE -> DoubleLE -> DoubleLE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> DoubleLE
$cfromInteger :: Integer -> DoubleLE
signum :: DoubleLE -> DoubleLE
$csignum :: DoubleLE -> DoubleLE
abs :: DoubleLE -> DoubleLE
$cabs :: DoubleLE -> DoubleLE
negate :: DoubleLE -> DoubleLE
$cnegate :: DoubleLE -> DoubleLE
* :: DoubleLE -> DoubleLE -> DoubleLE
$c* :: DoubleLE -> DoubleLE -> DoubleLE
- :: DoubleLE -> DoubleLE -> DoubleLE
$c- :: DoubleLE -> DoubleLE -> DoubleLE
+ :: DoubleLE -> DoubleLE -> DoubleLE
$c+ :: DoubleLE -> DoubleLE -> DoubleLE
Num, Num DoubleLE
Ord DoubleLE
DoubleLE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: DoubleLE -> Rational
$ctoRational :: DoubleLE -> Rational
Real, Num DoubleLE
Rational -> DoubleLE
DoubleLE -> DoubleLE
DoubleLE -> DoubleLE -> DoubleLE
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> DoubleLE
$cfromRational :: Rational -> DoubleLE
recip :: DoubleLE -> DoubleLE
$crecip :: DoubleLE -> DoubleLE
/ :: DoubleLE -> DoubleLE -> DoubleLE
$c/ :: DoubleLE -> DoubleLE -> DoubleLE
Fractional, Fractional DoubleLE
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
log1mexp :: DoubleLE -> DoubleLE
$clog1mexp :: DoubleLE -> DoubleLE
log1pexp :: DoubleLE -> DoubleLE
$clog1pexp :: DoubleLE -> DoubleLE
expm1 :: DoubleLE -> DoubleLE
$cexpm1 :: DoubleLE -> DoubleLE
log1p :: DoubleLE -> DoubleLE
$clog1p :: DoubleLE -> DoubleLE
atanh :: DoubleLE -> DoubleLE
$catanh :: DoubleLE -> DoubleLE
acosh :: DoubleLE -> DoubleLE
$cacosh :: DoubleLE -> DoubleLE
asinh :: DoubleLE -> DoubleLE
$casinh :: DoubleLE -> DoubleLE
tanh :: DoubleLE -> DoubleLE
$ctanh :: DoubleLE -> DoubleLE
cosh :: DoubleLE -> DoubleLE
$ccosh :: DoubleLE -> DoubleLE
sinh :: DoubleLE -> DoubleLE
$csinh :: DoubleLE -> DoubleLE
atan :: DoubleLE -> DoubleLE
$catan :: DoubleLE -> DoubleLE
acos :: DoubleLE -> DoubleLE
$cacos :: DoubleLE -> DoubleLE
asin :: DoubleLE -> DoubleLE
$casin :: DoubleLE -> DoubleLE
tan :: DoubleLE -> DoubleLE
$ctan :: DoubleLE -> DoubleLE
cos :: DoubleLE -> DoubleLE
$ccos :: DoubleLE -> DoubleLE
sin :: DoubleLE -> DoubleLE
$csin :: DoubleLE -> DoubleLE
logBase :: DoubleLE -> DoubleLE -> DoubleLE
$clogBase :: DoubleLE -> DoubleLE -> DoubleLE
** :: DoubleLE -> DoubleLE -> DoubleLE
$c** :: DoubleLE -> DoubleLE -> DoubleLE
sqrt :: DoubleLE -> DoubleLE
$csqrt :: DoubleLE -> DoubleLE
log :: DoubleLE -> DoubleLE
$clog :: DoubleLE -> DoubleLE
exp :: DoubleLE -> DoubleLE
$cexp :: DoubleLE -> DoubleLE
pi :: DoubleLE
$cpi :: DoubleLE
Floating, Fractional DoubleLE
Real 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
floor :: forall b. Integral b => DoubleLE -> b
$cfloor :: forall b. Integral b => DoubleLE -> b
ceiling :: forall b. Integral b => DoubleLE -> b
$cceiling :: forall b. Integral b => DoubleLE -> b
round :: forall b. Integral b => DoubleLE -> b
$cround :: forall b. Integral b => DoubleLE -> b
truncate :: forall b. Integral b => DoubleLE -> b
$ctruncate :: forall b. Integral b => DoubleLE -> b
properFraction :: forall b. Integral b => DoubleLE -> (b, DoubleLE)
$cproperFraction :: forall b. Integral b => DoubleLE -> (b, DoubleLE)
RealFrac, DoubleLE
forall a. a -> Default a
def :: DoubleLE
$cdef :: DoubleLE
Default)

newtype Word16BE = Word16BE {Word16BE -> Word16
unWord16BE :: Word16}
  deriving stock (Int -> Word16BE -> ShowS
[Word16BE] -> ShowS
Word16BE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Word16BE] -> ShowS
$cshowList :: [Word16BE] -> ShowS
show :: Word16BE -> String
$cshow :: Word16BE -> String
showsPrec :: Int -> Word16BE -> ShowS
$cshowsPrec :: Int -> Word16BE -> ShowS
Show)
  deriving newtype (Word16BE -> Word16BE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Word16BE -> Word16BE -> Bool
$c/= :: Word16BE -> Word16BE -> Bool
== :: Word16BE -> Word16BE -> Bool
$c== :: Word16BE -> Word16BE -> Bool
Eq, Eq 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
min :: Word16BE -> Word16BE -> Word16BE
$cmin :: Word16BE -> Word16BE -> Word16BE
max :: Word16BE -> Word16BE -> Word16BE
$cmax :: Word16BE -> Word16BE -> Word16BE
>= :: Word16BE -> Word16BE -> Bool
$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
compare :: Word16BE -> Word16BE -> Ordering
$ccompare :: Word16BE -> Word16BE -> Ordering
Ord, Integer -> Word16BE
Word16BE -> Word16BE
Word16BE -> Word16BE -> Word16BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Word16BE
$cfromInteger :: Integer -> Word16BE
signum :: Word16BE -> Word16BE
$csignum :: Word16BE -> Word16BE
abs :: Word16BE -> Word16BE
$cabs :: Word16BE -> Word16BE
negate :: Word16BE -> Word16BE
$cnegate :: Word16BE -> Word16BE
* :: Word16BE -> Word16BE -> Word16BE
$c* :: Word16BE -> Word16BE -> Word16BE
- :: Word16BE -> Word16BE -> Word16BE
$c- :: Word16BE -> Word16BE -> Word16BE
+ :: Word16BE -> Word16BE -> Word16BE
$c+ :: Word16BE -> Word16BE -> Word16BE
Num, Int -> Word16BE
Word16BE -> Int
Word16BE -> [Word16BE]
Word16BE -> Word16BE
Word16BE -> Word16BE -> [Word16BE]
Word16BE -> Word16BE -> Word16BE -> [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
enumFromThenTo :: Word16BE -> Word16BE -> Word16BE -> [Word16BE]
$cenumFromThenTo :: Word16BE -> Word16BE -> Word16BE -> [Word16BE]
enumFromTo :: Word16BE -> Word16BE -> [Word16BE]
$cenumFromTo :: Word16BE -> Word16BE -> [Word16BE]
enumFromThen :: Word16BE -> Word16BE -> [Word16BE]
$cenumFromThen :: Word16BE -> Word16BE -> [Word16BE]
enumFrom :: Word16BE -> [Word16BE]
$cenumFrom :: Word16BE -> [Word16BE]
fromEnum :: Word16BE -> Int
$cfromEnum :: Word16BE -> Int
toEnum :: Int -> Word16BE
$ctoEnum :: Int -> Word16BE
pred :: Word16BE -> Word16BE
$cpred :: Word16BE -> Word16BE
succ :: Word16BE -> Word16BE
$csucc :: Word16BE -> Word16BE
Enum, Word16BE
forall a. a -> a -> Bounded a
maxBound :: Word16BE
$cmaxBound :: Word16BE
minBound :: Word16BE
$cminBound :: Word16BE
Bounded, Num Word16BE
Ord Word16BE
Word16BE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Word16BE -> Rational
$ctoRational :: Word16BE -> Rational
Real, Enum Word16BE
Real 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
toInteger :: Word16BE -> Integer
$ctoInteger :: Word16BE -> Integer
divMod :: Word16BE -> Word16BE -> (Word16BE, Word16BE)
$cdivMod :: Word16BE -> Word16BE -> (Word16BE, Word16BE)
quotRem :: Word16BE -> Word16BE -> (Word16BE, Word16BE)
$cquotRem :: Word16BE -> Word16BE -> (Word16BE, Word16BE)
mod :: Word16BE -> Word16BE -> Word16BE
$cmod :: Word16BE -> Word16BE -> Word16BE
div :: Word16BE -> Word16BE -> Word16BE
$cdiv :: Word16BE -> Word16BE -> Word16BE
rem :: Word16BE -> Word16BE -> Word16BE
$crem :: Word16BE -> Word16BE -> Word16BE
quot :: Word16BE -> Word16BE -> Word16BE
$cquot :: Word16BE -> Word16BE -> Word16BE
Integral, Eq Word16BE
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
popCount :: Word16BE -> Int
$cpopCount :: Word16BE -> Int
rotateR :: Word16BE -> Int -> Word16BE
$crotateR :: Word16BE -> Int -> Word16BE
rotateL :: Word16BE -> Int -> Word16BE
$crotateL :: Word16BE -> Int -> Word16BE
unsafeShiftR :: Word16BE -> Int -> Word16BE
$cunsafeShiftR :: Word16BE -> Int -> Word16BE
shiftR :: Word16BE -> Int -> Word16BE
$cshiftR :: Word16BE -> Int -> Word16BE
unsafeShiftL :: Word16BE -> Int -> Word16BE
$cunsafeShiftL :: Word16BE -> Int -> Word16BE
shiftL :: Word16BE -> Int -> Word16BE
$cshiftL :: Word16BE -> Int -> Word16BE
isSigned :: Word16BE -> Bool
$cisSigned :: Word16BE -> Bool
bitSize :: Word16BE -> Int
$cbitSize :: Word16BE -> Int
bitSizeMaybe :: Word16BE -> Maybe Int
$cbitSizeMaybe :: Word16BE -> Maybe Int
testBit :: Word16BE -> Int -> Bool
$ctestBit :: Word16BE -> Int -> Bool
complementBit :: Word16BE -> Int -> Word16BE
$ccomplementBit :: Word16BE -> Int -> Word16BE
clearBit :: Word16BE -> Int -> Word16BE
$cclearBit :: Word16BE -> Int -> Word16BE
setBit :: Word16BE -> Int -> Word16BE
$csetBit :: Word16BE -> Int -> Word16BE
bit :: Int -> Word16BE
$cbit :: Int -> Word16BE
zeroBits :: Word16BE
$czeroBits :: Word16BE
rotate :: Word16BE -> Int -> Word16BE
$crotate :: Word16BE -> Int -> Word16BE
shift :: Word16BE -> Int -> Word16BE
$cshift :: Word16BE -> Int -> Word16BE
complement :: Word16BE -> Word16BE
$ccomplement :: Word16BE -> Word16BE
xor :: Word16BE -> Word16BE -> Word16BE
$cxor :: Word16BE -> Word16BE -> Word16BE
.|. :: Word16BE -> Word16BE -> Word16BE
$c.|. :: Word16BE -> Word16BE -> Word16BE
.&. :: Word16BE -> Word16BE -> Word16BE
$c.&. :: Word16BE -> Word16BE -> Word16BE
Bits, Word16BE
forall a. a -> Default a
def :: Word16BE
$cdef :: Word16BE
Default)

newtype Int16BE = Int16BE {Int16BE -> Int16
unInt16BE :: Int16}
  deriving stock (Int -> Int16BE -> ShowS
[Int16BE] -> ShowS
Int16BE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Int16BE] -> ShowS
$cshowList :: [Int16BE] -> ShowS
show :: Int16BE -> String
$cshow :: Int16BE -> String
showsPrec :: Int -> Int16BE -> ShowS
$cshowsPrec :: Int -> Int16BE -> ShowS
Show)
  deriving newtype (Int16BE -> Int16BE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Int16BE -> Int16BE -> Bool
$c/= :: Int16BE -> Int16BE -> Bool
== :: Int16BE -> Int16BE -> Bool
$c== :: Int16BE -> Int16BE -> Bool
Eq, Eq 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
min :: Int16BE -> Int16BE -> Int16BE
$cmin :: Int16BE -> Int16BE -> Int16BE
max :: Int16BE -> Int16BE -> Int16BE
$cmax :: Int16BE -> Int16BE -> Int16BE
>= :: Int16BE -> Int16BE -> Bool
$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
compare :: Int16BE -> Int16BE -> Ordering
$ccompare :: Int16BE -> Int16BE -> Ordering
Ord, Integer -> Int16BE
Int16BE -> Int16BE
Int16BE -> Int16BE -> Int16BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Int16BE
$cfromInteger :: Integer -> Int16BE
signum :: Int16BE -> Int16BE
$csignum :: Int16BE -> Int16BE
abs :: Int16BE -> Int16BE
$cabs :: Int16BE -> Int16BE
negate :: Int16BE -> Int16BE
$cnegate :: Int16BE -> Int16BE
* :: Int16BE -> Int16BE -> Int16BE
$c* :: Int16BE -> Int16BE -> Int16BE
- :: Int16BE -> Int16BE -> Int16BE
$c- :: Int16BE -> Int16BE -> Int16BE
+ :: Int16BE -> Int16BE -> Int16BE
$c+ :: Int16BE -> Int16BE -> Int16BE
Num, Int -> Int16BE
Int16BE -> Int
Int16BE -> [Int16BE]
Int16BE -> Int16BE
Int16BE -> Int16BE -> [Int16BE]
Int16BE -> Int16BE -> Int16BE -> [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
enumFromThenTo :: Int16BE -> Int16BE -> Int16BE -> [Int16BE]
$cenumFromThenTo :: Int16BE -> Int16BE -> Int16BE -> [Int16BE]
enumFromTo :: Int16BE -> Int16BE -> [Int16BE]
$cenumFromTo :: Int16BE -> Int16BE -> [Int16BE]
enumFromThen :: Int16BE -> Int16BE -> [Int16BE]
$cenumFromThen :: Int16BE -> Int16BE -> [Int16BE]
enumFrom :: Int16BE -> [Int16BE]
$cenumFrom :: Int16BE -> [Int16BE]
fromEnum :: Int16BE -> Int
$cfromEnum :: Int16BE -> Int
toEnum :: Int -> Int16BE
$ctoEnum :: Int -> Int16BE
pred :: Int16BE -> Int16BE
$cpred :: Int16BE -> Int16BE
succ :: Int16BE -> Int16BE
$csucc :: Int16BE -> Int16BE
Enum, Int16BE
forall a. a -> a -> Bounded a
maxBound :: Int16BE
$cmaxBound :: Int16BE
minBound :: Int16BE
$cminBound :: Int16BE
Bounded, Num Int16BE
Ord Int16BE
Int16BE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Int16BE -> Rational
$ctoRational :: Int16BE -> Rational
Real, Enum Int16BE
Real 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
toInteger :: Int16BE -> Integer
$ctoInteger :: Int16BE -> Integer
divMod :: Int16BE -> Int16BE -> (Int16BE, Int16BE)
$cdivMod :: Int16BE -> Int16BE -> (Int16BE, Int16BE)
quotRem :: Int16BE -> Int16BE -> (Int16BE, Int16BE)
$cquotRem :: Int16BE -> Int16BE -> (Int16BE, Int16BE)
mod :: Int16BE -> Int16BE -> Int16BE
$cmod :: Int16BE -> Int16BE -> Int16BE
div :: Int16BE -> Int16BE -> Int16BE
$cdiv :: Int16BE -> Int16BE -> Int16BE
rem :: Int16BE -> Int16BE -> Int16BE
$crem :: Int16BE -> Int16BE -> Int16BE
quot :: Int16BE -> Int16BE -> Int16BE
$cquot :: Int16BE -> Int16BE -> Int16BE
Integral, Eq Int16BE
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
popCount :: Int16BE -> Int
$cpopCount :: Int16BE -> Int
rotateR :: Int16BE -> Int -> Int16BE
$crotateR :: Int16BE -> Int -> Int16BE
rotateL :: Int16BE -> Int -> Int16BE
$crotateL :: Int16BE -> Int -> Int16BE
unsafeShiftR :: Int16BE -> Int -> Int16BE
$cunsafeShiftR :: Int16BE -> Int -> Int16BE
shiftR :: Int16BE -> Int -> Int16BE
$cshiftR :: Int16BE -> Int -> Int16BE
unsafeShiftL :: Int16BE -> Int -> Int16BE
$cunsafeShiftL :: Int16BE -> Int -> Int16BE
shiftL :: Int16BE -> Int -> Int16BE
$cshiftL :: Int16BE -> Int -> Int16BE
isSigned :: Int16BE -> Bool
$cisSigned :: Int16BE -> Bool
bitSize :: Int16BE -> Int
$cbitSize :: Int16BE -> Int
bitSizeMaybe :: Int16BE -> Maybe Int
$cbitSizeMaybe :: Int16BE -> Maybe Int
testBit :: Int16BE -> Int -> Bool
$ctestBit :: Int16BE -> Int -> Bool
complementBit :: Int16BE -> Int -> Int16BE
$ccomplementBit :: Int16BE -> Int -> Int16BE
clearBit :: Int16BE -> Int -> Int16BE
$cclearBit :: Int16BE -> Int -> Int16BE
setBit :: Int16BE -> Int -> Int16BE
$csetBit :: Int16BE -> Int -> Int16BE
bit :: Int -> Int16BE
$cbit :: Int -> Int16BE
zeroBits :: Int16BE
$czeroBits :: Int16BE
rotate :: Int16BE -> Int -> Int16BE
$crotate :: Int16BE -> Int -> Int16BE
shift :: Int16BE -> Int -> Int16BE
$cshift :: Int16BE -> Int -> Int16BE
complement :: Int16BE -> Int16BE
$ccomplement :: Int16BE -> Int16BE
xor :: Int16BE -> Int16BE -> Int16BE
$cxor :: Int16BE -> Int16BE -> Int16BE
.|. :: Int16BE -> Int16BE -> Int16BE
$c.|. :: Int16BE -> Int16BE -> Int16BE
.&. :: Int16BE -> Int16BE -> Int16BE
$c.&. :: Int16BE -> Int16BE -> Int16BE
Bits, Int16BE
forall a. a -> Default a
def :: Int16BE
$cdef :: Int16BE
Default)

newtype Word24BE = Word24BE {Word24BE -> Word24
unWord24BE :: Word24}
  deriving stock (Int -> Word24BE -> ShowS
[Word24BE] -> ShowS
Word24BE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Word24BE] -> ShowS
$cshowList :: [Word24BE] -> ShowS
show :: Word24BE -> String
$cshow :: Word24BE -> String
showsPrec :: Int -> Word24BE -> ShowS
$cshowsPrec :: Int -> Word24BE -> ShowS
Show)
  deriving newtype (Word24BE -> Word24BE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Word24BE -> Word24BE -> Bool
$c/= :: Word24BE -> Word24BE -> Bool
== :: Word24BE -> Word24BE -> Bool
$c== :: Word24BE -> Word24BE -> Bool
Eq, Eq 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
min :: Word24BE -> Word24BE -> Word24BE
$cmin :: Word24BE -> Word24BE -> Word24BE
max :: Word24BE -> Word24BE -> Word24BE
$cmax :: Word24BE -> Word24BE -> Word24BE
>= :: Word24BE -> Word24BE -> Bool
$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
compare :: Word24BE -> Word24BE -> Ordering
$ccompare :: Word24BE -> Word24BE -> Ordering
Ord, Integer -> Word24BE
Word24BE -> Word24BE
Word24BE -> Word24BE -> Word24BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Word24BE
$cfromInteger :: Integer -> Word24BE
signum :: Word24BE -> Word24BE
$csignum :: Word24BE -> Word24BE
abs :: Word24BE -> Word24BE
$cabs :: Word24BE -> Word24BE
negate :: Word24BE -> Word24BE
$cnegate :: Word24BE -> Word24BE
* :: Word24BE -> Word24BE -> Word24BE
$c* :: Word24BE -> Word24BE -> Word24BE
- :: Word24BE -> Word24BE -> Word24BE
$c- :: Word24BE -> Word24BE -> Word24BE
+ :: Word24BE -> Word24BE -> Word24BE
$c+ :: Word24BE -> Word24BE -> Word24BE
Num, Int -> Word24BE
Word24BE -> Int
Word24BE -> [Word24BE]
Word24BE -> Word24BE
Word24BE -> Word24BE -> [Word24BE]
Word24BE -> Word24BE -> Word24BE -> [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
enumFromThenTo :: Word24BE -> Word24BE -> Word24BE -> [Word24BE]
$cenumFromThenTo :: Word24BE -> Word24BE -> Word24BE -> [Word24BE]
enumFromTo :: Word24BE -> Word24BE -> [Word24BE]
$cenumFromTo :: Word24BE -> Word24BE -> [Word24BE]
enumFromThen :: Word24BE -> Word24BE -> [Word24BE]
$cenumFromThen :: Word24BE -> Word24BE -> [Word24BE]
enumFrom :: Word24BE -> [Word24BE]
$cenumFrom :: Word24BE -> [Word24BE]
fromEnum :: Word24BE -> Int
$cfromEnum :: Word24BE -> Int
toEnum :: Int -> Word24BE
$ctoEnum :: Int -> Word24BE
pred :: Word24BE -> Word24BE
$cpred :: Word24BE -> Word24BE
succ :: Word24BE -> Word24BE
$csucc :: Word24BE -> Word24BE
Enum, Word24BE
forall a. a -> a -> Bounded a
maxBound :: Word24BE
$cmaxBound :: Word24BE
minBound :: Word24BE
$cminBound :: Word24BE
Bounded, Num Word24BE
Ord Word24BE
Word24BE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Word24BE -> Rational
$ctoRational :: Word24BE -> Rational
Real, Enum Word24BE
Real 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
toInteger :: Word24BE -> Integer
$ctoInteger :: Word24BE -> Integer
divMod :: Word24BE -> Word24BE -> (Word24BE, Word24BE)
$cdivMod :: Word24BE -> Word24BE -> (Word24BE, Word24BE)
quotRem :: Word24BE -> Word24BE -> (Word24BE, Word24BE)
$cquotRem :: Word24BE -> Word24BE -> (Word24BE, Word24BE)
mod :: Word24BE -> Word24BE -> Word24BE
$cmod :: Word24BE -> Word24BE -> Word24BE
div :: Word24BE -> Word24BE -> Word24BE
$cdiv :: Word24BE -> Word24BE -> Word24BE
rem :: Word24BE -> Word24BE -> Word24BE
$crem :: Word24BE -> Word24BE -> Word24BE
quot :: Word24BE -> Word24BE -> Word24BE
$cquot :: Word24BE -> Word24BE -> Word24BE
Integral, Eq Word24BE
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
popCount :: Word24BE -> Int
$cpopCount :: Word24BE -> Int
rotateR :: Word24BE -> Int -> Word24BE
$crotateR :: Word24BE -> Int -> Word24BE
rotateL :: Word24BE -> Int -> Word24BE
$crotateL :: Word24BE -> Int -> Word24BE
unsafeShiftR :: Word24BE -> Int -> Word24BE
$cunsafeShiftR :: Word24BE -> Int -> Word24BE
shiftR :: Word24BE -> Int -> Word24BE
$cshiftR :: Word24BE -> Int -> Word24BE
unsafeShiftL :: Word24BE -> Int -> Word24BE
$cunsafeShiftL :: Word24BE -> Int -> Word24BE
shiftL :: Word24BE -> Int -> Word24BE
$cshiftL :: Word24BE -> Int -> Word24BE
isSigned :: Word24BE -> Bool
$cisSigned :: Word24BE -> Bool
bitSize :: Word24BE -> Int
$cbitSize :: Word24BE -> Int
bitSizeMaybe :: Word24BE -> Maybe Int
$cbitSizeMaybe :: Word24BE -> Maybe Int
testBit :: Word24BE -> Int -> Bool
$ctestBit :: Word24BE -> Int -> Bool
complementBit :: Word24BE -> Int -> Word24BE
$ccomplementBit :: Word24BE -> Int -> Word24BE
clearBit :: Word24BE -> Int -> Word24BE
$cclearBit :: Word24BE -> Int -> Word24BE
setBit :: Word24BE -> Int -> Word24BE
$csetBit :: Word24BE -> Int -> Word24BE
bit :: Int -> Word24BE
$cbit :: Int -> Word24BE
zeroBits :: Word24BE
$czeroBits :: Word24BE
rotate :: Word24BE -> Int -> Word24BE
$crotate :: Word24BE -> Int -> Word24BE
shift :: Word24BE -> Int -> Word24BE
$cshift :: Word24BE -> Int -> Word24BE
complement :: Word24BE -> Word24BE
$ccomplement :: Word24BE -> Word24BE
xor :: Word24BE -> Word24BE -> Word24BE
$cxor :: Word24BE -> Word24BE -> Word24BE
.|. :: Word24BE -> Word24BE -> Word24BE
$c.|. :: Word24BE -> Word24BE -> Word24BE
.&. :: Word24BE -> Word24BE -> Word24BE
$c.&. :: Word24BE -> Word24BE -> Word24BE
Bits)

instance Default Word24BE where
  def :: Word24BE
def = Word24BE
0

newtype Int24BE = Int24BE {Int24BE -> Int24
unInt24BE :: Int24}
  deriving stock (Int -> Int24BE -> ShowS
[Int24BE] -> ShowS
Int24BE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Int24BE] -> ShowS
$cshowList :: [Int24BE] -> ShowS
show :: Int24BE -> String
$cshow :: Int24BE -> String
showsPrec :: Int -> Int24BE -> ShowS
$cshowsPrec :: Int -> Int24BE -> ShowS
Show)
  deriving newtype (Int24BE -> Int24BE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Int24BE -> Int24BE -> Bool
$c/= :: Int24BE -> Int24BE -> Bool
== :: Int24BE -> Int24BE -> Bool
$c== :: Int24BE -> Int24BE -> Bool
Eq, Eq 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
min :: Int24BE -> Int24BE -> Int24BE
$cmin :: Int24BE -> Int24BE -> Int24BE
max :: Int24BE -> Int24BE -> Int24BE
$cmax :: Int24BE -> Int24BE -> Int24BE
>= :: Int24BE -> Int24BE -> Bool
$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
compare :: Int24BE -> Int24BE -> Ordering
$ccompare :: Int24BE -> Int24BE -> Ordering
Ord, Integer -> Int24BE
Int24BE -> Int24BE
Int24BE -> Int24BE -> Int24BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Int24BE
$cfromInteger :: Integer -> Int24BE
signum :: Int24BE -> Int24BE
$csignum :: Int24BE -> Int24BE
abs :: Int24BE -> Int24BE
$cabs :: Int24BE -> Int24BE
negate :: Int24BE -> Int24BE
$cnegate :: Int24BE -> Int24BE
* :: Int24BE -> Int24BE -> Int24BE
$c* :: Int24BE -> Int24BE -> Int24BE
- :: Int24BE -> Int24BE -> Int24BE
$c- :: Int24BE -> Int24BE -> Int24BE
+ :: Int24BE -> Int24BE -> Int24BE
$c+ :: Int24BE -> Int24BE -> Int24BE
Num, Int -> Int24BE
Int24BE -> Int
Int24BE -> [Int24BE]
Int24BE -> Int24BE
Int24BE -> Int24BE -> [Int24BE]
Int24BE -> Int24BE -> Int24BE -> [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
enumFromThenTo :: Int24BE -> Int24BE -> Int24BE -> [Int24BE]
$cenumFromThenTo :: Int24BE -> Int24BE -> Int24BE -> [Int24BE]
enumFromTo :: Int24BE -> Int24BE -> [Int24BE]
$cenumFromTo :: Int24BE -> Int24BE -> [Int24BE]
enumFromThen :: Int24BE -> Int24BE -> [Int24BE]
$cenumFromThen :: Int24BE -> Int24BE -> [Int24BE]
enumFrom :: Int24BE -> [Int24BE]
$cenumFrom :: Int24BE -> [Int24BE]
fromEnum :: Int24BE -> Int
$cfromEnum :: Int24BE -> Int
toEnum :: Int -> Int24BE
$ctoEnum :: Int -> Int24BE
pred :: Int24BE -> Int24BE
$cpred :: Int24BE -> Int24BE
succ :: Int24BE -> Int24BE
$csucc :: Int24BE -> Int24BE
Enum, Int24BE
forall a. a -> a -> Bounded a
maxBound :: Int24BE
$cmaxBound :: Int24BE
minBound :: Int24BE
$cminBound :: Int24BE
Bounded, Num Int24BE
Ord Int24BE
Int24BE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Int24BE -> Rational
$ctoRational :: Int24BE -> Rational
Real, Enum Int24BE
Real 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
toInteger :: Int24BE -> Integer
$ctoInteger :: Int24BE -> Integer
divMod :: Int24BE -> Int24BE -> (Int24BE, Int24BE)
$cdivMod :: Int24BE -> Int24BE -> (Int24BE, Int24BE)
quotRem :: Int24BE -> Int24BE -> (Int24BE, Int24BE)
$cquotRem :: Int24BE -> Int24BE -> (Int24BE, Int24BE)
mod :: Int24BE -> Int24BE -> Int24BE
$cmod :: Int24BE -> Int24BE -> Int24BE
div :: Int24BE -> Int24BE -> Int24BE
$cdiv :: Int24BE -> Int24BE -> Int24BE
rem :: Int24BE -> Int24BE -> Int24BE
$crem :: Int24BE -> Int24BE -> Int24BE
quot :: Int24BE -> Int24BE -> Int24BE
$cquot :: Int24BE -> Int24BE -> Int24BE
Integral, Eq Int24BE
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
popCount :: Int24BE -> Int
$cpopCount :: Int24BE -> Int
rotateR :: Int24BE -> Int -> Int24BE
$crotateR :: Int24BE -> Int -> Int24BE
rotateL :: Int24BE -> Int -> Int24BE
$crotateL :: Int24BE -> Int -> Int24BE
unsafeShiftR :: Int24BE -> Int -> Int24BE
$cunsafeShiftR :: Int24BE -> Int -> Int24BE
shiftR :: Int24BE -> Int -> Int24BE
$cshiftR :: Int24BE -> Int -> Int24BE
unsafeShiftL :: Int24BE -> Int -> Int24BE
$cunsafeShiftL :: Int24BE -> Int -> Int24BE
shiftL :: Int24BE -> Int -> Int24BE
$cshiftL :: Int24BE -> Int -> Int24BE
isSigned :: Int24BE -> Bool
$cisSigned :: Int24BE -> Bool
bitSize :: Int24BE -> Int
$cbitSize :: Int24BE -> Int
bitSizeMaybe :: Int24BE -> Maybe Int
$cbitSizeMaybe :: Int24BE -> Maybe Int
testBit :: Int24BE -> Int -> Bool
$ctestBit :: Int24BE -> Int -> Bool
complementBit :: Int24BE -> Int -> Int24BE
$ccomplementBit :: Int24BE -> Int -> Int24BE
clearBit :: Int24BE -> Int -> Int24BE
$cclearBit :: Int24BE -> Int -> Int24BE
setBit :: Int24BE -> Int -> Int24BE
$csetBit :: Int24BE -> Int -> Int24BE
bit :: Int -> Int24BE
$cbit :: Int -> Int24BE
zeroBits :: Int24BE
$czeroBits :: Int24BE
rotate :: Int24BE -> Int -> Int24BE
$crotate :: Int24BE -> Int -> Int24BE
shift :: Int24BE -> Int -> Int24BE
$cshift :: Int24BE -> Int -> Int24BE
complement :: Int24BE -> Int24BE
$ccomplement :: Int24BE -> Int24BE
xor :: Int24BE -> Int24BE -> Int24BE
$cxor :: Int24BE -> Int24BE -> Int24BE
.|. :: Int24BE -> Int24BE -> Int24BE
$c.|. :: Int24BE -> Int24BE -> Int24BE
.&. :: Int24BE -> Int24BE -> Int24BE
$c.&. :: Int24BE -> Int24BE -> Int24BE
Bits)

instance Default Int24BE where
  def :: Int24BE
def = Int24BE
0

newtype Word32BE = Word32BE {Word32BE -> Word32
unWord32BE :: Word32}
  deriving stock (Int -> Word32BE -> ShowS
[Word32BE] -> ShowS
Word32BE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Word32BE] -> ShowS
$cshowList :: [Word32BE] -> ShowS
show :: Word32BE -> String
$cshow :: Word32BE -> String
showsPrec :: Int -> Word32BE -> ShowS
$cshowsPrec :: Int -> Word32BE -> ShowS
Show)
  deriving newtype (Word32BE -> Word32BE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Word32BE -> Word32BE -> Bool
$c/= :: Word32BE -> Word32BE -> Bool
== :: Word32BE -> Word32BE -> Bool
$c== :: Word32BE -> Word32BE -> Bool
Eq, Eq 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
min :: Word32BE -> Word32BE -> Word32BE
$cmin :: Word32BE -> Word32BE -> Word32BE
max :: Word32BE -> Word32BE -> Word32BE
$cmax :: Word32BE -> Word32BE -> Word32BE
>= :: Word32BE -> Word32BE -> Bool
$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
compare :: Word32BE -> Word32BE -> Ordering
$ccompare :: Word32BE -> Word32BE -> Ordering
Ord, Integer -> Word32BE
Word32BE -> Word32BE
Word32BE -> Word32BE -> Word32BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Word32BE
$cfromInteger :: Integer -> Word32BE
signum :: Word32BE -> Word32BE
$csignum :: Word32BE -> Word32BE
abs :: Word32BE -> Word32BE
$cabs :: Word32BE -> Word32BE
negate :: Word32BE -> Word32BE
$cnegate :: Word32BE -> Word32BE
* :: Word32BE -> Word32BE -> Word32BE
$c* :: Word32BE -> Word32BE -> Word32BE
- :: Word32BE -> Word32BE -> Word32BE
$c- :: Word32BE -> Word32BE -> Word32BE
+ :: Word32BE -> Word32BE -> Word32BE
$c+ :: Word32BE -> Word32BE -> Word32BE
Num, Int -> Word32BE
Word32BE -> Int
Word32BE -> [Word32BE]
Word32BE -> Word32BE
Word32BE -> Word32BE -> [Word32BE]
Word32BE -> Word32BE -> Word32BE -> [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
enumFromThenTo :: Word32BE -> Word32BE -> Word32BE -> [Word32BE]
$cenumFromThenTo :: Word32BE -> Word32BE -> Word32BE -> [Word32BE]
enumFromTo :: Word32BE -> Word32BE -> [Word32BE]
$cenumFromTo :: Word32BE -> Word32BE -> [Word32BE]
enumFromThen :: Word32BE -> Word32BE -> [Word32BE]
$cenumFromThen :: Word32BE -> Word32BE -> [Word32BE]
enumFrom :: Word32BE -> [Word32BE]
$cenumFrom :: Word32BE -> [Word32BE]
fromEnum :: Word32BE -> Int
$cfromEnum :: Word32BE -> Int
toEnum :: Int -> Word32BE
$ctoEnum :: Int -> Word32BE
pred :: Word32BE -> Word32BE
$cpred :: Word32BE -> Word32BE
succ :: Word32BE -> Word32BE
$csucc :: Word32BE -> Word32BE
Enum, Word32BE
forall a. a -> a -> Bounded a
maxBound :: Word32BE
$cmaxBound :: Word32BE
minBound :: Word32BE
$cminBound :: Word32BE
Bounded, Num Word32BE
Ord Word32BE
Word32BE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Word32BE -> Rational
$ctoRational :: Word32BE -> Rational
Real, Enum Word32BE
Real 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
toInteger :: Word32BE -> Integer
$ctoInteger :: Word32BE -> Integer
divMod :: Word32BE -> Word32BE -> (Word32BE, Word32BE)
$cdivMod :: Word32BE -> Word32BE -> (Word32BE, Word32BE)
quotRem :: Word32BE -> Word32BE -> (Word32BE, Word32BE)
$cquotRem :: Word32BE -> Word32BE -> (Word32BE, Word32BE)
mod :: Word32BE -> Word32BE -> Word32BE
$cmod :: Word32BE -> Word32BE -> Word32BE
div :: Word32BE -> Word32BE -> Word32BE
$cdiv :: Word32BE -> Word32BE -> Word32BE
rem :: Word32BE -> Word32BE -> Word32BE
$crem :: Word32BE -> Word32BE -> Word32BE
quot :: Word32BE -> Word32BE -> Word32BE
$cquot :: Word32BE -> Word32BE -> Word32BE
Integral, Eq Word32BE
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
popCount :: Word32BE -> Int
$cpopCount :: Word32BE -> Int
rotateR :: Word32BE -> Int -> Word32BE
$crotateR :: Word32BE -> Int -> Word32BE
rotateL :: Word32BE -> Int -> Word32BE
$crotateL :: Word32BE -> Int -> Word32BE
unsafeShiftR :: Word32BE -> Int -> Word32BE
$cunsafeShiftR :: Word32BE -> Int -> Word32BE
shiftR :: Word32BE -> Int -> Word32BE
$cshiftR :: Word32BE -> Int -> Word32BE
unsafeShiftL :: Word32BE -> Int -> Word32BE
$cunsafeShiftL :: Word32BE -> Int -> Word32BE
shiftL :: Word32BE -> Int -> Word32BE
$cshiftL :: Word32BE -> Int -> Word32BE
isSigned :: Word32BE -> Bool
$cisSigned :: Word32BE -> Bool
bitSize :: Word32BE -> Int
$cbitSize :: Word32BE -> Int
bitSizeMaybe :: Word32BE -> Maybe Int
$cbitSizeMaybe :: Word32BE -> Maybe Int
testBit :: Word32BE -> Int -> Bool
$ctestBit :: Word32BE -> Int -> Bool
complementBit :: Word32BE -> Int -> Word32BE
$ccomplementBit :: Word32BE -> Int -> Word32BE
clearBit :: Word32BE -> Int -> Word32BE
$cclearBit :: Word32BE -> Int -> Word32BE
setBit :: Word32BE -> Int -> Word32BE
$csetBit :: Word32BE -> Int -> Word32BE
bit :: Int -> Word32BE
$cbit :: Int -> Word32BE
zeroBits :: Word32BE
$czeroBits :: Word32BE
rotate :: Word32BE -> Int -> Word32BE
$crotate :: Word32BE -> Int -> Word32BE
shift :: Word32BE -> Int -> Word32BE
$cshift :: Word32BE -> Int -> Word32BE
complement :: Word32BE -> Word32BE
$ccomplement :: Word32BE -> Word32BE
xor :: Word32BE -> Word32BE -> Word32BE
$cxor :: Word32BE -> Word32BE -> Word32BE
.|. :: Word32BE -> Word32BE -> Word32BE
$c.|. :: Word32BE -> Word32BE -> Word32BE
.&. :: Word32BE -> Word32BE -> Word32BE
$c.&. :: Word32BE -> Word32BE -> Word32BE
Bits, Word32BE
forall a. a -> Default a
def :: Word32BE
$cdef :: Word32BE
Default)

newtype Int32BE = Int32BE {Int32BE -> Int32
unInt32BE :: Int32}
  deriving stock (Int -> Int32BE -> ShowS
[Int32BE] -> ShowS
Int32BE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Int32BE] -> ShowS
$cshowList :: [Int32BE] -> ShowS
show :: Int32BE -> String
$cshow :: Int32BE -> String
showsPrec :: Int -> Int32BE -> ShowS
$cshowsPrec :: Int -> Int32BE -> ShowS
Show)
  deriving newtype (Int32BE -> Int32BE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Int32BE -> Int32BE -> Bool
$c/= :: Int32BE -> Int32BE -> Bool
== :: Int32BE -> Int32BE -> Bool
$c== :: Int32BE -> Int32BE -> Bool
Eq, Eq 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
min :: Int32BE -> Int32BE -> Int32BE
$cmin :: Int32BE -> Int32BE -> Int32BE
max :: Int32BE -> Int32BE -> Int32BE
$cmax :: Int32BE -> Int32BE -> Int32BE
>= :: Int32BE -> Int32BE -> Bool
$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
compare :: Int32BE -> Int32BE -> Ordering
$ccompare :: Int32BE -> Int32BE -> Ordering
Ord, Integer -> Int32BE
Int32BE -> Int32BE
Int32BE -> Int32BE -> Int32BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Int32BE
$cfromInteger :: Integer -> Int32BE
signum :: Int32BE -> Int32BE
$csignum :: Int32BE -> Int32BE
abs :: Int32BE -> Int32BE
$cabs :: Int32BE -> Int32BE
negate :: Int32BE -> Int32BE
$cnegate :: Int32BE -> Int32BE
* :: Int32BE -> Int32BE -> Int32BE
$c* :: Int32BE -> Int32BE -> Int32BE
- :: Int32BE -> Int32BE -> Int32BE
$c- :: Int32BE -> Int32BE -> Int32BE
+ :: Int32BE -> Int32BE -> Int32BE
$c+ :: Int32BE -> Int32BE -> Int32BE
Num, Int -> Int32BE
Int32BE -> Int
Int32BE -> [Int32BE]
Int32BE -> Int32BE
Int32BE -> Int32BE -> [Int32BE]
Int32BE -> Int32BE -> Int32BE -> [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
enumFromThenTo :: Int32BE -> Int32BE -> Int32BE -> [Int32BE]
$cenumFromThenTo :: Int32BE -> Int32BE -> Int32BE -> [Int32BE]
enumFromTo :: Int32BE -> Int32BE -> [Int32BE]
$cenumFromTo :: Int32BE -> Int32BE -> [Int32BE]
enumFromThen :: Int32BE -> Int32BE -> [Int32BE]
$cenumFromThen :: Int32BE -> Int32BE -> [Int32BE]
enumFrom :: Int32BE -> [Int32BE]
$cenumFrom :: Int32BE -> [Int32BE]
fromEnum :: Int32BE -> Int
$cfromEnum :: Int32BE -> Int
toEnum :: Int -> Int32BE
$ctoEnum :: Int -> Int32BE
pred :: Int32BE -> Int32BE
$cpred :: Int32BE -> Int32BE
succ :: Int32BE -> Int32BE
$csucc :: Int32BE -> Int32BE
Enum, Int32BE
forall a. a -> a -> Bounded a
maxBound :: Int32BE
$cmaxBound :: Int32BE
minBound :: Int32BE
$cminBound :: Int32BE
Bounded, Num Int32BE
Ord Int32BE
Int32BE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Int32BE -> Rational
$ctoRational :: Int32BE -> Rational
Real, Enum Int32BE
Real 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
toInteger :: Int32BE -> Integer
$ctoInteger :: Int32BE -> Integer
divMod :: Int32BE -> Int32BE -> (Int32BE, Int32BE)
$cdivMod :: Int32BE -> Int32BE -> (Int32BE, Int32BE)
quotRem :: Int32BE -> Int32BE -> (Int32BE, Int32BE)
$cquotRem :: Int32BE -> Int32BE -> (Int32BE, Int32BE)
mod :: Int32BE -> Int32BE -> Int32BE
$cmod :: Int32BE -> Int32BE -> Int32BE
div :: Int32BE -> Int32BE -> Int32BE
$cdiv :: Int32BE -> Int32BE -> Int32BE
rem :: Int32BE -> Int32BE -> Int32BE
$crem :: Int32BE -> Int32BE -> Int32BE
quot :: Int32BE -> Int32BE -> Int32BE
$cquot :: Int32BE -> Int32BE -> Int32BE
Integral, Eq Int32BE
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
popCount :: Int32BE -> Int
$cpopCount :: Int32BE -> Int
rotateR :: Int32BE -> Int -> Int32BE
$crotateR :: Int32BE -> Int -> Int32BE
rotateL :: Int32BE -> Int -> Int32BE
$crotateL :: Int32BE -> Int -> Int32BE
unsafeShiftR :: Int32BE -> Int -> Int32BE
$cunsafeShiftR :: Int32BE -> Int -> Int32BE
shiftR :: Int32BE -> Int -> Int32BE
$cshiftR :: Int32BE -> Int -> Int32BE
unsafeShiftL :: Int32BE -> Int -> Int32BE
$cunsafeShiftL :: Int32BE -> Int -> Int32BE
shiftL :: Int32BE -> Int -> Int32BE
$cshiftL :: Int32BE -> Int -> Int32BE
isSigned :: Int32BE -> Bool
$cisSigned :: Int32BE -> Bool
bitSize :: Int32BE -> Int
$cbitSize :: Int32BE -> Int
bitSizeMaybe :: Int32BE -> Maybe Int
$cbitSizeMaybe :: Int32BE -> Maybe Int
testBit :: Int32BE -> Int -> Bool
$ctestBit :: Int32BE -> Int -> Bool
complementBit :: Int32BE -> Int -> Int32BE
$ccomplementBit :: Int32BE -> Int -> Int32BE
clearBit :: Int32BE -> Int -> Int32BE
$cclearBit :: Int32BE -> Int -> Int32BE
setBit :: Int32BE -> Int -> Int32BE
$csetBit :: Int32BE -> Int -> Int32BE
bit :: Int -> Int32BE
$cbit :: Int -> Int32BE
zeroBits :: Int32BE
$czeroBits :: Int32BE
rotate :: Int32BE -> Int -> Int32BE
$crotate :: Int32BE -> Int -> Int32BE
shift :: Int32BE -> Int -> Int32BE
$cshift :: Int32BE -> Int -> Int32BE
complement :: Int32BE -> Int32BE
$ccomplement :: Int32BE -> Int32BE
xor :: Int32BE -> Int32BE -> Int32BE
$cxor :: Int32BE -> Int32BE -> Int32BE
.|. :: Int32BE -> Int32BE -> Int32BE
$c.|. :: Int32BE -> Int32BE -> Int32BE
.&. :: Int32BE -> Int32BE -> Int32BE
$c.&. :: Int32BE -> Int32BE -> Int32BE
Bits, Int32BE
forall a. a -> Default a
def :: Int32BE
$cdef :: Int32BE
Default)

newtype Word64BE = Word64BE {Word64BE -> Word64
unWord64BE :: Word64}
  deriving stock (Int -> Word64BE -> ShowS
[Word64BE] -> ShowS
Word64BE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Word64BE] -> ShowS
$cshowList :: [Word64BE] -> ShowS
show :: Word64BE -> String
$cshow :: Word64BE -> String
showsPrec :: Int -> Word64BE -> ShowS
$cshowsPrec :: Int -> Word64BE -> ShowS
Show)
  deriving newtype (Word64BE -> Word64BE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Word64BE -> Word64BE -> Bool
$c/= :: Word64BE -> Word64BE -> Bool
== :: Word64BE -> Word64BE -> Bool
$c== :: Word64BE -> Word64BE -> Bool
Eq, Eq 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
min :: Word64BE -> Word64BE -> Word64BE
$cmin :: Word64BE -> Word64BE -> Word64BE
max :: Word64BE -> Word64BE -> Word64BE
$cmax :: Word64BE -> Word64BE -> Word64BE
>= :: Word64BE -> Word64BE -> Bool
$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
compare :: Word64BE -> Word64BE -> Ordering
$ccompare :: Word64BE -> Word64BE -> Ordering
Ord, Integer -> Word64BE
Word64BE -> Word64BE
Word64BE -> Word64BE -> Word64BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Word64BE
$cfromInteger :: Integer -> Word64BE
signum :: Word64BE -> Word64BE
$csignum :: Word64BE -> Word64BE
abs :: Word64BE -> Word64BE
$cabs :: Word64BE -> Word64BE
negate :: Word64BE -> Word64BE
$cnegate :: Word64BE -> Word64BE
* :: Word64BE -> Word64BE -> Word64BE
$c* :: Word64BE -> Word64BE -> Word64BE
- :: Word64BE -> Word64BE -> Word64BE
$c- :: Word64BE -> Word64BE -> Word64BE
+ :: Word64BE -> Word64BE -> Word64BE
$c+ :: Word64BE -> Word64BE -> Word64BE
Num, Int -> Word64BE
Word64BE -> Int
Word64BE -> [Word64BE]
Word64BE -> Word64BE
Word64BE -> Word64BE -> [Word64BE]
Word64BE -> Word64BE -> Word64BE -> [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
enumFromThenTo :: Word64BE -> Word64BE -> Word64BE -> [Word64BE]
$cenumFromThenTo :: Word64BE -> Word64BE -> Word64BE -> [Word64BE]
enumFromTo :: Word64BE -> Word64BE -> [Word64BE]
$cenumFromTo :: Word64BE -> Word64BE -> [Word64BE]
enumFromThen :: Word64BE -> Word64BE -> [Word64BE]
$cenumFromThen :: Word64BE -> Word64BE -> [Word64BE]
enumFrom :: Word64BE -> [Word64BE]
$cenumFrom :: Word64BE -> [Word64BE]
fromEnum :: Word64BE -> Int
$cfromEnum :: Word64BE -> Int
toEnum :: Int -> Word64BE
$ctoEnum :: Int -> Word64BE
pred :: Word64BE -> Word64BE
$cpred :: Word64BE -> Word64BE
succ :: Word64BE -> Word64BE
$csucc :: Word64BE -> Word64BE
Enum, Word64BE
forall a. a -> a -> Bounded a
maxBound :: Word64BE
$cmaxBound :: Word64BE
minBound :: Word64BE
$cminBound :: Word64BE
Bounded, Num Word64BE
Ord Word64BE
Word64BE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Word64BE -> Rational
$ctoRational :: Word64BE -> Rational
Real, Enum Word64BE
Real 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
toInteger :: Word64BE -> Integer
$ctoInteger :: Word64BE -> Integer
divMod :: Word64BE -> Word64BE -> (Word64BE, Word64BE)
$cdivMod :: Word64BE -> Word64BE -> (Word64BE, Word64BE)
quotRem :: Word64BE -> Word64BE -> (Word64BE, Word64BE)
$cquotRem :: Word64BE -> Word64BE -> (Word64BE, Word64BE)
mod :: Word64BE -> Word64BE -> Word64BE
$cmod :: Word64BE -> Word64BE -> Word64BE
div :: Word64BE -> Word64BE -> Word64BE
$cdiv :: Word64BE -> Word64BE -> Word64BE
rem :: Word64BE -> Word64BE -> Word64BE
$crem :: Word64BE -> Word64BE -> Word64BE
quot :: Word64BE -> Word64BE -> Word64BE
$cquot :: Word64BE -> Word64BE -> Word64BE
Integral, Eq Word64BE
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
popCount :: Word64BE -> Int
$cpopCount :: Word64BE -> Int
rotateR :: Word64BE -> Int -> Word64BE
$crotateR :: Word64BE -> Int -> Word64BE
rotateL :: Word64BE -> Int -> Word64BE
$crotateL :: Word64BE -> Int -> Word64BE
unsafeShiftR :: Word64BE -> Int -> Word64BE
$cunsafeShiftR :: Word64BE -> Int -> Word64BE
shiftR :: Word64BE -> Int -> Word64BE
$cshiftR :: Word64BE -> Int -> Word64BE
unsafeShiftL :: Word64BE -> Int -> Word64BE
$cunsafeShiftL :: Word64BE -> Int -> Word64BE
shiftL :: Word64BE -> Int -> Word64BE
$cshiftL :: Word64BE -> Int -> Word64BE
isSigned :: Word64BE -> Bool
$cisSigned :: Word64BE -> Bool
bitSize :: Word64BE -> Int
$cbitSize :: Word64BE -> Int
bitSizeMaybe :: Word64BE -> Maybe Int
$cbitSizeMaybe :: Word64BE -> Maybe Int
testBit :: Word64BE -> Int -> Bool
$ctestBit :: Word64BE -> Int -> Bool
complementBit :: Word64BE -> Int -> Word64BE
$ccomplementBit :: Word64BE -> Int -> Word64BE
clearBit :: Word64BE -> Int -> Word64BE
$cclearBit :: Word64BE -> Int -> Word64BE
setBit :: Word64BE -> Int -> Word64BE
$csetBit :: Word64BE -> Int -> Word64BE
bit :: Int -> Word64BE
$cbit :: Int -> Word64BE
zeroBits :: Word64BE
$czeroBits :: Word64BE
rotate :: Word64BE -> Int -> Word64BE
$crotate :: Word64BE -> Int -> Word64BE
shift :: Word64BE -> Int -> Word64BE
$cshift :: Word64BE -> Int -> Word64BE
complement :: Word64BE -> Word64BE
$ccomplement :: Word64BE -> Word64BE
xor :: Word64BE -> Word64BE -> Word64BE
$cxor :: Word64BE -> Word64BE -> Word64BE
.|. :: Word64BE -> Word64BE -> Word64BE
$c.|. :: Word64BE -> Word64BE -> Word64BE
.&. :: Word64BE -> Word64BE -> Word64BE
$c.&. :: Word64BE -> Word64BE -> Word64BE
Bits, Word64BE
forall a. a -> Default a
def :: Word64BE
$cdef :: Word64BE
Default)

newtype Int64BE = Int64BE {Int64BE -> Int64
unInt64BE :: Int64}
  deriving stock (Int -> Int64BE -> ShowS
[Int64BE] -> ShowS
Int64BE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Int64BE] -> ShowS
$cshowList :: [Int64BE] -> ShowS
show :: Int64BE -> String
$cshow :: Int64BE -> String
showsPrec :: Int -> Int64BE -> ShowS
$cshowsPrec :: Int -> Int64BE -> ShowS
Show)
  deriving newtype (Int64BE -> Int64BE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Int64BE -> Int64BE -> Bool
$c/= :: Int64BE -> Int64BE -> Bool
== :: Int64BE -> Int64BE -> Bool
$c== :: Int64BE -> Int64BE -> Bool
Eq, Eq 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
min :: Int64BE -> Int64BE -> Int64BE
$cmin :: Int64BE -> Int64BE -> Int64BE
max :: Int64BE -> Int64BE -> Int64BE
$cmax :: Int64BE -> Int64BE -> Int64BE
>= :: Int64BE -> Int64BE -> Bool
$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
compare :: Int64BE -> Int64BE -> Ordering
$ccompare :: Int64BE -> Int64BE -> Ordering
Ord, Integer -> Int64BE
Int64BE -> Int64BE
Int64BE -> Int64BE -> Int64BE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> Int64BE
$cfromInteger :: Integer -> Int64BE
signum :: Int64BE -> Int64BE
$csignum :: Int64BE -> Int64BE
abs :: Int64BE -> Int64BE
$cabs :: Int64BE -> Int64BE
negate :: Int64BE -> Int64BE
$cnegate :: Int64BE -> Int64BE
* :: Int64BE -> Int64BE -> Int64BE
$c* :: Int64BE -> Int64BE -> Int64BE
- :: Int64BE -> Int64BE -> Int64BE
$c- :: Int64BE -> Int64BE -> Int64BE
+ :: Int64BE -> Int64BE -> Int64BE
$c+ :: Int64BE -> Int64BE -> Int64BE
Num, Int -> Int64BE
Int64BE -> Int
Int64BE -> [Int64BE]
Int64BE -> Int64BE
Int64BE -> Int64BE -> [Int64BE]
Int64BE -> Int64BE -> Int64BE -> [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
enumFromThenTo :: Int64BE -> Int64BE -> Int64BE -> [Int64BE]
$cenumFromThenTo :: Int64BE -> Int64BE -> Int64BE -> [Int64BE]
enumFromTo :: Int64BE -> Int64BE -> [Int64BE]
$cenumFromTo :: Int64BE -> Int64BE -> [Int64BE]
enumFromThen :: Int64BE -> Int64BE -> [Int64BE]
$cenumFromThen :: Int64BE -> Int64BE -> [Int64BE]
enumFrom :: Int64BE -> [Int64BE]
$cenumFrom :: Int64BE -> [Int64BE]
fromEnum :: Int64BE -> Int
$cfromEnum :: Int64BE -> Int
toEnum :: Int -> Int64BE
$ctoEnum :: Int -> Int64BE
pred :: Int64BE -> Int64BE
$cpred :: Int64BE -> Int64BE
succ :: Int64BE -> Int64BE
$csucc :: Int64BE -> Int64BE
Enum, Int64BE
forall a. a -> a -> Bounded a
maxBound :: Int64BE
$cmaxBound :: Int64BE
minBound :: Int64BE
$cminBound :: Int64BE
Bounded, Num Int64BE
Ord Int64BE
Int64BE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: Int64BE -> Rational
$ctoRational :: Int64BE -> Rational
Real, Enum Int64BE
Real 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
toInteger :: Int64BE -> Integer
$ctoInteger :: Int64BE -> Integer
divMod :: Int64BE -> Int64BE -> (Int64BE, Int64BE)
$cdivMod :: Int64BE -> Int64BE -> (Int64BE, Int64BE)
quotRem :: Int64BE -> Int64BE -> (Int64BE, Int64BE)
$cquotRem :: Int64BE -> Int64BE -> (Int64BE, Int64BE)
mod :: Int64BE -> Int64BE -> Int64BE
$cmod :: Int64BE -> Int64BE -> Int64BE
div :: Int64BE -> Int64BE -> Int64BE
$cdiv :: Int64BE -> Int64BE -> Int64BE
rem :: Int64BE -> Int64BE -> Int64BE
$crem :: Int64BE -> Int64BE -> Int64BE
quot :: Int64BE -> Int64BE -> Int64BE
$cquot :: Int64BE -> Int64BE -> Int64BE
Integral, Eq Int64BE
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
popCount :: Int64BE -> Int
$cpopCount :: Int64BE -> Int
rotateR :: Int64BE -> Int -> Int64BE
$crotateR :: Int64BE -> Int -> Int64BE
rotateL :: Int64BE -> Int -> Int64BE
$crotateL :: Int64BE -> Int -> Int64BE
unsafeShiftR :: Int64BE -> Int -> Int64BE
$cunsafeShiftR :: Int64BE -> Int -> Int64BE
shiftR :: Int64BE -> Int -> Int64BE
$cshiftR :: Int64BE -> Int -> Int64BE
unsafeShiftL :: Int64BE -> Int -> Int64BE
$cunsafeShiftL :: Int64BE -> Int -> Int64BE
shiftL :: Int64BE -> Int -> Int64BE
$cshiftL :: Int64BE -> Int -> Int64BE
isSigned :: Int64BE -> Bool
$cisSigned :: Int64BE -> Bool
bitSize :: Int64BE -> Int
$cbitSize :: Int64BE -> Int
bitSizeMaybe :: Int64BE -> Maybe Int
$cbitSizeMaybe :: Int64BE -> Maybe Int
testBit :: Int64BE -> Int -> Bool
$ctestBit :: Int64BE -> Int -> Bool
complementBit :: Int64BE -> Int -> Int64BE
$ccomplementBit :: Int64BE -> Int -> Int64BE
clearBit :: Int64BE -> Int -> Int64BE
$cclearBit :: Int64BE -> Int -> Int64BE
setBit :: Int64BE -> Int -> Int64BE
$csetBit :: Int64BE -> Int -> Int64BE
bit :: Int -> Int64BE
$cbit :: Int -> Int64BE
zeroBits :: Int64BE
$czeroBits :: Int64BE
rotate :: Int64BE -> Int -> Int64BE
$crotate :: Int64BE -> Int -> Int64BE
shift :: Int64BE -> Int -> Int64BE
$cshift :: Int64BE -> Int -> Int64BE
complement :: Int64BE -> Int64BE
$ccomplement :: Int64BE -> Int64BE
xor :: Int64BE -> Int64BE -> Int64BE
$cxor :: Int64BE -> Int64BE -> Int64BE
.|. :: Int64BE -> Int64BE -> Int64BE
$c.|. :: Int64BE -> Int64BE -> Int64BE
.&. :: Int64BE -> Int64BE -> Int64BE
$c.&. :: Int64BE -> Int64BE -> Int64BE
Bits, Int64BE
forall a. a -> Default a
def :: Int64BE
$cdef :: Int64BE
Default)

newtype FloatBE = FloatBE {FloatBE -> Float
unFloatBE :: Float}
  deriving stock (Int -> FloatBE -> ShowS
[FloatBE] -> ShowS
FloatBE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [FloatBE] -> ShowS
$cshowList :: [FloatBE] -> ShowS
show :: FloatBE -> String
$cshow :: FloatBE -> String
showsPrec :: Int -> FloatBE -> ShowS
$cshowsPrec :: Int -> FloatBE -> ShowS
Show)
  deriving newtype (FloatBE -> FloatBE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: FloatBE -> FloatBE -> Bool
$c/= :: FloatBE -> FloatBE -> Bool
== :: FloatBE -> FloatBE -> Bool
$c== :: FloatBE -> FloatBE -> Bool
Eq, Eq 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
min :: FloatBE -> FloatBE -> FloatBE
$cmin :: FloatBE -> FloatBE -> FloatBE
max :: FloatBE -> FloatBE -> FloatBE
$cmax :: FloatBE -> FloatBE -> FloatBE
>= :: FloatBE -> FloatBE -> Bool
$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
compare :: FloatBE -> FloatBE -> Ordering
$ccompare :: FloatBE -> FloatBE -> Ordering
Ord, Integer -> FloatBE
FloatBE -> FloatBE
FloatBE -> FloatBE -> FloatBE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> FloatBE
$cfromInteger :: Integer -> FloatBE
signum :: FloatBE -> FloatBE
$csignum :: FloatBE -> FloatBE
abs :: FloatBE -> FloatBE
$cabs :: FloatBE -> FloatBE
negate :: FloatBE -> FloatBE
$cnegate :: FloatBE -> FloatBE
* :: FloatBE -> FloatBE -> FloatBE
$c* :: FloatBE -> FloatBE -> FloatBE
- :: FloatBE -> FloatBE -> FloatBE
$c- :: FloatBE -> FloatBE -> FloatBE
+ :: FloatBE -> FloatBE -> FloatBE
$c+ :: FloatBE -> FloatBE -> FloatBE
Num, Num FloatBE
Ord FloatBE
FloatBE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: FloatBE -> Rational
$ctoRational :: FloatBE -> Rational
Real, Num FloatBE
Rational -> FloatBE
FloatBE -> FloatBE
FloatBE -> FloatBE -> FloatBE
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> FloatBE
$cfromRational :: Rational -> FloatBE
recip :: FloatBE -> FloatBE
$crecip :: FloatBE -> FloatBE
/ :: FloatBE -> FloatBE -> FloatBE
$c/ :: FloatBE -> FloatBE -> FloatBE
Fractional, Fractional FloatBE
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
log1mexp :: FloatBE -> FloatBE
$clog1mexp :: FloatBE -> FloatBE
log1pexp :: FloatBE -> FloatBE
$clog1pexp :: FloatBE -> FloatBE
expm1 :: FloatBE -> FloatBE
$cexpm1 :: FloatBE -> FloatBE
log1p :: FloatBE -> FloatBE
$clog1p :: FloatBE -> FloatBE
atanh :: FloatBE -> FloatBE
$catanh :: FloatBE -> FloatBE
acosh :: FloatBE -> FloatBE
$cacosh :: FloatBE -> FloatBE
asinh :: FloatBE -> FloatBE
$casinh :: FloatBE -> FloatBE
tanh :: FloatBE -> FloatBE
$ctanh :: FloatBE -> FloatBE
cosh :: FloatBE -> FloatBE
$ccosh :: FloatBE -> FloatBE
sinh :: FloatBE -> FloatBE
$csinh :: FloatBE -> FloatBE
atan :: FloatBE -> FloatBE
$catan :: FloatBE -> FloatBE
acos :: FloatBE -> FloatBE
$cacos :: FloatBE -> FloatBE
asin :: FloatBE -> FloatBE
$casin :: FloatBE -> FloatBE
tan :: FloatBE -> FloatBE
$ctan :: FloatBE -> FloatBE
cos :: FloatBE -> FloatBE
$ccos :: FloatBE -> FloatBE
sin :: FloatBE -> FloatBE
$csin :: FloatBE -> FloatBE
logBase :: FloatBE -> FloatBE -> FloatBE
$clogBase :: FloatBE -> FloatBE -> FloatBE
** :: FloatBE -> FloatBE -> FloatBE
$c** :: FloatBE -> FloatBE -> FloatBE
sqrt :: FloatBE -> FloatBE
$csqrt :: FloatBE -> FloatBE
log :: FloatBE -> FloatBE
$clog :: FloatBE -> FloatBE
exp :: FloatBE -> FloatBE
$cexp :: FloatBE -> FloatBE
pi :: FloatBE
$cpi :: FloatBE
Floating, Fractional FloatBE
Real 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
floor :: forall b. Integral b => FloatBE -> b
$cfloor :: forall b. Integral b => FloatBE -> b
ceiling :: forall b. Integral b => FloatBE -> b
$cceiling :: forall b. Integral b => FloatBE -> b
round :: forall b. Integral b => FloatBE -> b
$cround :: forall b. Integral b => FloatBE -> b
truncate :: forall b. Integral b => FloatBE -> b
$ctruncate :: forall b. Integral b => FloatBE -> b
properFraction :: forall b. Integral b => FloatBE -> (b, FloatBE)
$cproperFraction :: forall b. Integral b => FloatBE -> (b, FloatBE)
RealFrac, FloatBE
forall a. a -> Default a
def :: FloatBE
$cdef :: FloatBE
Default)

newtype DoubleBE = DoubleBE {DoubleBE -> Double
unDoubleBE :: Double}
  deriving stock (Int -> DoubleBE -> ShowS
[DoubleBE] -> ShowS
DoubleBE -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [DoubleBE] -> ShowS
$cshowList :: [DoubleBE] -> ShowS
show :: DoubleBE -> String
$cshow :: DoubleBE -> String
showsPrec :: Int -> DoubleBE -> ShowS
$cshowsPrec :: Int -> DoubleBE -> ShowS
Show)
  deriving newtype (DoubleBE -> DoubleBE -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: DoubleBE -> DoubleBE -> Bool
$c/= :: DoubleBE -> DoubleBE -> Bool
== :: DoubleBE -> DoubleBE -> Bool
$c== :: DoubleBE -> DoubleBE -> Bool
Eq, Eq 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
min :: DoubleBE -> DoubleBE -> DoubleBE
$cmin :: DoubleBE -> DoubleBE -> DoubleBE
max :: DoubleBE -> DoubleBE -> DoubleBE
$cmax :: DoubleBE -> DoubleBE -> DoubleBE
>= :: DoubleBE -> DoubleBE -> Bool
$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
compare :: DoubleBE -> DoubleBE -> Ordering
$ccompare :: DoubleBE -> DoubleBE -> Ordering
Ord, Integer -> DoubleBE
DoubleBE -> DoubleBE
DoubleBE -> DoubleBE -> DoubleBE
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
fromInteger :: Integer -> DoubleBE
$cfromInteger :: Integer -> DoubleBE
signum :: DoubleBE -> DoubleBE
$csignum :: DoubleBE -> DoubleBE
abs :: DoubleBE -> DoubleBE
$cabs :: DoubleBE -> DoubleBE
negate :: DoubleBE -> DoubleBE
$cnegate :: DoubleBE -> DoubleBE
* :: DoubleBE -> DoubleBE -> DoubleBE
$c* :: DoubleBE -> DoubleBE -> DoubleBE
- :: DoubleBE -> DoubleBE -> DoubleBE
$c- :: DoubleBE -> DoubleBE -> DoubleBE
+ :: DoubleBE -> DoubleBE -> DoubleBE
$c+ :: DoubleBE -> DoubleBE -> DoubleBE
Num, Num DoubleBE
Ord DoubleBE
DoubleBE -> Rational
forall a. Num a -> Ord a -> (a -> Rational) -> Real a
toRational :: DoubleBE -> Rational
$ctoRational :: DoubleBE -> Rational
Real, Num DoubleBE
Rational -> DoubleBE
DoubleBE -> DoubleBE
DoubleBE -> DoubleBE -> DoubleBE
forall a.
Num a
-> (a -> a -> a) -> (a -> a) -> (Rational -> a) -> Fractional a
fromRational :: Rational -> DoubleBE
$cfromRational :: Rational -> DoubleBE
recip :: DoubleBE -> DoubleBE
$crecip :: DoubleBE -> DoubleBE
/ :: DoubleBE -> DoubleBE -> DoubleBE
$c/ :: DoubleBE -> DoubleBE -> DoubleBE
Fractional, Fractional DoubleBE
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
log1mexp :: DoubleBE -> DoubleBE
$clog1mexp :: DoubleBE -> DoubleBE
log1pexp :: DoubleBE -> DoubleBE
$clog1pexp :: DoubleBE -> DoubleBE
expm1 :: DoubleBE -> DoubleBE
$cexpm1 :: DoubleBE -> DoubleBE
log1p :: DoubleBE -> DoubleBE
$clog1p :: DoubleBE -> DoubleBE
atanh :: DoubleBE -> DoubleBE
$catanh :: DoubleBE -> DoubleBE
acosh :: DoubleBE -> DoubleBE
$cacosh :: DoubleBE -> DoubleBE
asinh :: DoubleBE -> DoubleBE
$casinh :: DoubleBE -> DoubleBE
tanh :: DoubleBE -> DoubleBE
$ctanh :: DoubleBE -> DoubleBE
cosh :: DoubleBE -> DoubleBE
$ccosh :: DoubleBE -> DoubleBE
sinh :: DoubleBE -> DoubleBE
$csinh :: DoubleBE -> DoubleBE
atan :: DoubleBE -> DoubleBE
$catan :: DoubleBE -> DoubleBE
acos :: DoubleBE -> DoubleBE
$cacos :: DoubleBE -> DoubleBE
asin :: DoubleBE -> DoubleBE
$casin :: DoubleBE -> DoubleBE
tan :: DoubleBE -> DoubleBE
$ctan :: DoubleBE -> DoubleBE
cos :: DoubleBE -> DoubleBE
$ccos :: DoubleBE -> DoubleBE
sin :: DoubleBE -> DoubleBE
$csin :: DoubleBE -> DoubleBE
logBase :: DoubleBE -> DoubleBE -> DoubleBE
$clogBase :: DoubleBE -> DoubleBE -> DoubleBE
** :: DoubleBE -> DoubleBE -> DoubleBE
$c** :: DoubleBE -> DoubleBE -> DoubleBE
sqrt :: DoubleBE -> DoubleBE
$csqrt :: DoubleBE -> DoubleBE
log :: DoubleBE -> DoubleBE
$clog :: DoubleBE -> DoubleBE
exp :: DoubleBE -> DoubleBE
$cexp :: DoubleBE -> DoubleBE
pi :: DoubleBE
$cpi :: DoubleBE
Floating, Fractional DoubleBE
Real 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
floor :: forall b. Integral b => DoubleBE -> b
$cfloor :: forall b. Integral b => DoubleBE -> b
ceiling :: forall b. Integral b => DoubleBE -> b
$cceiling :: forall b. Integral b => DoubleBE -> b
round :: forall b. Integral b => DoubleBE -> b
$cround :: forall b. Integral b => DoubleBE -> b
truncate :: forall b. Integral b => DoubleBE -> b
$ctruncate :: forall b. Integral b => DoubleBE -> b
properFraction :: forall b. Integral b => DoubleBE -> (b, DoubleBE)
$cproperFraction :: forall b. Integral b => DoubleBE -> (b, DoubleBE)
RealFrac, DoubleBE
forall a. a -> Default a
def :: DoubleBE
$cdef :: DoubleBE
Default)

instance EndianPair Word16LE Word16BE where
  toLittleEndian :: Word16BE -> Word16LE
toLittleEndian = Word16 -> Word16LE
Word16LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16BE -> Word16
unWord16BE
  toBigEndian :: Word16LE -> Word16BE
toBigEndian = Word16 -> Word16BE
Word16BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word16LE -> Word16
unWord16LE

instance EndianPair Int16LE Int16BE where
  toLittleEndian :: Int16BE -> Int16LE
toLittleEndian = Int16 -> Int16LE
Int16LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16BE -> Int16
unInt16BE
  toBigEndian :: Int16LE -> Int16BE
toBigEndian = Int16 -> Int16BE
Int16BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int16LE -> Int16
unInt16LE

instance EndianPair Word24LE Word24BE where
  toLittleEndian :: Word24BE -> Word24LE
toLittleEndian = Word24 -> Word24LE
Word24LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word24BE -> Word24
unWord24BE
  toBigEndian :: Word24LE -> Word24BE
toBigEndian = Word24 -> Word24BE
Word24BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word24LE -> Word24
unWord24LE

instance EndianPair Int24LE Int24BE where
  toLittleEndian :: Int24BE -> Int24LE
toLittleEndian = Int24 -> Int24LE
Int24LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int24BE -> Int24
unInt24BE
  toBigEndian :: Int24LE -> Int24BE
toBigEndian = Int24 -> Int24BE
Int24BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int24LE -> Int24
unInt24LE

instance EndianPair Word32LE Word32BE where
  toLittleEndian :: Word32BE -> Word32LE
toLittleEndian = Word32 -> Word32LE
Word32LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32BE -> Word32
unWord32BE
  toBigEndian :: Word32LE -> Word32BE
toBigEndian = Word32 -> Word32BE
Word32BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word32LE -> Word32
unWord32LE

instance EndianPair Int32LE Int32BE where
  toLittleEndian :: Int32BE -> Int32LE
toLittleEndian = Int32 -> Int32LE
Int32LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32BE -> Int32
unInt32BE
  toBigEndian :: Int32LE -> Int32BE
toBigEndian = Int32 -> Int32BE
Int32BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int32LE -> Int32
unInt32LE

instance EndianPair Word64LE Word64BE where
  toLittleEndian :: Word64BE -> Word64LE
toLittleEndian = Word64 -> Word64LE
Word64LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64BE -> Word64
unWord64BE
  toBigEndian :: Word64LE -> Word64BE
toBigEndian = Word64 -> Word64BE
Word64BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Word64LE -> Word64
unWord64LE

instance EndianPair Int64LE Int64BE where
  toLittleEndian :: Int64BE -> Int64LE
toLittleEndian = Int64 -> Int64LE
Int64LE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64BE -> Int64
unInt64BE
  toBigEndian :: Int64LE -> Int64BE
toBigEndian = Int64 -> Int64BE
Int64BE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int64LE -> Int64
unInt64LE

instance EndianPair FloatLE FloatBE where
  toLittleEndian :: FloatBE -> FloatLE
toLittleEndian = Float -> FloatLE
FloatLE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. FloatBE -> Float
unFloatBE
  toBigEndian :: FloatLE -> FloatBE
toBigEndian = Float -> FloatBE
FloatBE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. FloatLE -> Float
unFloatLE

instance EndianPair DoubleLE DoubleBE where
  toLittleEndian :: DoubleBE -> DoubleLE
toLittleEndian = Double -> DoubleLE
DoubleLE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. DoubleBE -> Double
unDoubleBE
  toBigEndian :: DoubleLE -> DoubleBE
toBigEndian = Double -> DoubleBE
DoubleBE forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall w. SwapEndian w => w -> w
swapEndian forall b c a. (b -> c) -> (a -> b) -> a -> c
. DoubleLE -> Double
unDoubleLE