{-# OPTIONS_HADDOCK hide #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE TypeFamilies #-}
module Raaz.Core.Types.Endian
(
EndianStore(..), copyFromBytes, copyToBytes
, LE(..), BE(..), littleEndian, bigEndian
, storeAt, storeAtIndex
, loadFrom, loadFromIndex
) where
import Control.DeepSeq ( NFData)
import Data.Typeable
import Data.Vector.Unboxed ( MVector(..), Vector, Unbox )
import Foreign.Ptr ( castPtr )
import Foreign.Storable ( Storable, peek, poke )
import qualified Data.Vector.Generic as GV
import qualified Data.Vector.Generic.Mutable as GVM
import Raaz.Core.Prelude
import Raaz.Core.Types.Copying
import Raaz.Core.Types.Pointer
import Raaz.Core.Types.Equality
#ifndef __HLINT__
#include "MachDeps.h"
#endif
class Storable w => EndianStore w where
store :: Ptr w
-> w
-> IO ()
load :: Ptr w -> IO w
adjustEndian :: Ptr w
-> Int
-> IO ()
instance EndianStore () where
store :: Ptr () -> () -> IO ()
store = Ptr () -> () -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke
load :: Ptr () -> IO ()
load = Ptr () -> IO ()
forall a. Storable a => Ptr a -> IO a
peek
adjustEndian :: Ptr () -> Int -> IO ()
adjustEndian Ptr ()
_ Int
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
instance EndianStore Word8 where
store :: Ptr Word8 -> Word8 -> IO ()
store = Ptr Word8 -> Word8 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke
load :: Ptr Word8 -> IO Word8
load = Ptr Word8 -> IO Word8
forall a. Storable a => Ptr a -> IO a
peek
adjustEndian :: Ptr Word8 -> Int -> IO ()
adjustEndian Ptr Word8
_ Int
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
instance EndianStore w => EndianStore (BYTES w) where
store :: Ptr (BYTES w) -> BYTES w -> IO ()
store Ptr (BYTES w)
ptr (BYTES w
w) = Ptr w -> w -> IO ()
forall w. EndianStore w => Ptr w -> w -> IO ()
store (Ptr (BYTES w) -> Ptr w
forall a b. Ptr a -> Ptr b
castPtr Ptr (BYTES w)
ptr) w
w
load :: Ptr (BYTES w) -> IO (BYTES w)
load = (w -> BYTES w) -> IO w -> IO (BYTES w)
forall a b. (a -> b) -> IO a -> IO b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap w -> BYTES w
forall a. a -> BYTES a
BYTES (IO w -> IO (BYTES w))
-> (Ptr (BYTES w) -> IO w) -> Ptr (BYTES w) -> IO (BYTES w)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr w -> IO w
forall w. EndianStore w => Ptr w -> IO w
load (Ptr w -> IO w)
-> (Ptr (BYTES w) -> Ptr w) -> Ptr (BYTES w) -> IO w
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (BYTES w) -> Ptr w
forall a b. Ptr a -> Ptr b
castPtr
adjustEndian :: Ptr (BYTES w) -> Int -> IO ()
adjustEndian = Ptr w -> Int -> IO ()
forall w. EndianStore w => Ptr w -> Int -> IO ()
adjustEndian (Ptr w -> Int -> IO ())
-> (Ptr (BYTES w) -> Ptr w) -> Ptr (BYTES w) -> Int -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (BYTES w) -> Ptr w
forall w. Ptr (BYTES w) -> Ptr w
castToPtrW
where castToPtrW :: Ptr (BYTES w) -> Ptr w
castToPtrW :: forall w. Ptr (BYTES w) -> Ptr w
castToPtrW = Ptr (BYTES w) -> Ptr w
forall a b. Ptr a -> Ptr b
castPtr
storeAt :: ( EndianStore w
, LengthUnit offset
)
=> Ptr w
-> offset
-> w
-> IO ()
{-# INLINE storeAt #-}
storeAt :: forall w offset.
(EndianStore w, LengthUnit offset) =>
Ptr w -> offset -> w -> IO ()
storeAt Ptr w
ptr = Ptr w -> w -> IO ()
forall w. EndianStore w => Ptr w -> w -> IO ()
store (Ptr w -> w -> IO ()) -> (offset -> Ptr w) -> offset -> w -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr w -> offset -> Ptr w
forall l a. LengthUnit l => Ptr a -> l -> Ptr a
movePtr Ptr w
ptr
storeAtIndex :: EndianStore w
=> Ptr w
-> Int
-> w
-> IO ()
{-# INLINE storeAtIndex #-}
storeAtIndex :: forall w. EndianStore w => Ptr w -> Int -> w -> IO ()
storeAtIndex Ptr w
cptr Int
index w
w = Ptr w -> BYTES Int -> w -> IO ()
forall w offset.
(EndianStore w, LengthUnit offset) =>
Ptr w -> offset -> w -> IO ()
storeAt Ptr w
cptr BYTES Int
offset w
w
where offset :: BYTES Int
offset = Int -> BYTES Int
forall a. Enum a => Int -> a
toEnum Int
index BYTES Int -> BYTES Int -> BYTES Int
forall a. Num a => a -> a -> a
* Proxy w -> BYTES Int
forall a. Storable a => Proxy a -> BYTES Int
sizeOf (w -> Proxy w
forall a. a -> Proxy a
forall (f :: * -> *) a. Applicative f => a -> f a
pure w
w)
loadFromIndex :: EndianStore w
=> Ptr w
-> Int
-> IO w
{-# INLINE loadFromIndex #-}
loadFromIndex :: forall w. EndianStore w => Ptr w -> Int -> IO w
loadFromIndex Ptr w
cptr Int
index = Ptr w -> IO w
forall w. EndianStore w => Ptr w -> IO w
load (Ptr w -> IO w) -> Ptr w -> IO w
forall a b. (a -> b) -> a -> b
$ Ptr w -> Ptr w
forall w. Storable w => Ptr w -> Ptr w
shiftPtr Ptr w
cptr
where shiftPtr :: Storable w => Ptr w -> Ptr w
shiftPtr :: forall w. Storable w => Ptr w -> Ptr w
shiftPtr Ptr w
ptr = Ptr w -> BYTES Int -> Ptr w
forall l a. LengthUnit l => Ptr a -> l -> Ptr a
movePtr Ptr w
ptr (Int -> BYTES Int
forall a. Enum a => Int -> a
toEnum Int
index BYTES Int -> BYTES Int -> BYTES Int
forall a. Num a => a -> a -> a
* Proxy w -> BYTES Int
forall a. Storable a => Proxy a -> BYTES Int
sizeOf (Ptr w -> Proxy w
forall w. Ptr w -> Proxy w
getProxy Ptr w
ptr))
getProxy :: Ptr w -> Proxy w
getProxy :: forall w. Ptr w -> Proxy w
getProxy = Proxy w -> Ptr w -> Proxy w
forall a b. a -> b -> a
const Proxy w
forall {k} (t :: k). Proxy t
Proxy
loadFrom :: ( EndianStore w
, LengthUnit offset
)
=> Ptr w
-> offset
-> IO w
{-# INLINE loadFrom #-}
loadFrom :: forall w offset.
(EndianStore w, LengthUnit offset) =>
Ptr w -> offset -> IO w
loadFrom Ptr w
ptr = Ptr w -> IO w
forall w. EndianStore w => Ptr w -> IO w
load (Ptr w -> IO w) -> (offset -> Ptr w) -> offset -> IO w
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr w -> offset -> Ptr w
forall l a. LengthUnit l => Ptr a -> l -> Ptr a
movePtr Ptr w
ptr
copyFromBytes :: EndianStore w
=> Dest (Ptr w)
-> Src (Ptr Word8)
-> Int
-> IO ()
copyFromBytes :: forall w.
EndianStore w =>
Dest (Ptr w) -> Src (Ptr Word8) -> Int -> IO ()
copyFromBytes dest :: Dest (Ptr w)
dest@(Dest Ptr w
ptr) Src (Ptr Word8)
src Int
n = Dest (Ptr Any) -> Src (Ptr Word8) -> BYTES Int -> IO ()
forall l (ptrS :: * -> *) (ptrD :: * -> *) dest src.
(LengthUnit l, Pointer ptrS, Pointer ptrD) =>
Dest (ptrD dest) -> Src (ptrS src) -> l -> IO ()
memcpy (Ptr w -> Ptr Any
forall a b. Ptr a -> Ptr b
castPtr (Ptr w -> Ptr Any) -> Dest (Ptr w) -> Dest (Ptr Any)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Dest (Ptr w)
dest) Src (Ptr Word8)
src (Dest (Ptr w) -> Proxy w -> BYTES Int
forall w. Storable w => Dest (Ptr w) -> Proxy w -> BYTES Int
sz Dest (Ptr w)
dest Proxy w
forall {k} (t :: k). Proxy t
Proxy)
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Ptr w -> Int -> IO ()
forall w. EndianStore w => Ptr w -> Int -> IO ()
adjustEndian Ptr w
ptr Int
n
where sz :: Storable w => Dest (Ptr w) -> Proxy w -> BYTES Int
sz :: forall w. Storable w => Dest (Ptr w) -> Proxy w -> BYTES Int
sz Dest (Ptr w)
_ Proxy w
wProxy = Proxy w -> BYTES Int
forall a. Storable a => Proxy a -> BYTES Int
sizeOf Proxy w
wProxy BYTES Int -> BYTES Int -> BYTES Int
forall a. Num a => a -> a -> a
* Int -> BYTES Int
forall a. Enum a => Int -> a
toEnum Int
n
copyToBytes :: EndianStore w
=> Dest (Ptr Word8)
-> Src (Ptr w)
-> Int
-> IO ()
copyToBytes :: forall w.
EndianStore w =>
Dest (Ptr Word8) -> Src (Ptr w) -> Int -> IO ()
copyToBytes dest :: Dest (Ptr Word8)
dest@(Dest Ptr Word8
dptr) Src (Ptr w)
src Int
n = Dest (Ptr Word8) -> Src (Ptr Any) -> BYTES Int -> IO ()
forall l (ptrS :: * -> *) (ptrD :: * -> *) dest src.
(LengthUnit l, Pointer ptrS, Pointer ptrD) =>
Dest (ptrD dest) -> Src (ptrS src) -> l -> IO ()
memcpy Dest (Ptr Word8)
dest (Ptr w -> Ptr Any
forall a b. Ptr a -> Ptr b
castPtr (Ptr w -> Ptr Any) -> Src (Ptr w) -> Src (Ptr Any)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Src (Ptr w)
src) (Src (Ptr w) -> Proxy w -> BYTES Int
forall w. Storable w => Src (Ptr w) -> Proxy w -> BYTES Int
sz Src (Ptr w)
src Proxy w
forall a. HasCallStack => a
undefined)
IO () -> IO () -> IO ()
forall a b. IO a -> IO b -> IO b
forall (m :: * -> *) a b. Monad m => m a -> m b -> m b
>> Src (Ptr w) -> Ptr w -> IO ()
forall w. EndianStore w => Src (Ptr w) -> Ptr w -> IO ()
adjust Src (Ptr w)
src (Ptr Word8 -> Ptr w
forall a b. Ptr a -> Ptr b
castPtr Ptr Word8
dptr)
where adjust :: EndianStore w => Src (Ptr w) -> Ptr w -> IO ()
adjust :: forall w. EndianStore w => Src (Ptr w) -> Ptr w -> IO ()
adjust Src (Ptr w)
_ Ptr w
ptr = Ptr w -> Int -> IO ()
forall w. EndianStore w => Ptr w -> Int -> IO ()
adjustEndian Ptr w
ptr Int
n
sz :: Storable w => Src (Ptr w) -> Proxy w -> BYTES Int
sz :: forall w. Storable w => Src (Ptr w) -> Proxy w -> BYTES Int
sz Src (Ptr w)
_ Proxy w
w = Proxy w -> BYTES Int
forall a. Storable a => Proxy a -> BYTES Int
sizeOf Proxy w
w BYTES Int -> BYTES Int -> BYTES Int
forall a. Num a => a -> a -> a
* Int -> BYTES Int
forall a. Enum a => Int -> a
toEnum Int
n
newtype LE w = LE { forall w. LE w -> w
unLE :: w }
deriving ( LE w
LE w -> LE w -> Bounded (LE w)
forall a. a -> a -> Bounded a
forall w. Bounded w => LE w
$cminBound :: forall w. Bounded w => LE w
minBound :: LE w
$cmaxBound :: forall w. Bounded w => LE w
maxBound :: LE w
Bounded, Int -> LE w
LE w -> Int
LE w -> [LE w]
LE w -> LE w
LE w -> LE w -> [LE w]
LE w -> LE w -> LE w -> [LE w]
(LE w -> LE w)
-> (LE w -> LE w)
-> (Int -> LE w)
-> (LE w -> Int)
-> (LE w -> [LE w])
-> (LE w -> LE w -> [LE w])
-> (LE w -> LE w -> [LE w])
-> (LE w -> LE w -> LE w -> [LE w])
-> Enum (LE w)
forall w. Enum w => Int -> LE w
forall w. Enum w => LE w -> Int
forall w. Enum w => LE w -> [LE w]
forall w. Enum w => LE w -> LE w
forall w. Enum w => LE w -> LE w -> [LE w]
forall w. Enum w => LE w -> LE w -> LE w -> [LE w]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: forall w. Enum w => LE w -> LE w
succ :: LE w -> LE w
$cpred :: forall w. Enum w => LE w -> LE w
pred :: LE w -> LE w
$ctoEnum :: forall w. Enum w => Int -> LE w
toEnum :: Int -> LE w
$cfromEnum :: forall w. Enum w => LE w -> Int
fromEnum :: LE w -> Int
$cenumFrom :: forall w. Enum w => LE w -> [LE w]
enumFrom :: LE w -> [LE w]
$cenumFromThen :: forall w. Enum w => LE w -> LE w -> [LE w]
enumFromThen :: LE w -> LE w -> [LE w]
$cenumFromTo :: forall w. Enum w => LE w -> LE w -> [LE w]
enumFromTo :: LE w -> LE w -> [LE w]
$cenumFromThenTo :: forall w. Enum w => LE w -> LE w -> LE w -> [LE w]
enumFromThenTo :: LE w -> LE w -> LE w -> [LE w]
Enum, ReadPrec [LE w]
ReadPrec (LE w)
Int -> ReadS (LE w)
ReadS [LE w]
(Int -> ReadS (LE w))
-> ReadS [LE w]
-> ReadPrec (LE w)
-> ReadPrec [LE w]
-> Read (LE w)
forall w. Read w => ReadPrec [LE w]
forall w. Read w => ReadPrec (LE w)
forall w. Read w => Int -> ReadS (LE w)
forall w. Read w => ReadS [LE w]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall w. Read w => Int -> ReadS (LE w)
readsPrec :: Int -> ReadS (LE w)
$creadList :: forall w. Read w => ReadS [LE w]
readList :: ReadS [LE w]
$creadPrec :: forall w. Read w => ReadPrec (LE w)
readPrec :: ReadPrec (LE w)
$creadListPrec :: forall w. Read w => ReadPrec [LE w]
readListPrec :: ReadPrec [LE w]
Read, Int -> LE w -> ShowS
[LE w] -> ShowS
LE w -> String
(Int -> LE w -> ShowS)
-> (LE w -> String) -> ([LE w] -> ShowS) -> Show (LE w)
forall w. Show w => Int -> LE w -> ShowS
forall w. Show w => [LE w] -> ShowS
forall w. Show w => LE w -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall w. Show w => Int -> LE w -> ShowS
showsPrec :: Int -> LE w -> ShowS
$cshow :: forall w. Show w => LE w -> String
show :: LE w -> String
$cshowList :: forall w. Show w => [LE w] -> ShowS
showList :: [LE w] -> ShowS
Show
, Enum (LE w)
Real (LE w)
(Real (LE w), Enum (LE w)) =>
(LE w -> LE w -> LE w)
-> (LE w -> LE w -> LE w)
-> (LE w -> LE w -> LE w)
-> (LE w -> LE w -> LE w)
-> (LE w -> LE w -> (LE w, LE w))
-> (LE w -> LE w -> (LE w, LE w))
-> (LE w -> Integer)
-> Integral (LE w)
LE w -> Integer
LE w -> LE w -> (LE w, LE w)
LE w -> LE w -> LE w
forall w. Integral w => Enum (LE w)
forall w. Integral w => Real (LE w)
forall w. Integral w => LE w -> Integer
forall w. Integral w => LE w -> LE w -> (LE w, LE w)
forall w. Integral w => LE w -> LE w -> LE w
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: forall w. Integral w => LE w -> LE w -> LE w
quot :: LE w -> LE w -> LE w
$crem :: forall w. Integral w => LE w -> LE w -> LE w
rem :: LE w -> LE w -> LE w
$cdiv :: forall w. Integral w => LE w -> LE w -> LE w
div :: LE w -> LE w -> LE w
$cmod :: forall w. Integral w => LE w -> LE w -> LE w
mod :: LE w -> LE w -> LE w
$cquotRem :: forall w. Integral w => LE w -> LE w -> (LE w, LE w)
quotRem :: LE w -> LE w -> (LE w, LE w)
$cdivMod :: forall w. Integral w => LE w -> LE w -> (LE w, LE w)
divMod :: LE w -> LE w -> (LE w, LE w)
$ctoInteger :: forall w. Integral w => LE w -> Integer
toInteger :: LE w -> Integer
Integral, Integer -> LE w
LE w -> LE w
LE w -> LE w -> LE w
(LE w -> LE w -> LE w)
-> (LE w -> LE w -> LE w)
-> (LE w -> LE w -> LE w)
-> (LE w -> LE w)
-> (LE w -> LE w)
-> (LE w -> LE w)
-> (Integer -> LE w)
-> Num (LE w)
forall w. Num w => Integer -> LE w
forall w. Num w => LE w -> LE w
forall w. Num w => LE w -> LE w -> LE w
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: forall w. Num w => LE w -> LE w -> LE w
+ :: LE w -> LE w -> LE w
$c- :: forall w. Num w => LE w -> LE w -> LE w
- :: LE w -> LE w -> LE w
$c* :: forall w. Num w => LE w -> LE w -> LE w
* :: LE w -> LE w -> LE w
$cnegate :: forall w. Num w => LE w -> LE w
negate :: LE w -> LE w
$cabs :: forall w. Num w => LE w -> LE w
abs :: LE w -> LE w
$csignum :: forall w. Num w => LE w -> LE w
signum :: LE w -> LE w
$cfromInteger :: forall w. Num w => Integer -> LE w
fromInteger :: Integer -> LE w
Num, Num (LE w)
Ord (LE w)
(Num (LE w), Ord (LE w)) => (LE w -> Rational) -> Real (LE w)
LE w -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
forall w. Real w => Num (LE w)
forall w. Real w => Ord (LE w)
forall w. Real w => LE w -> Rational
$ctoRational :: forall w. Real w => LE w -> Rational
toRational :: LE w -> Rational
Real, LE w -> LE w -> Bool
(LE w -> LE w -> Bool) -> (LE w -> LE w -> Bool) -> Eq (LE w)
forall w. Eq w => LE w -> LE w -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall w. Eq w => LE w -> LE w -> Bool
== :: LE w -> LE w -> Bool
$c/= :: forall w. Eq w => LE w -> LE w -> Bool
/= :: LE w -> LE w -> Bool
Eq, LE w -> LE w -> Result
(LE w -> LE w -> Result) -> Equality (LE w)
forall w. Equality w => LE w -> LE w -> Result
forall a. (a -> a -> Result) -> Equality a
$ceq :: forall w. Equality w => LE w -> LE w -> Result
eq :: LE w -> LE w -> Result
Equality, Eq (LE w)
Eq (LE w) =>
(LE w -> LE w -> Ordering)
-> (LE w -> LE w -> Bool)
-> (LE w -> LE w -> Bool)
-> (LE w -> LE w -> Bool)
-> (LE w -> LE w -> Bool)
-> (LE w -> LE w -> LE w)
-> (LE w -> LE w -> LE w)
-> Ord (LE w)
LE w -> LE w -> Bool
LE w -> LE w -> Ordering
LE w -> LE w -> LE w
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
forall w. Ord w => Eq (LE w)
forall w. Ord w => LE w -> LE w -> Bool
forall w. Ord w => LE w -> LE w -> Ordering
forall w. Ord w => LE w -> LE w -> LE w
$ccompare :: forall w. Ord w => LE w -> LE w -> Ordering
compare :: LE w -> LE w -> Ordering
$c< :: forall w. Ord w => LE w -> LE w -> Bool
< :: LE w -> LE w -> Bool
$c<= :: forall w. Ord w => LE w -> LE w -> Bool
<= :: LE w -> LE w -> Bool
$c> :: forall w. Ord w => LE w -> LE w -> Bool
> :: LE w -> LE w -> Bool
$c>= :: forall w. Ord w => LE w -> LE w -> Bool
>= :: LE w -> LE w -> Bool
$cmax :: forall w. Ord w => LE w -> LE w -> LE w
max :: LE w -> LE w -> LE w
$cmin :: forall w. Ord w => LE w -> LE w -> LE w
min :: LE w -> LE w -> LE w
Ord
, Eq (LE w)
LE w
Eq (LE w) =>
(LE w -> LE w -> LE w)
-> (LE w -> LE w -> LE w)
-> (LE w -> LE w -> LE w)
-> (LE w -> LE w)
-> (LE w -> Int -> LE w)
-> (LE w -> Int -> LE w)
-> LE w
-> (Int -> LE w)
-> (LE w -> Int -> LE w)
-> (LE w -> Int -> LE w)
-> (LE w -> Int -> LE w)
-> (LE w -> Int -> Bool)
-> (LE w -> Maybe Int)
-> (LE w -> Int)
-> (LE w -> Bool)
-> (LE w -> Int -> LE w)
-> (LE w -> Int -> LE w)
-> (LE w -> Int -> LE w)
-> (LE w -> Int -> LE w)
-> (LE w -> Int -> LE w)
-> (LE w -> Int -> LE w)
-> (LE w -> Int)
-> Bits (LE w)
Int -> LE w
LE w -> Bool
LE w -> Int
LE w -> Maybe Int
LE w -> LE w
LE w -> Int -> Bool
LE w -> Int -> LE w
LE w -> LE w -> LE w
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
forall w. Bits w => Eq (LE w)
forall w. Bits w => LE w
forall w. Bits w => Int -> LE w
forall w. Bits w => LE w -> Bool
forall w. Bits w => LE w -> Int
forall w. Bits w => LE w -> Maybe Int
forall w. Bits w => LE w -> LE w
forall w. Bits w => LE w -> Int -> Bool
forall w. Bits w => LE w -> Int -> LE w
forall w. Bits w => LE w -> LE w -> LE w
$c.&. :: forall w. Bits w => LE w -> LE w -> LE w
.&. :: LE w -> LE w -> LE w
$c.|. :: forall w. Bits w => LE w -> LE w -> LE w
.|. :: LE w -> LE w -> LE w
$cxor :: forall w. Bits w => LE w -> LE w -> LE w
xor :: LE w -> LE w -> LE w
$ccomplement :: forall w. Bits w => LE w -> LE w
complement :: LE w -> LE w
$cshift :: forall w. Bits w => LE w -> Int -> LE w
shift :: LE w -> Int -> LE w
$crotate :: forall w. Bits w => LE w -> Int -> LE w
rotate :: LE w -> Int -> LE w
$czeroBits :: forall w. Bits w => LE w
zeroBits :: LE w
$cbit :: forall w. Bits w => Int -> LE w
bit :: Int -> LE w
$csetBit :: forall w. Bits w => LE w -> Int -> LE w
setBit :: LE w -> Int -> LE w
$cclearBit :: forall w. Bits w => LE w -> Int -> LE w
clearBit :: LE w -> Int -> LE w
$ccomplementBit :: forall w. Bits w => LE w -> Int -> LE w
complementBit :: LE w -> Int -> LE w
$ctestBit :: forall w. Bits w => LE w -> Int -> Bool
testBit :: LE w -> Int -> Bool
$cbitSizeMaybe :: forall w. Bits w => LE w -> Maybe Int
bitSizeMaybe :: LE w -> Maybe Int
$cbitSize :: forall w. Bits w => LE w -> Int
bitSize :: LE w -> Int
$cisSigned :: forall w. Bits w => LE w -> Bool
isSigned :: LE w -> Bool
$cshiftL :: forall w. Bits w => LE w -> Int -> LE w
shiftL :: LE w -> Int -> LE w
$cunsafeShiftL :: forall w. Bits w => LE w -> Int -> LE w
unsafeShiftL :: LE w -> Int -> LE w
$cshiftR :: forall w. Bits w => LE w -> Int -> LE w
shiftR :: LE w -> Int -> LE w
$cunsafeShiftR :: forall w. Bits w => LE w -> Int -> LE w
unsafeShiftR :: LE w -> Int -> LE w
$crotateL :: forall w. Bits w => LE w -> Int -> LE w
rotateL :: LE w -> Int -> LE w
$crotateR :: forall w. Bits w => LE w -> Int -> LE w
rotateR :: LE w -> Int -> LE w
$cpopCount :: forall w. Bits w => LE w -> Int
popCount :: LE w -> Int
Bits, Ptr (LE w) -> IO (LE w)
Ptr (LE w) -> Int -> IO (LE w)
Ptr (LE w) -> Int -> LE w -> IO ()
Ptr (LE w) -> LE w -> IO ()
LE w -> Int
(LE w -> Int)
-> (LE w -> Int)
-> (Ptr (LE w) -> Int -> IO (LE w))
-> (Ptr (LE w) -> Int -> LE w -> IO ())
-> (forall b. Ptr b -> Int -> IO (LE w))
-> (forall b. Ptr b -> Int -> LE w -> IO ())
-> (Ptr (LE w) -> IO (LE w))
-> (Ptr (LE w) -> LE w -> IO ())
-> Storable (LE w)
forall b. Ptr b -> Int -> IO (LE w)
forall b. Ptr b -> Int -> LE w -> IO ()
forall w. Storable w => Ptr (LE w) -> IO (LE w)
forall w. Storable w => Ptr (LE w) -> Int -> IO (LE w)
forall w. Storable w => Ptr (LE w) -> Int -> LE w -> IO ()
forall w. Storable w => Ptr (LE w) -> LE w -> IO ()
forall w. Storable w => LE w -> Int
forall w b. Storable w => Ptr b -> Int -> IO (LE w)
forall w b. Storable w => Ptr b -> Int -> LE w -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: forall w. Storable w => LE w -> Int
sizeOf :: LE w -> Int
$calignment :: forall w. Storable w => LE w -> Int
alignment :: LE w -> Int
$cpeekElemOff :: forall w. Storable w => Ptr (LE w) -> Int -> IO (LE w)
peekElemOff :: Ptr (LE w) -> Int -> IO (LE w)
$cpokeElemOff :: forall w. Storable w => Ptr (LE w) -> Int -> LE w -> IO ()
pokeElemOff :: Ptr (LE w) -> Int -> LE w -> IO ()
$cpeekByteOff :: forall w b. Storable w => Ptr b -> Int -> IO (LE w)
peekByteOff :: forall b. Ptr b -> Int -> IO (LE w)
$cpokeByteOff :: forall w b. Storable w => Ptr b -> Int -> LE w -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> LE w -> IO ()
$cpeek :: forall w. Storable w => Ptr (LE w) -> IO (LE w)
peek :: Ptr (LE w) -> IO (LE w)
$cpoke :: forall w. Storable w => Ptr (LE w) -> LE w -> IO ()
poke :: Ptr (LE w) -> LE w -> IO ()
Storable, Typeable, LE w -> ()
(LE w -> ()) -> NFData (LE w)
forall w. NFData w => LE w -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall w. NFData w => LE w -> ()
rnf :: LE w -> ()
NFData
)
instance Functor LE where
fmap :: forall a b. (a -> b) -> LE a -> LE b
fmap a -> b
f = b -> LE b
forall w. w -> LE w
LE (b -> LE b) -> (LE a -> b) -> LE a -> LE b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f (a -> b) -> (LE a -> a) -> LE a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LE a -> a
forall w. LE w -> w
unLE
newtype BE w = BE { forall w. BE w -> w
unBE :: w }
deriving ( BE w
BE w -> BE w -> Bounded (BE w)
forall a. a -> a -> Bounded a
forall w. Bounded w => BE w
$cminBound :: forall w. Bounded w => BE w
minBound :: BE w
$cmaxBound :: forall w. Bounded w => BE w
maxBound :: BE w
Bounded, Int -> BE w
BE w -> Int
BE w -> [BE w]
BE w -> BE w
BE w -> BE w -> [BE w]
BE w -> BE w -> BE w -> [BE w]
(BE w -> BE w)
-> (BE w -> BE w)
-> (Int -> BE w)
-> (BE w -> Int)
-> (BE w -> [BE w])
-> (BE w -> BE w -> [BE w])
-> (BE w -> BE w -> [BE w])
-> (BE w -> BE w -> BE w -> [BE w])
-> Enum (BE w)
forall w. Enum w => Int -> BE w
forall w. Enum w => BE w -> Int
forall w. Enum w => BE w -> [BE w]
forall w. Enum w => BE w -> BE w
forall w. Enum w => BE w -> BE w -> [BE w]
forall w. Enum w => BE w -> BE w -> BE w -> [BE w]
forall a.
(a -> a)
-> (a -> a)
-> (Int -> a)
-> (a -> Int)
-> (a -> [a])
-> (a -> a -> [a])
-> (a -> a -> [a])
-> (a -> a -> a -> [a])
-> Enum a
$csucc :: forall w. Enum w => BE w -> BE w
succ :: BE w -> BE w
$cpred :: forall w. Enum w => BE w -> BE w
pred :: BE w -> BE w
$ctoEnum :: forall w. Enum w => Int -> BE w
toEnum :: Int -> BE w
$cfromEnum :: forall w. Enum w => BE w -> Int
fromEnum :: BE w -> Int
$cenumFrom :: forall w. Enum w => BE w -> [BE w]
enumFrom :: BE w -> [BE w]
$cenumFromThen :: forall w. Enum w => BE w -> BE w -> [BE w]
enumFromThen :: BE w -> BE w -> [BE w]
$cenumFromTo :: forall w. Enum w => BE w -> BE w -> [BE w]
enumFromTo :: BE w -> BE w -> [BE w]
$cenumFromThenTo :: forall w. Enum w => BE w -> BE w -> BE w -> [BE w]
enumFromThenTo :: BE w -> BE w -> BE w -> [BE w]
Enum, ReadPrec [BE w]
ReadPrec (BE w)
Int -> ReadS (BE w)
ReadS [BE w]
(Int -> ReadS (BE w))
-> ReadS [BE w]
-> ReadPrec (BE w)
-> ReadPrec [BE w]
-> Read (BE w)
forall w. Read w => ReadPrec [BE w]
forall w. Read w => ReadPrec (BE w)
forall w. Read w => Int -> ReadS (BE w)
forall w. Read w => ReadS [BE w]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
$creadsPrec :: forall w. Read w => Int -> ReadS (BE w)
readsPrec :: Int -> ReadS (BE w)
$creadList :: forall w. Read w => ReadS [BE w]
readList :: ReadS [BE w]
$creadPrec :: forall w. Read w => ReadPrec (BE w)
readPrec :: ReadPrec (BE w)
$creadListPrec :: forall w. Read w => ReadPrec [BE w]
readListPrec :: ReadPrec [BE w]
Read, Int -> BE w -> ShowS
[BE w] -> ShowS
BE w -> String
(Int -> BE w -> ShowS)
-> (BE w -> String) -> ([BE w] -> ShowS) -> Show (BE w)
forall w. Show w => Int -> BE w -> ShowS
forall w. Show w => [BE w] -> ShowS
forall w. Show w => BE w -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
$cshowsPrec :: forall w. Show w => Int -> BE w -> ShowS
showsPrec :: Int -> BE w -> ShowS
$cshow :: forall w. Show w => BE w -> String
show :: BE w -> String
$cshowList :: forall w. Show w => [BE w] -> ShowS
showList :: [BE w] -> ShowS
Show
, Enum (BE w)
Real (BE w)
(Real (BE w), Enum (BE w)) =>
(BE w -> BE w -> BE w)
-> (BE w -> BE w -> BE w)
-> (BE w -> BE w -> BE w)
-> (BE w -> BE w -> BE w)
-> (BE w -> BE w -> (BE w, BE w))
-> (BE w -> BE w -> (BE w, BE w))
-> (BE w -> Integer)
-> Integral (BE w)
BE w -> Integer
BE w -> BE w -> (BE w, BE w)
BE w -> BE w -> BE w
forall w. Integral w => Enum (BE w)
forall w. Integral w => Real (BE w)
forall w. Integral w => BE w -> Integer
forall w. Integral w => BE w -> BE w -> (BE w, BE w)
forall w. Integral w => BE w -> BE w -> BE w
forall a.
(Real a, Enum a) =>
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> (a, a))
-> (a -> a -> (a, a))
-> (a -> Integer)
-> Integral a
$cquot :: forall w. Integral w => BE w -> BE w -> BE w
quot :: BE w -> BE w -> BE w
$crem :: forall w. Integral w => BE w -> BE w -> BE w
rem :: BE w -> BE w -> BE w
$cdiv :: forall w. Integral w => BE w -> BE w -> BE w
div :: BE w -> BE w -> BE w
$cmod :: forall w. Integral w => BE w -> BE w -> BE w
mod :: BE w -> BE w -> BE w
$cquotRem :: forall w. Integral w => BE w -> BE w -> (BE w, BE w)
quotRem :: BE w -> BE w -> (BE w, BE w)
$cdivMod :: forall w. Integral w => BE w -> BE w -> (BE w, BE w)
divMod :: BE w -> BE w -> (BE w, BE w)
$ctoInteger :: forall w. Integral w => BE w -> Integer
toInteger :: BE w -> Integer
Integral, Integer -> BE w
BE w -> BE w
BE w -> BE w -> BE w
(BE w -> BE w -> BE w)
-> (BE w -> BE w -> BE w)
-> (BE w -> BE w -> BE w)
-> (BE w -> BE w)
-> (BE w -> BE w)
-> (BE w -> BE w)
-> (Integer -> BE w)
-> Num (BE w)
forall w. Num w => Integer -> BE w
forall w. Num w => BE w -> BE w
forall w. Num w => BE w -> BE w -> BE w
forall a.
(a -> a -> a)
-> (a -> a -> a)
-> (a -> a -> a)
-> (a -> a)
-> (a -> a)
-> (a -> a)
-> (Integer -> a)
-> Num a
$c+ :: forall w. Num w => BE w -> BE w -> BE w
+ :: BE w -> BE w -> BE w
$c- :: forall w. Num w => BE w -> BE w -> BE w
- :: BE w -> BE w -> BE w
$c* :: forall w. Num w => BE w -> BE w -> BE w
* :: BE w -> BE w -> BE w
$cnegate :: forall w. Num w => BE w -> BE w
negate :: BE w -> BE w
$cabs :: forall w. Num w => BE w -> BE w
abs :: BE w -> BE w
$csignum :: forall w. Num w => BE w -> BE w
signum :: BE w -> BE w
$cfromInteger :: forall w. Num w => Integer -> BE w
fromInteger :: Integer -> BE w
Num, Num (BE w)
Ord (BE w)
(Num (BE w), Ord (BE w)) => (BE w -> Rational) -> Real (BE w)
BE w -> Rational
forall a. (Num a, Ord a) => (a -> Rational) -> Real a
forall w. Real w => Num (BE w)
forall w. Real w => Ord (BE w)
forall w. Real w => BE w -> Rational
$ctoRational :: forall w. Real w => BE w -> Rational
toRational :: BE w -> Rational
Real, BE w -> BE w -> Bool
(BE w -> BE w -> Bool) -> (BE w -> BE w -> Bool) -> Eq (BE w)
forall w. Eq w => BE w -> BE w -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall w. Eq w => BE w -> BE w -> Bool
== :: BE w -> BE w -> Bool
$c/= :: forall w. Eq w => BE w -> BE w -> Bool
/= :: BE w -> BE w -> Bool
Eq, BE w -> BE w -> Result
(BE w -> BE w -> Result) -> Equality (BE w)
forall w. Equality w => BE w -> BE w -> Result
forall a. (a -> a -> Result) -> Equality a
$ceq :: forall w. Equality w => BE w -> BE w -> Result
eq :: BE w -> BE w -> Result
Equality, Eq (BE w)
Eq (BE w) =>
(BE w -> BE w -> Ordering)
-> (BE w -> BE w -> Bool)
-> (BE w -> BE w -> Bool)
-> (BE w -> BE w -> Bool)
-> (BE w -> BE w -> Bool)
-> (BE w -> BE w -> BE w)
-> (BE w -> BE w -> BE w)
-> Ord (BE w)
BE w -> BE w -> Bool
BE w -> BE w -> Ordering
BE w -> BE w -> BE w
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
forall w. Ord w => Eq (BE w)
forall w. Ord w => BE w -> BE w -> Bool
forall w. Ord w => BE w -> BE w -> Ordering
forall w. Ord w => BE w -> BE w -> BE w
$ccompare :: forall w. Ord w => BE w -> BE w -> Ordering
compare :: BE w -> BE w -> Ordering
$c< :: forall w. Ord w => BE w -> BE w -> Bool
< :: BE w -> BE w -> Bool
$c<= :: forall w. Ord w => BE w -> BE w -> Bool
<= :: BE w -> BE w -> Bool
$c> :: forall w. Ord w => BE w -> BE w -> Bool
> :: BE w -> BE w -> Bool
$c>= :: forall w. Ord w => BE w -> BE w -> Bool
>= :: BE w -> BE w -> Bool
$cmax :: forall w. Ord w => BE w -> BE w -> BE w
max :: BE w -> BE w -> BE w
$cmin :: forall w. Ord w => BE w -> BE w -> BE w
min :: BE w -> BE w -> BE w
Ord
, Eq (BE w)
BE w
Eq (BE w) =>
(BE w -> BE w -> BE w)
-> (BE w -> BE w -> BE w)
-> (BE w -> BE w -> BE w)
-> (BE w -> BE w)
-> (BE w -> Int -> BE w)
-> (BE w -> Int -> BE w)
-> BE w
-> (Int -> BE w)
-> (BE w -> Int -> BE w)
-> (BE w -> Int -> BE w)
-> (BE w -> Int -> BE w)
-> (BE w -> Int -> Bool)
-> (BE w -> Maybe Int)
-> (BE w -> Int)
-> (BE w -> Bool)
-> (BE w -> Int -> BE w)
-> (BE w -> Int -> BE w)
-> (BE w -> Int -> BE w)
-> (BE w -> Int -> BE w)
-> (BE w -> Int -> BE w)
-> (BE w -> Int -> BE w)
-> (BE w -> Int)
-> Bits (BE w)
Int -> BE w
BE w -> Bool
BE w -> Int
BE w -> Maybe Int
BE w -> BE w
BE w -> Int -> Bool
BE w -> Int -> BE w
BE w -> BE w -> BE w
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
forall w. Bits w => Eq (BE w)
forall w. Bits w => BE w
forall w. Bits w => Int -> BE w
forall w. Bits w => BE w -> Bool
forall w. Bits w => BE w -> Int
forall w. Bits w => BE w -> Maybe Int
forall w. Bits w => BE w -> BE w
forall w. Bits w => BE w -> Int -> Bool
forall w. Bits w => BE w -> Int -> BE w
forall w. Bits w => BE w -> BE w -> BE w
$c.&. :: forall w. Bits w => BE w -> BE w -> BE w
.&. :: BE w -> BE w -> BE w
$c.|. :: forall w. Bits w => BE w -> BE w -> BE w
.|. :: BE w -> BE w -> BE w
$cxor :: forall w. Bits w => BE w -> BE w -> BE w
xor :: BE w -> BE w -> BE w
$ccomplement :: forall w. Bits w => BE w -> BE w
complement :: BE w -> BE w
$cshift :: forall w. Bits w => BE w -> Int -> BE w
shift :: BE w -> Int -> BE w
$crotate :: forall w. Bits w => BE w -> Int -> BE w
rotate :: BE w -> Int -> BE w
$czeroBits :: forall w. Bits w => BE w
zeroBits :: BE w
$cbit :: forall w. Bits w => Int -> BE w
bit :: Int -> BE w
$csetBit :: forall w. Bits w => BE w -> Int -> BE w
setBit :: BE w -> Int -> BE w
$cclearBit :: forall w. Bits w => BE w -> Int -> BE w
clearBit :: BE w -> Int -> BE w
$ccomplementBit :: forall w. Bits w => BE w -> Int -> BE w
complementBit :: BE w -> Int -> BE w
$ctestBit :: forall w. Bits w => BE w -> Int -> Bool
testBit :: BE w -> Int -> Bool
$cbitSizeMaybe :: forall w. Bits w => BE w -> Maybe Int
bitSizeMaybe :: BE w -> Maybe Int
$cbitSize :: forall w. Bits w => BE w -> Int
bitSize :: BE w -> Int
$cisSigned :: forall w. Bits w => BE w -> Bool
isSigned :: BE w -> Bool
$cshiftL :: forall w. Bits w => BE w -> Int -> BE w
shiftL :: BE w -> Int -> BE w
$cunsafeShiftL :: forall w. Bits w => BE w -> Int -> BE w
unsafeShiftL :: BE w -> Int -> BE w
$cshiftR :: forall w. Bits w => BE w -> Int -> BE w
shiftR :: BE w -> Int -> BE w
$cunsafeShiftR :: forall w. Bits w => BE w -> Int -> BE w
unsafeShiftR :: BE w -> Int -> BE w
$crotateL :: forall w. Bits w => BE w -> Int -> BE w
rotateL :: BE w -> Int -> BE w
$crotateR :: forall w. Bits w => BE w -> Int -> BE w
rotateR :: BE w -> Int -> BE w
$cpopCount :: forall w. Bits w => BE w -> Int
popCount :: BE w -> Int
Bits, Ptr (BE w) -> IO (BE w)
Ptr (BE w) -> Int -> IO (BE w)
Ptr (BE w) -> Int -> BE w -> IO ()
Ptr (BE w) -> BE w -> IO ()
BE w -> Int
(BE w -> Int)
-> (BE w -> Int)
-> (Ptr (BE w) -> Int -> IO (BE w))
-> (Ptr (BE w) -> Int -> BE w -> IO ())
-> (forall b. Ptr b -> Int -> IO (BE w))
-> (forall b. Ptr b -> Int -> BE w -> IO ())
-> (Ptr (BE w) -> IO (BE w))
-> (Ptr (BE w) -> BE w -> IO ())
-> Storable (BE w)
forall b. Ptr b -> Int -> IO (BE w)
forall b. Ptr b -> Int -> BE w -> IO ()
forall w. Storable w => Ptr (BE w) -> IO (BE w)
forall w. Storable w => Ptr (BE w) -> Int -> IO (BE w)
forall w. Storable w => Ptr (BE w) -> Int -> BE w -> IO ()
forall w. Storable w => Ptr (BE w) -> BE w -> IO ()
forall w. Storable w => BE w -> Int
forall w b. Storable w => Ptr b -> Int -> IO (BE w)
forall w b. Storable w => Ptr b -> Int -> BE w -> IO ()
forall a.
(a -> Int)
-> (a -> Int)
-> (Ptr a -> Int -> IO a)
-> (Ptr a -> Int -> a -> IO ())
-> (forall b. Ptr b -> Int -> IO a)
-> (forall b. Ptr b -> Int -> a -> IO ())
-> (Ptr a -> IO a)
-> (Ptr a -> a -> IO ())
-> Storable a
$csizeOf :: forall w. Storable w => BE w -> Int
sizeOf :: BE w -> Int
$calignment :: forall w. Storable w => BE w -> Int
alignment :: BE w -> Int
$cpeekElemOff :: forall w. Storable w => Ptr (BE w) -> Int -> IO (BE w)
peekElemOff :: Ptr (BE w) -> Int -> IO (BE w)
$cpokeElemOff :: forall w. Storable w => Ptr (BE w) -> Int -> BE w -> IO ()
pokeElemOff :: Ptr (BE w) -> Int -> BE w -> IO ()
$cpeekByteOff :: forall w b. Storable w => Ptr b -> Int -> IO (BE w)
peekByteOff :: forall b. Ptr b -> Int -> IO (BE w)
$cpokeByteOff :: forall w b. Storable w => Ptr b -> Int -> BE w -> IO ()
pokeByteOff :: forall b. Ptr b -> Int -> BE w -> IO ()
$cpeek :: forall w. Storable w => Ptr (BE w) -> IO (BE w)
peek :: Ptr (BE w) -> IO (BE w)
$cpoke :: forall w. Storable w => Ptr (BE w) -> BE w -> IO ()
poke :: Ptr (BE w) -> BE w -> IO ()
Storable, Typeable, BE w -> ()
(BE w -> ()) -> NFData (BE w)
forall w. NFData w => BE w -> ()
forall a. (a -> ()) -> NFData a
$crnf :: forall w. NFData w => BE w -> ()
rnf :: BE w -> ()
NFData
)
instance Functor BE where
fmap :: forall a b. (a -> b) -> BE a -> BE b
fmap a -> b
f = b -> BE b
forall w. w -> BE w
BE (b -> BE b) -> (BE a -> b) -> BE a -> BE b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> b
f (a -> b) -> (BE a -> a) -> BE a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. BE a -> a
forall w. BE w -> w
unBE
littleEndian :: w -> LE w
{-# INLINE littleEndian #-}
littleEndian :: forall w. w -> LE w
littleEndian = w -> LE w
forall w. w -> LE w
LE
bigEndian :: w -> BE w
{-# INLINE bigEndian #-}
bigEndian :: forall w. w -> BE w
bigEndian = w -> BE w
forall w. w -> BE w
BE
foreign import ccall unsafe "raaz/core/endian.h raazSwap32Array"
c_Swap32Array :: Ptr Word32 -> Int -> IO ()
foreign import ccall unsafe "raaz/core/endian.h raazSwap64Array"
c_Swap64Array :: Ptr Word64 -> Int -> IO ()
#ifdef WORDS_BIGENDIAN
unLEPtr :: Ptr (LE w) -> Ptr w
unLEPtr = castPtr
instance EndianStore (LE Word32) where
load ptr = fmap byteSwap32 <$> peek ptr
store ptr = poke ptr . fmap byteSwap32
adjustEndian = c_Swap32Array . unLEPtr
instance EndianStore (LE Word64) where
load ptr = fmap byteSwap64 <$> peek ptr
store ptr = poke ptr . fmap byteSwap64
adjustEndian = c_Swap64Array . unLEPtr
instance EndianStore (BE Word32) where
load = peek
store = poke
adjustEndian _ _ = return ()
instance EndianStore (BE Word64) where
load = peek
store = poke
adjustEndian _ _ = return ()
# else
unBEPtr :: Ptr (BE w) -> Ptr w
unBEPtr :: forall w. Ptr (BE w) -> Ptr w
unBEPtr = Ptr (BE w) -> Ptr w
forall a b. Ptr a -> Ptr b
castPtr
instance EndianStore (BE Word32) where
load :: Ptr (BE Word32) -> IO (BE Word32)
load Ptr (BE Word32)
ptr = (Word32 -> Word32) -> BE Word32 -> BE Word32
forall a b. (a -> b) -> BE a -> BE b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> Word32
byteSwap32 (BE Word32 -> BE Word32) -> IO (BE Word32) -> IO (BE Word32)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr (BE Word32) -> IO (BE Word32)
forall a. Storable a => Ptr a -> IO a
peek Ptr (BE Word32)
ptr
store :: Ptr (BE Word32) -> BE Word32 -> IO ()
store Ptr (BE Word32)
ptr = Ptr (BE Word32) -> BE Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (BE Word32)
ptr (BE Word32 -> IO ())
-> (BE Word32 -> BE Word32) -> BE Word32 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word32 -> Word32) -> BE Word32 -> BE Word32
forall a b. (a -> b) -> BE a -> BE b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word32 -> Word32
byteSwap32
adjustEndian :: Ptr (BE Word32) -> Int -> IO ()
adjustEndian = Ptr Word32 -> Int -> IO ()
c_Swap32Array (Ptr Word32 -> Int -> IO ())
-> (Ptr (BE Word32) -> Ptr Word32)
-> Ptr (BE Word32)
-> Int
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (BE Word32) -> Ptr Word32
forall w. Ptr (BE w) -> Ptr w
unBEPtr
instance EndianStore (BE Word64) where
load :: Ptr (BE Word64) -> IO (BE Word64)
load Ptr (BE Word64)
ptr = (Word64 -> Word64) -> BE Word64 -> BE Word64
forall a b. (a -> b) -> BE a -> BE b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word64 -> Word64
byteSwap64 (BE Word64 -> BE Word64) -> IO (BE Word64) -> IO (BE Word64)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Ptr (BE Word64) -> IO (BE Word64)
forall a. Storable a => Ptr a -> IO a
peek Ptr (BE Word64)
ptr
store :: Ptr (BE Word64) -> BE Word64 -> IO ()
store Ptr (BE Word64)
ptr = Ptr (BE Word64) -> BE Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr (BE Word64)
ptr (BE Word64 -> IO ())
-> (BE Word64 -> BE Word64) -> BE Word64 -> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Word64 -> Word64) -> BE Word64 -> BE Word64
forall a b. (a -> b) -> BE a -> BE b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Word64 -> Word64
byteSwap64
adjustEndian :: Ptr (BE Word64) -> Int -> IO ()
adjustEndian = Ptr Word64 -> Int -> IO ()
c_Swap64Array (Ptr Word64 -> Int -> IO ())
-> (Ptr (BE Word64) -> Ptr Word64)
-> Ptr (BE Word64)
-> Int
-> IO ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Ptr (BE Word64) -> Ptr Word64
forall w. Ptr (BE w) -> Ptr w
unBEPtr
instance EndianStore (LE Word32) where
load :: Ptr (LE Word32) -> IO (LE Word32)
load = Ptr (LE Word32) -> IO (LE Word32)
forall a. Storable a => Ptr a -> IO a
peek
store :: Ptr (LE Word32) -> LE Word32 -> IO ()
store = Ptr (LE Word32) -> LE Word32 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke
adjustEndian :: Ptr (LE Word32) -> Int -> IO ()
adjustEndian Ptr (LE Word32)
_ Int
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
instance EndianStore (LE Word64) where
load :: Ptr (LE Word64) -> IO (LE Word64)
load = Ptr (LE Word64) -> IO (LE Word64)
forall a. Storable a => Ptr a -> IO a
peek
store :: Ptr (LE Word64) -> LE Word64 -> IO ()
store = Ptr (LE Word64) -> LE Word64 -> IO ()
forall a. Storable a => Ptr a -> a -> IO ()
poke
adjustEndian :: Ptr (LE Word64) -> Int -> IO ()
adjustEndian Ptr (LE Word64)
_ Int
_ = () -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return ()
#endif
instance Unbox w => Unbox (LE w)
instance Unbox w => Unbox (BE w)
newtype instance MVector s (LE w) = MV_LE (MVector s w)
newtype instance Vector (LE w) = V_LE (Vector w)
newtype instance MVector s (BE w) = MV_BE (MVector s w)
newtype instance Vector (BE w) = V_BE (Vector w)
instance Unbox w => GVM.MVector MVector (LE w) where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicOverlaps #-}
{-# INLINE basicUnsafeNew #-}
{-# INLINE basicUnsafeReplicate #-}
{-# INLINE basicUnsafeRead #-}
{-# INLINE basicUnsafeWrite #-}
{-# INLINE basicClear #-}
{-# INLINE basicSet #-}
{-# INLINE basicUnsafeCopy #-}
{-# INLINE basicUnsafeGrow #-}
basicLength :: forall s. MVector s (LE w) -> Int
basicLength (MV_LE MVector s w
v) = MVector s w -> Int
forall s. MVector s w -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
GVM.basicLength MVector s w
v
basicUnsafeSlice :: forall s. Int -> Int -> MVector s (LE w) -> MVector s (LE w)
basicUnsafeSlice Int
i Int
n (MV_LE MVector s w
v) = MVector s w -> MVector s (LE w)
forall s w. MVector s w -> MVector s (LE w)
MV_LE (MVector s w -> MVector s (LE w))
-> MVector s w -> MVector s (LE w)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> MVector s w -> MVector s w
forall s. Int -> Int -> MVector s w -> MVector s w
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
GVM.basicUnsafeSlice Int
i Int
n MVector s w
v
basicOverlaps :: forall s. MVector s (LE w) -> MVector s (LE w) -> Bool
basicOverlaps (MV_LE MVector s w
v1) (MV_LE MVector s w
v2) = MVector s w -> MVector s w -> Bool
forall s. MVector s w -> MVector s w -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
GVM.basicOverlaps MVector s w
v1 MVector s w
v2
basicUnsafeRead :: forall s. MVector s (LE w) -> Int -> ST s (LE w)
basicUnsafeRead (MV_LE MVector s w
v) Int
i = w -> LE w
forall w. w -> LE w
LE (w -> LE w) -> ST s w -> ST s (LE w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s w -> Int -> ST s w
forall s. MVector s w -> Int -> ST s w
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s a
GVM.basicUnsafeRead MVector s w
v Int
i
basicUnsafeWrite :: forall s. MVector s (LE w) -> Int -> LE w -> ST s ()
basicUnsafeWrite (MV_LE MVector s w
v) Int
i (LE w
x) = MVector s w -> Int -> w -> ST s ()
forall s. MVector s w -> Int -> w -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> a -> ST s ()
GVM.basicUnsafeWrite MVector s w
v Int
i w
x
basicClear :: forall s. MVector s (LE w) -> ST s ()
basicClear (MV_LE MVector s w
v) = MVector s w -> ST s ()
forall s. MVector s w -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
GVM.basicClear MVector s w
v
basicSet :: forall s. MVector s (LE w) -> LE w -> ST s ()
basicSet (MV_LE MVector s w
v) (LE w
x) = MVector s w -> w -> ST s ()
forall s. MVector s w -> w -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> a -> ST s ()
GVM.basicSet MVector s w
v w
x
basicUnsafeNew :: forall s. Int -> ST s (MVector s (LE w))
basicUnsafeNew Int
n = MVector s w -> MVector s (LE w)
forall s w. MVector s w -> MVector s (LE w)
MV_LE (MVector s w -> MVector s (LE w))
-> ST s (MVector s w) -> ST s (MVector s (LE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> ST s (MVector s w)
forall s. Int -> ST s (MVector s w)
forall (v :: * -> * -> *) a s. MVector v a => Int -> ST s (v s a)
GVM.basicUnsafeNew Int
n
basicUnsafeReplicate :: forall s. Int -> LE w -> ST s (MVector s (LE w))
basicUnsafeReplicate Int
n (LE w
x) = MVector s w -> MVector s (LE w)
forall s w. MVector s w -> MVector s (LE w)
MV_LE (MVector s w -> MVector s (LE w))
-> ST s (MVector s w) -> ST s (MVector s (LE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> w -> ST s (MVector s w)
forall s. Int -> w -> ST s (MVector s w)
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> a -> ST s (v s a)
GVM.basicUnsafeReplicate Int
n w
x
basicUnsafeCopy :: forall s. MVector s (LE w) -> MVector s (LE w) -> ST s ()
basicUnsafeCopy (MV_LE MVector s w
v1) (MV_LE MVector s w
v2) = MVector s w -> MVector s w -> ST s ()
forall s. MVector s w -> MVector s w -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
GVM.basicUnsafeCopy MVector s w
v1 MVector s w
v2
basicUnsafeGrow :: forall s. MVector s (LE w) -> Int -> ST s (MVector s (LE w))
basicUnsafeGrow (MV_LE MVector s w
v) Int
n = MVector s w -> MVector s (LE w)
forall s w. MVector s w -> MVector s (LE w)
MV_LE (MVector s w -> MVector s (LE w))
-> ST s (MVector s w) -> ST s (MVector s (LE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s w -> Int -> ST s (MVector s w)
forall s. MVector s w -> Int -> ST s (MVector s w)
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s (v s a)
GVM.basicUnsafeGrow MVector s w
v Int
n
basicInitialize :: forall s. MVector s (LE w) -> ST s ()
basicInitialize (MV_LE MVector s w
v) = MVector s w -> ST s ()
forall s. MVector s w -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
GVM.basicInitialize MVector s w
v
instance Unbox w => GV.Vector Vector (LE w) where
{-# INLINE basicUnsafeFreeze #-}
{-# INLINE basicUnsafeThaw #-}
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicUnsafeIndexM #-}
{-# INLINE elemseq #-}
basicUnsafeFreeze :: forall s. Mutable Vector s (LE w) -> ST s (Vector (LE w))
basicUnsafeFreeze (MV_LE MVector s w
v) = Vector w -> Vector (LE w)
forall w. Vector w -> Vector (LE w)
V_LE (Vector w -> Vector (LE w))
-> ST s (Vector w) -> ST s (Vector (LE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mutable Vector s w -> ST s (Vector w)
forall s. Mutable Vector s w -> ST s (Vector w)
forall (v :: * -> *) a s. Vector v a => Mutable v s a -> ST s (v a)
GV.basicUnsafeFreeze Mutable Vector s w
MVector s w
v
basicUnsafeThaw :: forall s. Vector (LE w) -> ST s (Mutable Vector s (LE w))
basicUnsafeThaw (V_LE Vector w
v) = MVector s w -> MVector s (LE w)
forall s w. MVector s w -> MVector s (LE w)
MV_LE (MVector s w -> MVector s (LE w))
-> ST s (MVector s w) -> ST s (MVector s (LE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector w -> ST s (Mutable Vector s w)
forall s. Vector w -> ST s (Mutable Vector s w)
forall (v :: * -> *) a s. Vector v a => v a -> ST s (Mutable v s a)
GV.basicUnsafeThaw Vector w
v
basicLength :: Vector (LE w) -> Int
basicLength (V_LE Vector w
v) = Vector w -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
GV.basicLength Vector w
v
basicUnsafeSlice :: Int -> Int -> Vector (LE w) -> Vector (LE w)
basicUnsafeSlice Int
i Int
n (V_LE Vector w
v) = Vector w -> Vector (LE w)
forall w. Vector w -> Vector (LE w)
V_LE (Vector w -> Vector (LE w)) -> Vector w -> Vector (LE w)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector w -> Vector w
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
GV.basicUnsafeSlice Int
i Int
n Vector w
v
basicUnsafeIndexM :: Vector (LE w) -> Int -> Box (LE w)
basicUnsafeIndexM (V_LE Vector w
v) Int
i = w -> LE w
forall w. w -> LE w
LE (w -> LE w) -> Box w -> Box (LE w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector w -> Int -> Box w
forall (v :: * -> *) a. Vector v a => v a -> Int -> Box a
GV.basicUnsafeIndexM Vector w
v Int
i
basicUnsafeCopy :: forall s. Mutable Vector s (LE w) -> Vector (LE w) -> ST s ()
basicUnsafeCopy (MV_LE MVector s w
mv) (V_LE Vector w
v) = Mutable Vector s w -> Vector w -> ST s ()
forall s. Mutable Vector s w -> Vector w -> ST s ()
forall (v :: * -> *) a s.
Vector v a =>
Mutable v s a -> v a -> ST s ()
GV.basicUnsafeCopy Mutable Vector s w
MVector s w
mv Vector w
v
elemseq :: forall b. Vector (LE w) -> LE w -> b -> b
elemseq Vector (LE w)
_ (LE w
x) = Vector w -> w -> b -> b
forall b. Vector w -> w -> b -> b
forall (v :: * -> *) a b. Vector v a => v a -> a -> b -> b
GV.elemseq (Vector a
forall {a}. Vector a
forall a. HasCallStack => a
undefined :: Vector a) w
x
instance Unbox w => GVM.MVector MVector (BE w) where
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicOverlaps #-}
{-# INLINE basicUnsafeNew #-}
{-# INLINE basicUnsafeReplicate #-}
{-# INLINE basicUnsafeRead #-}
{-# INLINE basicUnsafeWrite #-}
{-# INLINE basicClear #-}
{-# INLINE basicSet #-}
{-# INLINE basicUnsafeCopy #-}
{-# INLINE basicUnsafeGrow #-}
basicLength :: forall s. MVector s (BE w) -> Int
basicLength (MV_BE MVector s w
v) = MVector s w -> Int
forall s. MVector s w -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
GVM.basicLength MVector s w
v
basicUnsafeSlice :: forall s. Int -> Int -> MVector s (BE w) -> MVector s (BE w)
basicUnsafeSlice Int
i Int
n (MV_BE MVector s w
v) = MVector s w -> MVector s (BE w)
forall s w. MVector s w -> MVector s (BE w)
MV_BE (MVector s w -> MVector s (BE w))
-> MVector s w -> MVector s (BE w)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> MVector s w -> MVector s w
forall s. Int -> Int -> MVector s w -> MVector s w
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> Int -> v s a -> v s a
GVM.basicUnsafeSlice Int
i Int
n MVector s w
v
basicOverlaps :: forall s. MVector s (BE w) -> MVector s (BE w) -> Bool
basicOverlaps (MV_BE MVector s w
v1) (MV_BE MVector s w
v2) = MVector s w -> MVector s w -> Bool
forall s. MVector s w -> MVector s w -> Bool
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> Bool
GVM.basicOverlaps MVector s w
v1 MVector s w
v2
basicUnsafeRead :: forall s. MVector s (BE w) -> Int -> ST s (BE w)
basicUnsafeRead (MV_BE MVector s w
v) Int
i = w -> BE w
forall w. w -> BE w
BE (w -> BE w) -> ST s w -> ST s (BE w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s w -> Int -> ST s w
forall s. MVector s w -> Int -> ST s w
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s a
GVM.basicUnsafeRead MVector s w
v Int
i
basicUnsafeWrite :: forall s. MVector s (BE w) -> Int -> BE w -> ST s ()
basicUnsafeWrite (MV_BE MVector s w
v) Int
i (BE w
x) = MVector s w -> Int -> w -> ST s ()
forall s. MVector s w -> Int -> w -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> a -> ST s ()
GVM.basicUnsafeWrite MVector s w
v Int
i w
x
basicClear :: forall s. MVector s (BE w) -> ST s ()
basicClear (MV_BE MVector s w
v) = MVector s w -> ST s ()
forall s. MVector s w -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
GVM.basicClear MVector s w
v
basicSet :: forall s. MVector s (BE w) -> BE w -> ST s ()
basicSet (MV_BE MVector s w
v) (BE w
x) = MVector s w -> w -> ST s ()
forall s. MVector s w -> w -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> a -> ST s ()
GVM.basicSet MVector s w
v w
x
basicUnsafeNew :: forall s. Int -> ST s (MVector s (BE w))
basicUnsafeNew Int
n = MVector s w -> MVector s (BE w)
forall s w. MVector s w -> MVector s (BE w)
MV_BE (MVector s w -> MVector s (BE w))
-> ST s (MVector s w) -> ST s (MVector s (BE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> ST s (MVector s w)
forall s. Int -> ST s (MVector s w)
forall (v :: * -> * -> *) a s. MVector v a => Int -> ST s (v s a)
GVM.basicUnsafeNew Int
n
basicUnsafeReplicate :: forall s. Int -> BE w -> ST s (MVector s (BE w))
basicUnsafeReplicate Int
n (BE w
x) = MVector s w -> MVector s (BE w)
forall s w. MVector s w -> MVector s (BE w)
MV_BE (MVector s w -> MVector s (BE w))
-> ST s (MVector s w) -> ST s (MVector s (BE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> w -> ST s (MVector s w)
forall s. Int -> w -> ST s (MVector s w)
forall (v :: * -> * -> *) a s.
MVector v a =>
Int -> a -> ST s (v s a)
GVM.basicUnsafeReplicate Int
n w
x
basicUnsafeCopy :: forall s. MVector s (BE w) -> MVector s (BE w) -> ST s ()
basicUnsafeCopy (MV_BE MVector s w
v1) (MV_BE MVector s w
v2) = MVector s w -> MVector s w -> ST s ()
forall s. MVector s w -> MVector s w -> ST s ()
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> v s a -> ST s ()
GVM.basicUnsafeCopy MVector s w
v1 MVector s w
v2
basicUnsafeGrow :: forall s. MVector s (BE w) -> Int -> ST s (MVector s (BE w))
basicUnsafeGrow (MV_BE MVector s w
v) Int
n = MVector s w -> MVector s (BE w)
forall s w. MVector s w -> MVector s (BE w)
MV_BE (MVector s w -> MVector s (BE w))
-> ST s (MVector s w) -> ST s (MVector s (BE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector s w -> Int -> ST s (MVector s w)
forall s. MVector s w -> Int -> ST s (MVector s w)
forall (v :: * -> * -> *) a s.
MVector v a =>
v s a -> Int -> ST s (v s a)
GVM.basicUnsafeGrow MVector s w
v Int
n
basicInitialize :: forall s. MVector s (BE w) -> ST s ()
basicInitialize (MV_BE MVector s w
v) = MVector s w -> ST s ()
forall s. MVector s w -> ST s ()
forall (v :: * -> * -> *) a s. MVector v a => v s a -> ST s ()
GVM.basicInitialize MVector s w
v
instance Unbox w => GV.Vector Vector (BE w) where
{-# INLINE basicUnsafeFreeze #-}
{-# INLINE basicUnsafeThaw #-}
{-# INLINE basicLength #-}
{-# INLINE basicUnsafeSlice #-}
{-# INLINE basicUnsafeIndexM #-}
{-# INLINE elemseq #-}
basicUnsafeFreeze :: forall s. Mutable Vector s (BE w) -> ST s (Vector (BE w))
basicUnsafeFreeze (MV_BE MVector s w
v) = Vector w -> Vector (BE w)
forall w. Vector w -> Vector (BE w)
V_BE (Vector w -> Vector (BE w))
-> ST s (Vector w) -> ST s (Vector (BE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mutable Vector s w -> ST s (Vector w)
forall s. Mutable Vector s w -> ST s (Vector w)
forall (v :: * -> *) a s. Vector v a => Mutable v s a -> ST s (v a)
GV.basicUnsafeFreeze Mutable Vector s w
MVector s w
v
basicUnsafeThaw :: forall s. Vector (BE w) -> ST s (Mutable Vector s (BE w))
basicUnsafeThaw (V_BE Vector w
v) = MVector s w -> MVector s (BE w)
forall s w. MVector s w -> MVector s (BE w)
MV_BE (MVector s w -> MVector s (BE w))
-> ST s (MVector s w) -> ST s (MVector s (BE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector w -> ST s (Mutable Vector s w)
forall s. Vector w -> ST s (Mutable Vector s w)
forall (v :: * -> *) a s. Vector v a => v a -> ST s (Mutable v s a)
GV.basicUnsafeThaw Vector w
v
basicLength :: Vector (BE w) -> Int
basicLength (V_BE Vector w
v) = Vector w -> Int
forall (v :: * -> *) a. Vector v a => v a -> Int
GV.basicLength Vector w
v
basicUnsafeSlice :: Int -> Int -> Vector (BE w) -> Vector (BE w)
basicUnsafeSlice Int
i Int
n (V_BE Vector w
v) = Vector w -> Vector (BE w)
forall w. Vector w -> Vector (BE w)
V_BE (Vector w -> Vector (BE w)) -> Vector w -> Vector (BE w)
forall a b. (a -> b) -> a -> b
$ Int -> Int -> Vector w -> Vector w
forall (v :: * -> *) a. Vector v a => Int -> Int -> v a -> v a
GV.basicUnsafeSlice Int
i Int
n Vector w
v
basicUnsafeIndexM :: Vector (BE w) -> Int -> Box (BE w)
basicUnsafeIndexM (V_BE Vector w
v) Int
i = w -> BE w
forall w. w -> BE w
BE (w -> BE w) -> Box w -> Box (BE w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector w -> Int -> Box w
forall (v :: * -> *) a. Vector v a => v a -> Int -> Box a
GV.basicUnsafeIndexM Vector w
v Int
i
basicUnsafeCopy :: forall s. Mutable Vector s (BE w) -> Vector (BE w) -> ST s ()
basicUnsafeCopy (MV_BE MVector s w
mv) (V_BE Vector w
v) = Mutable Vector s w -> Vector w -> ST s ()
forall s. Mutable Vector s w -> Vector w -> ST s ()
forall (v :: * -> *) a s.
Vector v a =>
Mutable v s a -> v a -> ST s ()
GV.basicUnsafeCopy Mutable Vector s w
MVector s w
mv Vector w
v
elemseq :: forall b. Vector (BE w) -> BE w -> b -> b
elemseq Vector (BE w)
_ (BE w
x) = Vector w -> w -> b -> b
forall b. Vector w -> w -> b -> b
forall (v :: * -> *) a b. Vector v a => v a -> a -> b -> b
GV.elemseq (Vector a
forall {a}. Vector a
forall a. HasCallStack => a
undefined :: Vector a) w
x