{-# OPTIONS_HADDOCK hide                #-}
{-# LANGUAGE CPP                        #-}
{-# LANGUAGE ForeignFunctionInterface   #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE TypeFamilies               #-}

-- | Endian safe types.
module Raaz.Core.Types.Endian
       ( -- * Endianess aware types.
         -- $endianness$
         EndianStore(..), copyFromBytes, copyToBytes
       -- ** Endian explicit word types.
       , LE(..), BE(..), littleEndian, bigEndian
       -- ** Helper functions for endian aware storing and loading.
       , 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

-- $endianness$
--
-- Cryptographic primitives often consider their input as an array of
-- words of a particular endianness. Endianness is only relevant when
-- serialising to (or de-serialising from) their encoding to the
-- outside world. Raaz strives to use types to provide an endian
-- agnostic interface to all data that is relevant to the outside
-- world.
--
-- The starting point of an endian agnostic interface is the class
-- `EndianStore`. Instances of this class support an endian agnostic
-- `load` and `store`. Endian adjusted copying is also provided for
-- these types through the helper functions `copyFromBytes` and
-- `copyToBytes`.
--
-- It is tedious to think about endianness for each new type one might
-- encounter. As before, we have a top down approach to defining such
-- an interface. To start with, the library exposes endian aware
-- variants of `Word32` and `Word64` and functions @littleEndian@ and
-- @bigEndian@ for conversions. The `Tuple` type inherits the
-- endianness of its element type, i.e for example @Tuple 10 (LE
-- Word32)@ when loded (or stored) will load (or store) 10 32-bit
-- words assuming that the words are expressed in little endian. Other
-- types are then built out of these endian aware types. For example,
-- cryptographic type `SHA512` is defined as.
--
-- >
-- > newtype SHA512 = SHA512 (Tuple 8 (BE Word64))
-- >                      deriving (Equality, Eq, Storable, EndianStore)
-- >
--

-- | This class captures types which provides an endian agnostic way
-- of loading from and storing to data buffers. Any multi-byte type
-- that is meant to be serialised to the outside world should be an
-- instance of this class. When defining the `load`, `store`,
-- `adjustEndian` member functions, care should be taken to ensure
-- proper endian conversion.
--
class Storable w => EndianStore w where

  -- | The action @store ptr w@ stores @w@ at the location pointed by
  -- @ptr@.  Endianness of the type @w@ is taken care of when storing.
  -- For example, irrespective of the endianness of the machine,
  -- @store ptr (0x01020304 :: BE Word32)@ will store the bytes
  -- @0x01@, @0x02@, @0x03@, @0x04@ respectively at locations @ptr@,
  -- @ptr +1@, @ptr+2@ and @ptr+3@. On the other hand @store ptr
  -- (0x01020304 :: LE Word32)@ would store @0x04@, @0x03@, @0x02@,
  -- @0x01@ at the above locations.

  store :: Ptr w   -- ^ the location.
        -> w       -- ^ value to store
        -> IO ()

  -- | The action @load ptr@ loads the value stored at the @ptr@. Like
  -- store, it takes care of the endianness of the data type.  For
  -- example, if @ptr@ points to a buffer containing the bytes @0x01@,
  -- @0x02@, @0x03@, @0x04@, irrespective of the endianness of the
  -- machine, @load ptr :: IO (BE Word32)@ will load the vale
  -- @0x01020304@ of type @BE Word32@ and @load ptr :: IO (LE Word32)@
  -- will load @0x04030201@ of type @LE Word32@.
  load  :: Ptr w -> IO w

  -- | The action @adjustEndian ptr n@ adjusts the encoding of bytes
  -- stored at the location @ptr@ to conform with the endianness of
  -- the underlying data type. For example, assume that @ptr@ points
  -- to a buffer containing the bytes @0x01 0x02 0x03 0x04@, and we
  -- are on a big endian machine, then @adjustEndian (ptr :: Ptr (LE
  -- Word32)) 1@ will result in @ptr@ pointing to the sequence @0x04
  -- 0x03 0x02 0x01@. On the other hand if we were on a little endian
  -- machine, the sequence should remain the same.  In particular, the
  -- following equalities should hold.
  --
  -- >
  -- > store ptr w          = poke ptr w >> adjustEndian ptr 1
  -- >
  --
  -- Similarly the value loaded by @load ptr@ should be same as the
  -- value returned by @adjustEndian ptr 1 >> peak ptr@, although the
  -- former does not change the contents stored at @ptr@ where as the
  -- latter might does modify the contents pointed by @ptr@ if the
  -- endianness of the machine and the time do not agree.
  --
  -- The action @adjustEndian ptr n >> adjustEndian ptr n @ should be
  -- equivalent to @return ()@.
  --
  adjustEndian :: Ptr w  -- ^ buffer pointers,
               -> Int    -- ^ how many w's are present,
               -> 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 (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 (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 (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 :: Ptr (BYTES w) -> Ptr w
castToPtrW = Ptr (BYTES w) -> Ptr w
forall a b. Ptr a -> Ptr b
castPtr

-- | Store the given value at an offset from the crypto pointer. The
-- offset is given in type safe units.
storeAt :: ( EndianStore w
           , LengthUnit offset
           )
        => Ptr w     -- ^ the pointer
        -> offset    -- ^ the absolute offset in type safe length units.
        -> w         -- ^ value to store
        -> IO ()
{-# INLINE storeAt #-}
storeAt :: 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

-- | Store the given value as the @n@-th element of the array
-- pointed by the crypto pointer.
storeAtIndex :: EndianStore w
             => Ptr w          -- ^ the pointer to the first element of the
                               -- array
             -> Int            -- ^ the index of the array
             -> w              -- ^ the value to store
             -> IO ()
{-# INLINE storeAtIndex #-}
storeAtIndex :: 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 (f :: * -> *) a. Applicative f => a -> f a
pure w
w)


-- | Load the @n@-th value of an array pointed by the crypto pointer.
loadFromIndex :: EndianStore w
              => Ptr w   -- ^ the pointer to the first element of
                         -- the array
              -> Int     -- ^ the index of the array
              -> IO w
{-# INLINE loadFromIndex #-}
loadFromIndex :: 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 :: 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 :: 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
-- | Load from a given offset. The offset is given in type safe units.
loadFrom :: ( EndianStore w
            , LengthUnit offset
            )
         => Ptr w    -- ^ the pointer
         -> offset   -- ^ the offset
         -> IO w
{-# INLINE loadFrom #-}
loadFrom :: 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

-- | For the type @w@, the action @copyFromBytes dest src n@ copies @n@-elements from
-- @src@ to @dest@. Copy performed by this combinator accounts for the
-- endianness of the data in @dest@ and is therefore /not/ a mere copy
-- of @n * sizeOf(w)@ bytes. This action does not modify the @src@
-- pointer in any way.

copyFromBytes :: EndianStore w
              => Dest (Ptr w)
              -> Src  (Ptr Word8)
              -> Int          -- ^ How many items.
              -> IO ()
copyFromBytes :: 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 (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 :: 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

-- | Similar to @copyFromBytes@ but the transfer is done in the other direction. The copy takes
-- care of performing the appropriate endian encoding.
copyToBytes :: EndianStore w
            => Dest (Ptr Word8)
            -> Src  (Ptr w)
            -> Int
            -> IO ()
copyToBytes :: 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 (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 :: 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 :: 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


{-
Developers notes:
-----------------

Make sure that the endian encoded version does not have any
performance penalty. We may have to stare at the core code generated
by ghc.

-}

-- | Little endian version of the word type @w@
newtype LE w = LE { 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
maxBound :: LE w
$cmaxBound :: forall w. Bounded w => LE w
minBound :: LE w
$cminBound :: forall w. Bounded w => 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
enumFromThenTo :: LE w -> LE w -> LE w -> [LE w]
$cenumFromThenTo :: forall w. Enum w => LE w -> LE w -> LE w -> [LE w]
enumFromTo :: LE w -> LE w -> [LE w]
$cenumFromTo :: forall w. Enum w => LE w -> LE w -> [LE w]
enumFromThen :: LE w -> LE w -> [LE w]
$cenumFromThen :: forall w. Enum w => LE w -> LE w -> [LE w]
enumFrom :: LE w -> [LE w]
$cenumFrom :: forall w. Enum w => LE w -> [LE w]
fromEnum :: LE w -> Int
$cfromEnum :: forall w. Enum w => LE w -> Int
toEnum :: Int -> LE w
$ctoEnum :: forall w. Enum w => Int -> LE w
pred :: LE w -> LE w
$cpred :: forall w. Enum w => LE w -> LE w
succ :: LE w -> LE w
$csucc :: forall w. Enum 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
readListPrec :: ReadPrec [LE w]
$creadListPrec :: forall w. Read w => ReadPrec [LE w]
readPrec :: ReadPrec (LE w)
$creadPrec :: forall w. Read w => ReadPrec (LE w)
readList :: ReadS [LE w]
$creadList :: forall w. Read w => ReadS [LE w]
readsPrec :: Int -> ReadS (LE w)
$creadsPrec :: forall w. Read w => Int -> ReadS (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
showList :: [LE w] -> ShowS
$cshowList :: forall w. Show w => [LE w] -> ShowS
show :: LE w -> String
$cshow :: forall w. Show w => LE w -> String
showsPrec :: Int -> LE w -> ShowS
$cshowsPrec :: forall w. Show w => Int -> 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
toInteger :: LE w -> Integer
$ctoInteger :: forall w. Integral w => LE w -> Integer
divMod :: LE w -> LE w -> (LE w, LE w)
$cdivMod :: forall w. Integral w => LE w -> LE w -> (LE w, LE w)
quotRem :: LE w -> LE w -> (LE w, LE w)
$cquotRem :: forall w. Integral w => LE w -> LE w -> (LE w, LE w)
mod :: LE w -> LE w -> LE w
$cmod :: forall w. Integral w => LE w -> LE w -> LE w
div :: LE w -> LE w -> LE w
$cdiv :: forall w. Integral w => LE w -> LE w -> LE w
rem :: LE w -> LE w -> LE w
$crem :: forall w. Integral w => LE w -> LE w -> LE w
quot :: LE w -> LE w -> LE w
$cquot :: forall w. Integral w => LE w -> LE w -> LE w
$cp2Integral :: forall w. Integral w => Enum (LE w)
$cp1Integral :: forall w. Integral w => Real (LE w)
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
fromInteger :: Integer -> LE w
$cfromInteger :: forall w. Num w => Integer -> LE w
signum :: LE w -> LE w
$csignum :: forall w. Num w => LE w -> LE w
abs :: LE w -> LE w
$cabs :: forall w. Num w => LE w -> LE w
negate :: LE w -> LE w
$cnegate :: forall w. Num 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
$c+ :: forall w. Num w => LE w -> LE w -> 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
toRational :: LE w -> Rational
$ctoRational :: forall w. Real w => LE w -> Rational
$cp2Real :: forall w. Real w => Ord (LE w)
$cp1Real :: forall w. Real w => Num (LE w)
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
/= :: LE w -> LE w -> Bool
$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
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
eq :: LE w -> LE w -> Result
$ceq :: forall w. Equality w => 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
min :: LE w -> LE w -> LE w
$cmin :: forall w. Ord w => LE w -> LE w -> LE w
max :: LE w -> LE w -> LE w
$cmax :: forall w. Ord w => LE w -> LE w -> LE w
>= :: 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
$c< :: forall w. Ord w => LE w -> LE w -> Bool
compare :: LE w -> LE w -> Ordering
$ccompare :: forall w. Ord w => LE w -> LE w -> Ordering
$cp1Ord :: forall w. Ord w => Eq (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
popCount :: LE w -> Int
$cpopCount :: forall w. Bits w => LE w -> Int
rotateR :: LE w -> Int -> LE w
$crotateR :: forall w. Bits w => LE w -> Int -> LE w
rotateL :: LE w -> Int -> LE w
$crotateL :: forall w. Bits w => LE w -> Int -> LE w
unsafeShiftR :: LE w -> Int -> LE w
$cunsafeShiftR :: forall w. Bits w => LE w -> Int -> LE w
shiftR :: LE w -> Int -> LE w
$cshiftR :: forall w. Bits w => LE w -> Int -> LE w
unsafeShiftL :: LE w -> Int -> LE w
$cunsafeShiftL :: forall w. Bits w => LE w -> Int -> LE w
shiftL :: LE w -> Int -> LE w
$cshiftL :: forall w. Bits w => LE w -> Int -> LE w
isSigned :: LE w -> Bool
$cisSigned :: forall w. Bits w => LE w -> Bool
bitSize :: LE w -> Int
$cbitSize :: forall w. Bits w => LE w -> Int
bitSizeMaybe :: LE w -> Maybe Int
$cbitSizeMaybe :: forall w. Bits w => LE w -> Maybe Int
testBit :: LE w -> Int -> Bool
$ctestBit :: forall w. Bits w => LE w -> Int -> Bool
complementBit :: LE w -> Int -> LE w
$ccomplementBit :: forall w. Bits w => LE w -> Int -> LE w
clearBit :: LE w -> Int -> LE w
$cclearBit :: forall w. Bits w => LE w -> Int -> LE w
setBit :: LE w -> Int -> LE w
$csetBit :: forall w. Bits w => LE w -> Int -> LE w
bit :: Int -> LE w
$cbit :: forall w. Bits w => Int -> LE w
zeroBits :: LE w
$czeroBits :: forall w. Bits w => LE w
rotate :: LE w -> Int -> LE w
$crotate :: forall w. Bits w => LE w -> Int -> LE w
shift :: LE w -> Int -> LE w
$cshift :: forall w. Bits w => LE w -> Int -> LE w
complement :: LE w -> LE w
$ccomplement :: forall w. Bits w => LE w -> LE w
xor :: LE w -> LE w -> LE w
$cxor :: 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
$c.&. :: forall w. Bits w => LE w -> LE w -> LE w
$cp1Bits :: forall w. Bits w => Eq (LE w)
Bits, Ptr b -> Int -> IO (LE w)
Ptr b -> Int -> LE w -> IO ()
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
poke :: Ptr (LE w) -> LE w -> IO ()
$cpoke :: forall w. Storable w => Ptr (LE w) -> LE w -> IO ()
peek :: Ptr (LE w) -> IO (LE w)
$cpeek :: forall w. Storable w => Ptr (LE w) -> IO (LE w)
pokeByteOff :: Ptr b -> Int -> LE w -> IO ()
$cpokeByteOff :: forall w b. Storable w => Ptr b -> Int -> LE w -> IO ()
peekByteOff :: Ptr b -> Int -> IO (LE w)
$cpeekByteOff :: forall w b. Storable w => Ptr b -> Int -> IO (LE w)
pokeElemOff :: Ptr (LE w) -> Int -> LE w -> IO ()
$cpokeElemOff :: forall w. Storable w => Ptr (LE w) -> Int -> LE w -> IO ()
peekElemOff :: Ptr (LE w) -> Int -> IO (LE w)
$cpeekElemOff :: forall w. Storable w => Ptr (LE w) -> Int -> IO (LE w)
alignment :: LE w -> Int
$calignment :: forall w. Storable w => LE w -> Int
sizeOf :: LE w -> Int
$csizeOf :: forall w. Storable w => LE w -> Int
Storable, Typeable, LE w -> ()
(LE w -> ()) -> NFData (LE w)
forall w. NFData w => LE w -> ()
forall a. (a -> ()) -> NFData a
rnf :: LE w -> ()
$crnf :: forall w. NFData w => LE w -> ()
NFData
             )

instance Functor LE where
  fmap :: (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

-- | Big endian version of the word type @w@
newtype BE w = BE { 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
maxBound :: BE w
$cmaxBound :: forall w. Bounded w => BE w
minBound :: BE w
$cminBound :: forall w. Bounded w => 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
enumFromThenTo :: BE w -> BE w -> BE w -> [BE w]
$cenumFromThenTo :: forall w. Enum w => BE w -> BE w -> BE w -> [BE w]
enumFromTo :: BE w -> BE w -> [BE w]
$cenumFromTo :: forall w. Enum w => BE w -> BE w -> [BE w]
enumFromThen :: BE w -> BE w -> [BE w]
$cenumFromThen :: forall w. Enum w => BE w -> BE w -> [BE w]
enumFrom :: BE w -> [BE w]
$cenumFrom :: forall w. Enum w => BE w -> [BE w]
fromEnum :: BE w -> Int
$cfromEnum :: forall w. Enum w => BE w -> Int
toEnum :: Int -> BE w
$ctoEnum :: forall w. Enum w => Int -> BE w
pred :: BE w -> BE w
$cpred :: forall w. Enum w => BE w -> BE w
succ :: BE w -> BE w
$csucc :: forall w. Enum 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
readListPrec :: ReadPrec [BE w]
$creadListPrec :: forall w. Read w => ReadPrec [BE w]
readPrec :: ReadPrec (BE w)
$creadPrec :: forall w. Read w => ReadPrec (BE w)
readList :: ReadS [BE w]
$creadList :: forall w. Read w => ReadS [BE w]
readsPrec :: Int -> ReadS (BE w)
$creadsPrec :: forall w. Read w => Int -> ReadS (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
showList :: [BE w] -> ShowS
$cshowList :: forall w. Show w => [BE w] -> ShowS
show :: BE w -> String
$cshow :: forall w. Show w => BE w -> String
showsPrec :: Int -> BE w -> ShowS
$cshowsPrec :: forall w. Show w => Int -> 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
toInteger :: BE w -> Integer
$ctoInteger :: forall w. Integral w => BE w -> Integer
divMod :: BE w -> BE w -> (BE w, BE w)
$cdivMod :: forall w. Integral w => BE w -> BE w -> (BE w, BE w)
quotRem :: BE w -> BE w -> (BE w, BE w)
$cquotRem :: forall w. Integral w => BE w -> BE w -> (BE w, BE w)
mod :: BE w -> BE w -> BE w
$cmod :: forall w. Integral w => BE w -> BE w -> BE w
div :: BE w -> BE w -> BE w
$cdiv :: forall w. Integral w => BE w -> BE w -> BE w
rem :: BE w -> BE w -> BE w
$crem :: forall w. Integral w => BE w -> BE w -> BE w
quot :: BE w -> BE w -> BE w
$cquot :: forall w. Integral w => BE w -> BE w -> BE w
$cp2Integral :: forall w. Integral w => Enum (BE w)
$cp1Integral :: forall w. Integral w => Real (BE w)
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
fromInteger :: Integer -> BE w
$cfromInteger :: forall w. Num w => Integer -> BE w
signum :: BE w -> BE w
$csignum :: forall w. Num w => BE w -> BE w
abs :: BE w -> BE w
$cabs :: forall w. Num w => BE w -> BE w
negate :: BE w -> BE w
$cnegate :: forall w. Num 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
$c+ :: forall w. Num w => BE w -> BE w -> 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
toRational :: BE w -> Rational
$ctoRational :: forall w. Real w => BE w -> Rational
$cp2Real :: forall w. Real w => Ord (BE w)
$cp1Real :: forall w. Real w => Num (BE w)
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
/= :: BE w -> BE w -> Bool
$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
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
eq :: BE w -> BE w -> Result
$ceq :: forall w. Equality w => 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
min :: BE w -> BE w -> BE w
$cmin :: forall w. Ord w => BE w -> BE w -> BE w
max :: BE w -> BE w -> BE w
$cmax :: forall w. Ord w => BE w -> BE w -> BE w
>= :: 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
$c< :: forall w. Ord w => BE w -> BE w -> Bool
compare :: BE w -> BE w -> Ordering
$ccompare :: forall w. Ord w => BE w -> BE w -> Ordering
$cp1Ord :: forall w. Ord w => Eq (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
popCount :: BE w -> Int
$cpopCount :: forall w. Bits w => BE w -> Int
rotateR :: BE w -> Int -> BE w
$crotateR :: forall w. Bits w => BE w -> Int -> BE w
rotateL :: BE w -> Int -> BE w
$crotateL :: forall w. Bits w => BE w -> Int -> BE w
unsafeShiftR :: BE w -> Int -> BE w
$cunsafeShiftR :: forall w. Bits w => BE w -> Int -> BE w
shiftR :: BE w -> Int -> BE w
$cshiftR :: forall w. Bits w => BE w -> Int -> BE w
unsafeShiftL :: BE w -> Int -> BE w
$cunsafeShiftL :: forall w. Bits w => BE w -> Int -> BE w
shiftL :: BE w -> Int -> BE w
$cshiftL :: forall w. Bits w => BE w -> Int -> BE w
isSigned :: BE w -> Bool
$cisSigned :: forall w. Bits w => BE w -> Bool
bitSize :: BE w -> Int
$cbitSize :: forall w. Bits w => BE w -> Int
bitSizeMaybe :: BE w -> Maybe Int
$cbitSizeMaybe :: forall w. Bits w => BE w -> Maybe Int
testBit :: BE w -> Int -> Bool
$ctestBit :: forall w. Bits w => BE w -> Int -> Bool
complementBit :: BE w -> Int -> BE w
$ccomplementBit :: forall w. Bits w => BE w -> Int -> BE w
clearBit :: BE w -> Int -> BE w
$cclearBit :: forall w. Bits w => BE w -> Int -> BE w
setBit :: BE w -> Int -> BE w
$csetBit :: forall w. Bits w => BE w -> Int -> BE w
bit :: Int -> BE w
$cbit :: forall w. Bits w => Int -> BE w
zeroBits :: BE w
$czeroBits :: forall w. Bits w => BE w
rotate :: BE w -> Int -> BE w
$crotate :: forall w. Bits w => BE w -> Int -> BE w
shift :: BE w -> Int -> BE w
$cshift :: forall w. Bits w => BE w -> Int -> BE w
complement :: BE w -> BE w
$ccomplement :: forall w. Bits w => BE w -> BE w
xor :: BE w -> BE w -> BE w
$cxor :: 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
$c.&. :: forall w. Bits w => BE w -> BE w -> BE w
$cp1Bits :: forall w. Bits w => Eq (BE w)
Bits, Ptr b -> Int -> IO (BE w)
Ptr b -> Int -> BE w -> IO ()
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
poke :: Ptr (BE w) -> BE w -> IO ()
$cpoke :: forall w. Storable w => Ptr (BE w) -> BE w -> IO ()
peek :: Ptr (BE w) -> IO (BE w)
$cpeek :: forall w. Storable w => Ptr (BE w) -> IO (BE w)
pokeByteOff :: Ptr b -> Int -> BE w -> IO ()
$cpokeByteOff :: forall w b. Storable w => Ptr b -> Int -> BE w -> IO ()
peekByteOff :: Ptr b -> Int -> IO (BE w)
$cpeekByteOff :: forall w b. Storable w => Ptr b -> Int -> IO (BE w)
pokeElemOff :: Ptr (BE w) -> Int -> BE w -> IO ()
$cpokeElemOff :: forall w. Storable w => Ptr (BE w) -> Int -> BE w -> IO ()
peekElemOff :: Ptr (BE w) -> Int -> IO (BE w)
$cpeekElemOff :: forall w. Storable w => Ptr (BE w) -> Int -> IO (BE w)
alignment :: BE w -> Int
$calignment :: forall w. Storable w => BE w -> Int
sizeOf :: BE w -> Int
$csizeOf :: forall w. Storable w => BE w -> Int
Storable, Typeable, BE w -> ()
(BE w -> ()) -> NFData (BE w)
forall w. NFData w => BE w -> ()
forall a. (a -> ()) -> NFData a
rnf :: BE w -> ()
$crnf :: forall w. NFData w => BE w -> ()
NFData
             )

instance Functor BE where
  fmap :: (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

-- | Convert to the little endian variant.
littleEndian :: w -> LE w
{-# INLINE littleEndian #-}
littleEndian :: w -> LE w
littleEndian = w -> LE w
forall w. w -> LE w
LE

-- | Convert to the big endian variants.
bigEndian :: w -> BE w
{-# INLINE bigEndian #-}
bigEndian :: w -> BE w
bigEndian = w -> BE w
forall w. w -> BE w
BE

---------------- The foreign function calls ----------------------

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 :: Ptr (BE w) -> Ptr w
unBEPtr = Ptr (BE w) -> Ptr w
forall a b. Ptr a -> Ptr b
castPtr

--- We are in a little endian machine.

instance EndianStore (BE Word32) where
  load :: Ptr (BE Word32) -> IO (BE Word32)
load  Ptr (BE Word32)
ptr    = (Word32 -> Word32) -> BE Word32 -> BE Word32
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 (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 (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 (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 (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 (m :: * -> *) a. Monad m => a -> m a
return ()


#endif

------------------- Unboxed vector of Endian word types ---------------

instance Unbox w => Unbox (LE w)
instance Unbox w => Unbox (BE w)

------------------- Defining the vector types --------------------------

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 :: MVector s (LE w) -> Int
basicLength          (MV_LE v)        = MVector s w -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
GVM.basicLength MVector s w
v
  basicUnsafeSlice :: Int -> Int -> MVector s (LE w) -> MVector s (LE w)
basicUnsafeSlice Int
i Int
n (MV_LE 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 (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 :: MVector s (LE w) -> MVector s (LE w) -> Bool
basicOverlaps (MV_LE v1) (MV_LE v2)   = 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 :: MVector (PrimState m) (LE w) -> Int -> m (LE w)
basicUnsafeRead  (MV_LE v) Int
i          = w -> LE w
forall w. w -> LE w
LE (w -> LE w) -> m w -> m (LE w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState m) w -> Int -> m w
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
GVM.basicUnsafeRead MVector (PrimState m) w
v Int
i
  basicUnsafeWrite :: MVector (PrimState m) (LE w) -> Int -> LE w -> m ()
basicUnsafeWrite (MV_LE v) Int
i (LE w
x)   = MVector (PrimState m) w -> Int -> w -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
GVM.basicUnsafeWrite MVector (PrimState m) w
v Int
i w
x

  basicClear :: MVector (PrimState m) (LE w) -> m ()
basicClear (MV_LE v)                  = MVector (PrimState m) w -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
GVM.basicClear MVector (PrimState m) w
v
  basicSet :: MVector (PrimState m) (LE w) -> LE w -> m ()
basicSet   (MV_LE v)         (LE w
x)   = MVector (PrimState m) w -> w -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> a -> m ()
GVM.basicSet MVector (PrimState m) w
v w
x

  basicUnsafeNew :: Int -> m (MVector (PrimState m) (LE w))
basicUnsafeNew Int
n                      = MVector (PrimState m) w -> MVector (PrimState m) (LE w)
forall s w. MVector s w -> MVector s (LE w)
MV_LE (MVector (PrimState m) w -> MVector (PrimState m) (LE w))
-> m (MVector (PrimState m) w) -> m (MVector (PrimState m) (LE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> m (MVector (PrimState m) w)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
GVM.basicUnsafeNew Int
n
  basicUnsafeReplicate :: Int -> LE w -> m (MVector (PrimState m) (LE w))
basicUnsafeReplicate Int
n     (LE w
x)     = MVector (PrimState m) w -> MVector (PrimState m) (LE w)
forall s w. MVector s w -> MVector s (LE w)
MV_LE (MVector (PrimState m) w -> MVector (PrimState m) (LE w))
-> m (MVector (PrimState m) w) -> m (MVector (PrimState m) (LE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> w -> m (MVector (PrimState m) w)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> a -> m (v (PrimState m) a)
GVM.basicUnsafeReplicate Int
n w
x
  basicUnsafeCopy :: MVector (PrimState m) (LE w)
-> MVector (PrimState m) (LE w) -> m ()
basicUnsafeCopy (MV_LE v1) (MV_LE v2) = MVector (PrimState m) w -> MVector (PrimState m) w -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
GVM.basicUnsafeCopy MVector (PrimState m) w
v1 MVector (PrimState m) w
v2
  basicUnsafeGrow :: MVector (PrimState m) (LE w)
-> Int -> m (MVector (PrimState m) (LE w))
basicUnsafeGrow (MV_LE v)   Int
n         = MVector (PrimState m) w -> MVector (PrimState m) (LE w)
forall s w. MVector s w -> MVector s (LE w)
MV_LE (MVector (PrimState m) w -> MVector (PrimState m) (LE w))
-> m (MVector (PrimState m) w) -> m (MVector (PrimState m) (LE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState m) w -> Int -> m (MVector (PrimState m) w)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m (v (PrimState m) a)
GVM.basicUnsafeGrow MVector (PrimState m) w
v Int
n
  basicInitialize :: MVector (PrimState m) (LE w) -> m ()
basicInitialize (MV_LE v)           = MVector (PrimState m) w -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
GVM.basicInitialize MVector (PrimState m) w
v

instance Unbox w => GV.Vector Vector (LE w) where
  {-# INLINE basicUnsafeFreeze #-}
  {-# INLINE basicUnsafeThaw #-}
  {-# INLINE basicLength #-}
  {-# INLINE basicUnsafeSlice #-}
  {-# INLINE basicUnsafeIndexM #-}
  {-# INLINE elemseq #-}
  basicUnsafeFreeze :: Mutable Vector (PrimState m) (LE w) -> m (Vector (LE w))
basicUnsafeFreeze (MV_LE v)   = Vector w -> Vector (LE w)
forall w. Vector w -> Vector (LE w)
V_LE  (Vector w -> Vector (LE w)) -> m (Vector w) -> m (Vector (LE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mutable Vector (PrimState m) w -> m (Vector w)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
GV.basicUnsafeFreeze MVector (PrimState m) w
Mutable Vector (PrimState m) w
v
  basicUnsafeThaw :: Vector (LE w) -> m (Mutable Vector (PrimState m) (LE w))
basicUnsafeThaw (V_LE v)      = MVector (PrimState m) w -> MVector (PrimState m) (LE w)
forall s w. MVector s w -> MVector s (LE w)
MV_LE (MVector (PrimState m) w -> MVector (PrimState m) (LE w))
-> m (MVector (PrimState m) w) -> m (MVector (PrimState m) (LE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector w -> m (Mutable Vector (PrimState m) w)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
GV.basicUnsafeThaw Vector w
v
  basicLength :: Vector (LE w) -> Int
basicLength (V_LE 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 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 -> m (LE w)
basicUnsafeIndexM (V_LE v) Int
i  = w -> LE w
forall w. w -> LE w
LE   (w -> LE w) -> m w -> m (LE w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>  Vector w -> Int -> m w
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
GV.basicUnsafeIndexM Vector w
v Int
i

  basicUnsafeCopy :: Mutable Vector (PrimState m) (LE w) -> Vector (LE w) -> m ()
basicUnsafeCopy (MV_LE mv) (V_LE v) = Mutable Vector (PrimState m) w -> Vector w -> m ()
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> v a -> m ()
GV.basicUnsafeCopy MVector (PrimState m) w
Mutable Vector (PrimState m) w
mv Vector w
v
  elemseq :: Vector (LE w) -> LE w -> b -> b
elemseq Vector (LE w)
_ (LE w
x)                    = Vector w -> w -> b -> b
forall (v :: * -> *) a b. Vector v a => v a -> a -> b -> b
GV.elemseq (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 :: MVector s (BE w) -> Int
basicLength          (MV_BE v)        = MVector s w -> Int
forall (v :: * -> * -> *) a s. MVector v a => v s a -> Int
GVM.basicLength MVector s w
v
  basicUnsafeSlice :: Int -> Int -> MVector s (BE w) -> MVector s (BE w)
basicUnsafeSlice Int
i Int
n (MV_BE 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 (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 :: MVector s (BE w) -> MVector s (BE w) -> Bool
basicOverlaps (MV_BE v1) (MV_BE v2)   = 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 :: MVector (PrimState m) (BE w) -> Int -> m (BE w)
basicUnsafeRead  (MV_BE v) Int
i          = w -> BE w
forall w. w -> BE w
BE (w -> BE w) -> m w -> m (BE w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState m) w -> Int -> m w
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m a
GVM.basicUnsafeRead MVector (PrimState m) w
v Int
i
  basicUnsafeWrite :: MVector (PrimState m) (BE w) -> Int -> BE w -> m ()
basicUnsafeWrite (MV_BE v) Int
i (BE w
x)   = MVector (PrimState m) w -> Int -> w -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> a -> m ()
GVM.basicUnsafeWrite MVector (PrimState m) w
v Int
i w
x

  basicClear :: MVector (PrimState m) (BE w) -> m ()
basicClear (MV_BE v)                  = MVector (PrimState m) w -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
GVM.basicClear MVector (PrimState m) w
v
  basicSet :: MVector (PrimState m) (BE w) -> BE w -> m ()
basicSet   (MV_BE v)         (BE w
x)   = MVector (PrimState m) w -> w -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> a -> m ()
GVM.basicSet MVector (PrimState m) w
v w
x

  basicUnsafeNew :: Int -> m (MVector (PrimState m) (BE w))
basicUnsafeNew Int
n                      = MVector (PrimState m) w -> MVector (PrimState m) (BE w)
forall s w. MVector s w -> MVector s (BE w)
MV_BE (MVector (PrimState m) w -> MVector (PrimState m) (BE w))
-> m (MVector (PrimState m) w) -> m (MVector (PrimState m) (BE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> m (MVector (PrimState m) w)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> m (v (PrimState m) a)
GVM.basicUnsafeNew Int
n
  basicUnsafeReplicate :: Int -> BE w -> m (MVector (PrimState m) (BE w))
basicUnsafeReplicate Int
n     (BE w
x)     = MVector (PrimState m) w -> MVector (PrimState m) (BE w)
forall s w. MVector s w -> MVector s (BE w)
MV_BE (MVector (PrimState m) w -> MVector (PrimState m) (BE w))
-> m (MVector (PrimState m) w) -> m (MVector (PrimState m) (BE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> w -> m (MVector (PrimState m) w)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
Int -> a -> m (v (PrimState m) a)
GVM.basicUnsafeReplicate Int
n w
x
  basicUnsafeCopy :: MVector (PrimState m) (BE w)
-> MVector (PrimState m) (BE w) -> m ()
basicUnsafeCopy (MV_BE v1) (MV_BE v2) = MVector (PrimState m) w -> MVector (PrimState m) w -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> v (PrimState m) a -> m ()
GVM.basicUnsafeCopy MVector (PrimState m) w
v1 MVector (PrimState m) w
v2
  basicUnsafeGrow :: MVector (PrimState m) (BE w)
-> Int -> m (MVector (PrimState m) (BE w))
basicUnsafeGrow (MV_BE v)   Int
n         = MVector (PrimState m) w -> MVector (PrimState m) (BE w)
forall s w. MVector s w -> MVector s (BE w)
MV_BE (MVector (PrimState m) w -> MVector (PrimState m) (BE w))
-> m (MVector (PrimState m) w) -> m (MVector (PrimState m) (BE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> MVector (PrimState m) w -> Int -> m (MVector (PrimState m) w)
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> Int -> m (v (PrimState m) a)
GVM.basicUnsafeGrow MVector (PrimState m) w
v Int
n
  basicInitialize :: MVector (PrimState m) (BE w) -> m ()
basicInitialize (MV_BE v)           = MVector (PrimState m) w -> m ()
forall (v :: * -> * -> *) a (m :: * -> *).
(MVector v a, PrimMonad m) =>
v (PrimState m) a -> m ()
GVM.basicInitialize MVector (PrimState m) w
v



instance Unbox w => GV.Vector Vector (BE w) where
  {-# INLINE basicUnsafeFreeze #-}
  {-# INLINE basicUnsafeThaw #-}
  {-# INLINE basicLength #-}
  {-# INLINE basicUnsafeSlice #-}
  {-# INLINE basicUnsafeIndexM #-}
  {-# INLINE elemseq #-}
  basicUnsafeFreeze :: Mutable Vector (PrimState m) (BE w) -> m (Vector (BE w))
basicUnsafeFreeze (MV_BE v)   = Vector w -> Vector (BE w)
forall w. Vector w -> Vector (BE w)
V_BE  (Vector w -> Vector (BE w)) -> m (Vector w) -> m (Vector (BE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Mutable Vector (PrimState m) w -> m (Vector w)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> m (v a)
GV.basicUnsafeFreeze MVector (PrimState m) w
Mutable Vector (PrimState m) w
v
  basicUnsafeThaw :: Vector (BE w) -> m (Mutable Vector (PrimState m) (BE w))
basicUnsafeThaw (V_BE v)      = MVector (PrimState m) w -> MVector (PrimState m) (BE w)
forall s w. MVector s w -> MVector s (BE w)
MV_BE (MVector (PrimState m) w -> MVector (PrimState m) (BE w))
-> m (MVector (PrimState m) w) -> m (MVector (PrimState m) (BE w))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Vector w -> m (Mutable Vector (PrimState m) w)
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
v a -> m (Mutable v (PrimState m) a)
GV.basicUnsafeThaw Vector w
v
  basicLength :: Vector (BE w) -> Int
basicLength (V_BE 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 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 -> m (BE w)
basicUnsafeIndexM (V_BE v) Int
i  = w -> BE w
forall w. w -> BE w
BE   (w -> BE w) -> m w -> m (BE w)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>  Vector w -> Int -> m w
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, Monad m) =>
v a -> Int -> m a
GV.basicUnsafeIndexM Vector w
v Int
i

  basicUnsafeCopy :: Mutable Vector (PrimState m) (BE w) -> Vector (BE w) -> m ()
basicUnsafeCopy (MV_BE mv) (V_BE v) = Mutable Vector (PrimState m) w -> Vector w -> m ()
forall (v :: * -> *) a (m :: * -> *).
(Vector v a, PrimMonad m) =>
Mutable v (PrimState m) a -> v a -> m ()
GV.basicUnsafeCopy MVector (PrimState m) w
Mutable Vector (PrimState m) w
mv Vector w
v
  elemseq :: Vector (BE w) -> BE w -> b -> b
elemseq Vector (BE w)
_ (BE w
x)                    = Vector w -> w -> b -> b
forall (v :: * -> *) a b. Vector v a => v a -> a -> b -> b
GV.elemseq (forall a. Vector a
forall a. HasCallStack => a
undefined :: Vector a) w
x