raaz-0.3.5: Fast and type safe cryptography.
Copyright(c) Piyush P Kurur 2018
LicenseApache-2.0 OR BSD-3-Clause
MaintainerPiyush P Kurur <ppk@iitpkd.ac.in>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Raaz.Core.Types.Internal

Description

WARNING: There is very little reason for importing this module even if you are a developer of raaz let alone a user. The one place where you enhance type safety by importing this module is where you define FFI calls --- consider this FFI call to memcpy

foreign import ccall unsafe "string.h memcpy" c_memcpy
   :: Dest Pointer -> Src Pointer -> BYTES Int -> IO Pointer

instead of this

foreign import ccall unsafe "string.h memcpy" c_memcpy
   :: Pointer -> Pointer -> Int -> IO Pointer
Synopsis

Documentation

newtype BlockCount p Source #

Type safe message length in units of blocks of the primitive. When dealing with buffer lengths for a primitive, it is often better to use the type safe units BlockCount. Functions in the raaz package that take lengths usually allow any type safe length as long as they can be converted to bytes. This can avoid a lot of tedious and error prone length calculations.

Constructors

BlockCount 

Fields

Instances

Instances details
Extractable ChaCha20Mem (BlockCount ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Initialisable ChaCha20Mem (BlockCount ChaCha20) Source # 
Instance details

Defined in Raaz.Primitive.ChaCha20.Internal

Enum (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Eq (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Methods

(==) :: BlockCount p -> BlockCount p -> Bool #

(/=) :: BlockCount p -> BlockCount p -> Bool #

Ord (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Show (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Semigroup (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Monoid (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Storable (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

Methods

sizeOf :: BlockCount p -> Int #

alignment :: BlockCount p -> Int #

peekElemOff :: Ptr (BlockCount p) -> Int -> IO (BlockCount p) #

pokeElemOff :: Ptr (BlockCount p) -> Int -> BlockCount p -> IO () #

peekByteOff :: Ptr b -> Int -> IO (BlockCount p) #

pokeByteOff :: Ptr b -> Int -> BlockCount p -> IO () #

peek :: Ptr (BlockCount p) -> IO (BlockCount p) #

poke :: Ptr (BlockCount p) -> BlockCount p -> IO () #

Primitive p => LengthUnit (BlockCount p) Source # 
Instance details

Defined in Raaz.Core.Primitive

newtype BE w Source #

Big endian version of the word type w

Constructors

BE 

Fields

Instances

Instances details
Functor BE Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

fmap :: (a -> b) -> BE a -> BE b #

(<$) :: a -> BE b -> BE a #

Initialisable Sha256Mem () Source # 
Instance details

Defined in Raaz.Primitive.Sha2.Internal

Methods

initialise :: () -> Sha256Mem -> IO () Source #

Initialisable Sha512Mem () Source # 
Instance details

Defined in Raaz.Primitive.Sha2.Internal

Methods

initialise :: () -> Sha512Mem -> IO () Source #

Unbox w => Vector Vector (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (BE w) -> m (Vector (BE w)) #

basicUnsafeThaw :: PrimMonad m => Vector (BE w) -> m (Mutable Vector (PrimState m) (BE w)) #

basicLength :: Vector (BE w) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (BE w) -> Vector (BE w) #

basicUnsafeIndexM :: Monad m => Vector (BE w) -> Int -> m (BE w) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (BE w) -> Vector (BE w) -> m () #

elemseq :: Vector (BE w) -> BE w -> b -> b #

Unbox w => MVector MVector (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

basicLength :: MVector s (BE w) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (BE w) -> MVector s (BE w) #

basicOverlaps :: MVector s (BE w) -> MVector s (BE w) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (BE w)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (BE w) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> BE w -> m (MVector (PrimState m) (BE w)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (BE w) -> Int -> m (BE w) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (BE w) -> Int -> BE w -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (BE w) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (BE w) -> BE w -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (BE w) -> MVector (PrimState m) (BE w) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (BE w) -> MVector (PrimState m) (BE w) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (BE w) -> Int -> m (MVector (PrimState m) (BE w)) #

Bounded w => Bounded (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

minBound :: BE w #

maxBound :: BE w #

Enum w => Enum (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

succ :: BE w -> BE w #

pred :: BE w -> BE w #

toEnum :: Int -> BE w #

fromEnum :: BE w -> Int #

enumFrom :: BE w -> [BE w] #

enumFromThen :: BE w -> BE w -> [BE w] #

enumFromTo :: BE w -> BE w -> [BE w] #

enumFromThenTo :: BE w -> BE w -> BE w -> [BE w] #

Eq w => Eq (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(==) :: BE w -> BE w -> Bool #

(/=) :: BE w -> BE w -> Bool #

Integral w => Integral (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

quot :: BE w -> BE w -> BE w #

rem :: BE w -> BE w -> BE w #

div :: BE w -> BE w -> BE w #

mod :: BE w -> BE w -> BE w #

quotRem :: BE w -> BE w -> (BE w, BE w) #

divMod :: BE w -> BE w -> (BE w, BE w) #

toInteger :: BE w -> Integer #

Num w => Num (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(+) :: BE w -> BE w -> BE w #

(-) :: BE w -> BE w -> BE w #

(*) :: BE w -> BE w -> BE w #

negate :: BE w -> BE w #

abs :: BE w -> BE w #

signum :: BE w -> BE w #

fromInteger :: Integer -> BE w #

Ord w => Ord (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

compare :: 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 #

max :: BE w -> BE w -> BE w #

min :: BE w -> BE w -> BE w #

Read w => Read (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Real w => Real (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

toRational :: BE w -> Rational #

Show w => Show (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

showsPrec :: Int -> BE w -> ShowS #

show :: BE w -> String #

showList :: [BE w] -> ShowS #

Storable w => Storable (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

sizeOf :: BE w -> Int #

alignment :: BE w -> Int #

peekElemOff :: Ptr (BE w) -> Int -> IO (BE w) #

pokeElemOff :: Ptr (BE w) -> Int -> BE w -> IO () #

peekByteOff :: Ptr b -> Int -> IO (BE w) #

pokeByteOff :: Ptr b -> Int -> BE w -> IO () #

peek :: Ptr (BE w) -> IO (BE w) #

poke :: Ptr (BE w) -> BE w -> IO () #

Bits w => Bits (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(.&.) :: BE w -> BE w -> BE w #

(.|.) :: BE w -> BE w -> BE w #

xor :: BE w -> BE w -> BE w #

complement :: BE w -> BE w #

shift :: BE w -> Int -> BE w #

rotate :: BE w -> Int -> BE w #

zeroBits :: BE w #

bit :: Int -> BE w #

setBit :: BE w -> Int -> BE w #

clearBit :: BE w -> Int -> BE w #

complementBit :: BE w -> Int -> BE w #

testBit :: BE w -> Int -> Bool #

bitSizeMaybe :: BE w -> Maybe Int #

bitSize :: BE w -> Int #

isSigned :: BE w -> Bool #

shiftL :: BE w -> Int -> BE w #

unsafeShiftL :: BE w -> Int -> BE w #

shiftR :: BE w -> Int -> BE w #

unsafeShiftR :: BE w -> Int -> BE w #

rotateL :: BE w -> Int -> BE w #

rotateR :: BE w -> Int -> BE w #

popCount :: BE w -> Int #

NFData w => NFData (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

rnf :: BE w -> () #

Unbox w => Unbox (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Equality w => Equality (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

eq :: BE w -> BE w -> Result Source #

EndianStore (BE Word32) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (BE Word32) -> BE Word32 -> IO () Source #

load :: Ptr (BE Word32) -> IO (BE Word32) Source #

adjustEndian :: Ptr (BE Word32) -> Int -> IO () Source #

EndianStore (BE Word64) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (BE Word64) -> BE Word64 -> IO () Source #

load :: Ptr (BE Word64) -> IO (BE Word64) Source #

adjustEndian :: Ptr (BE Word64) -> Int -> IO () Source #

Encodable (BE Word32) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable (BE Word64) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

newtype MVector s (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

newtype MVector s (BE w) = MV_BE (MVector s w)
newtype Vector (BE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

newtype Vector (BE w) = V_BE (Vector w)

newtype LE w Source #

Little endian version of the word type w

Constructors

LE 

Fields

Instances

Instances details
Functor LE Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

fmap :: (a -> b) -> LE a -> LE b #

(<$) :: a -> LE b -> LE a #

KeyedHash Blake2s Source # 
Instance details

Defined in Raaz.Primitive.Blake2.Internal

KeyedHash Blake2b Source # 
Instance details

Defined in Raaz.Primitive.Blake2.Internal

Initialisable Blake2sMem () Source # 
Instance details

Defined in Raaz.Primitive.Blake2.Internal

Methods

initialise :: () -> Blake2sMem -> IO () Source #

Initialisable Blake2bMem () Source # 
Instance details

Defined in Raaz.Primitive.Blake2.Internal

Methods

initialise :: () -> Blake2bMem -> IO () Source #

Unbox w => Vector Vector (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

basicUnsafeFreeze :: PrimMonad m => Mutable Vector (PrimState m) (LE w) -> m (Vector (LE w)) #

basicUnsafeThaw :: PrimMonad m => Vector (LE w) -> m (Mutable Vector (PrimState m) (LE w)) #

basicLength :: Vector (LE w) -> Int #

basicUnsafeSlice :: Int -> Int -> Vector (LE w) -> Vector (LE w) #

basicUnsafeIndexM :: Monad m => Vector (LE w) -> Int -> m (LE w) #

basicUnsafeCopy :: PrimMonad m => Mutable Vector (PrimState m) (LE w) -> Vector (LE w) -> m () #

elemseq :: Vector (LE w) -> LE w -> b -> b #

Unbox w => MVector MVector (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

basicLength :: MVector s (LE w) -> Int #

basicUnsafeSlice :: Int -> Int -> MVector s (LE w) -> MVector s (LE w) #

basicOverlaps :: MVector s (LE w) -> MVector s (LE w) -> Bool #

basicUnsafeNew :: PrimMonad m => Int -> m (MVector (PrimState m) (LE w)) #

basicInitialize :: PrimMonad m => MVector (PrimState m) (LE w) -> m () #

basicUnsafeReplicate :: PrimMonad m => Int -> LE w -> m (MVector (PrimState m) (LE w)) #

basicUnsafeRead :: PrimMonad m => MVector (PrimState m) (LE w) -> Int -> m (LE w) #

basicUnsafeWrite :: PrimMonad m => MVector (PrimState m) (LE w) -> Int -> LE w -> m () #

basicClear :: PrimMonad m => MVector (PrimState m) (LE w) -> m () #

basicSet :: PrimMonad m => MVector (PrimState m) (LE w) -> LE w -> m () #

basicUnsafeCopy :: PrimMonad m => MVector (PrimState m) (LE w) -> MVector (PrimState m) (LE w) -> m () #

basicUnsafeMove :: PrimMonad m => MVector (PrimState m) (LE w) -> MVector (PrimState m) (LE w) -> m () #

basicUnsafeGrow :: PrimMonad m => MVector (PrimState m) (LE w) -> Int -> m (MVector (PrimState m) (LE w)) #

Bounded w => Bounded (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

minBound :: LE w #

maxBound :: LE w #

Enum w => Enum (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

succ :: LE w -> LE w #

pred :: LE w -> LE w #

toEnum :: Int -> LE w #

fromEnum :: LE w -> Int #

enumFrom :: LE w -> [LE w] #

enumFromThen :: LE w -> LE w -> [LE w] #

enumFromTo :: LE w -> LE w -> [LE w] #

enumFromThenTo :: LE w -> LE w -> LE w -> [LE w] #

Eq w => Eq (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(==) :: LE w -> LE w -> Bool #

(/=) :: LE w -> LE w -> Bool #

Integral w => Integral (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

quot :: LE w -> LE w -> LE w #

rem :: LE w -> LE w -> LE w #

div :: LE w -> LE w -> LE w #

mod :: LE w -> LE w -> LE w #

quotRem :: LE w -> LE w -> (LE w, LE w) #

divMod :: LE w -> LE w -> (LE w, LE w) #

toInteger :: LE w -> Integer #

Num w => Num (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(+) :: LE w -> LE w -> LE w #

(-) :: LE w -> LE w -> LE w #

(*) :: LE w -> LE w -> LE w #

negate :: LE w -> LE w #

abs :: LE w -> LE w #

signum :: LE w -> LE w #

fromInteger :: Integer -> LE w #

Ord w => Ord (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

compare :: 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 #

max :: LE w -> LE w -> LE w #

min :: LE w -> LE w -> LE w #

Read w => Read (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Real w => Real (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

toRational :: LE w -> Rational #

Show w => Show (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

showsPrec :: Int -> LE w -> ShowS #

show :: LE w -> String #

showList :: [LE w] -> ShowS #

Storable w => Storable (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

sizeOf :: LE w -> Int #

alignment :: LE w -> Int #

peekElemOff :: Ptr (LE w) -> Int -> IO (LE w) #

pokeElemOff :: Ptr (LE w) -> Int -> LE w -> IO () #

peekByteOff :: Ptr b -> Int -> IO (LE w) #

pokeByteOff :: Ptr b -> Int -> LE w -> IO () #

peek :: Ptr (LE w) -> IO (LE w) #

poke :: Ptr (LE w) -> LE w -> IO () #

Bits w => Bits (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

(.&.) :: LE w -> LE w -> LE w #

(.|.) :: LE w -> LE w -> LE w #

xor :: LE w -> LE w -> LE w #

complement :: LE w -> LE w #

shift :: LE w -> Int -> LE w #

rotate :: LE w -> Int -> LE w #

zeroBits :: LE w #

bit :: Int -> LE w #

setBit :: LE w -> Int -> LE w #

clearBit :: LE w -> Int -> LE w #

complementBit :: LE w -> Int -> LE w #

testBit :: LE w -> Int -> Bool #

bitSizeMaybe :: LE w -> Maybe Int #

bitSize :: LE w -> Int #

isSigned :: LE w -> Bool #

shiftL :: LE w -> Int -> LE w #

unsafeShiftL :: LE w -> Int -> LE w #

shiftR :: LE w -> Int -> LE w #

unsafeShiftR :: LE w -> Int -> LE w #

rotateL :: LE w -> Int -> LE w #

rotateR :: LE w -> Int -> LE w #

popCount :: LE w -> Int #

NFData w => NFData (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

rnf :: LE w -> () #

Unbox w => Unbox (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Equality w => Equality (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

eq :: LE w -> LE w -> Result Source #

EndianStore (LE Word32) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (LE Word32) -> LE Word32 -> IO () Source #

load :: Ptr (LE Word32) -> IO (LE Word32) Source #

adjustEndian :: Ptr (LE Word32) -> Int -> IO () Source #

EndianStore (LE Word64) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (LE Word64) -> LE Word64 -> IO () Source #

load :: Ptr (LE Word64) -> IO (LE Word64) Source #

adjustEndian :: Ptr (LE Word64) -> Int -> IO () Source #

Encodable (LE Word32) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

Encodable (LE Word64) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

newtype MVector s (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

newtype MVector s (LE w) = MV_LE (MVector s w)
newtype Vector (LE w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

newtype Vector (LE w) = V_LE (Vector w)

newtype AlignedPtr (n :: Nat) a Source #

The type AlignedPtr n that captures pointers that are aligned to n byte boundary.

Constructors

AlignedPtr 

Fields

Instances

Instances details
KnownNat n => Pointer (AlignedPtr n) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

newtype BYTES a Source #

Type safe lengths/offsets in units of bytes.

Constructors

BYTES a 

Instances

Instances details
Functor BYTES Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

fmap :: (a -> b) -> BYTES a -> BYTES b #

(<$) :: a -> BYTES b -> BYTES a #

IsString WriteTo Source # 
Instance details

Defined in Raaz.Core.Transfer.Unsafe

Methods

fromString :: String -> WriteTo #

Encodable WriteTo Source # 
Instance details

Defined in Raaz.Core.Transfer.Unsafe

Unbox w => Vector Vector (BYTES w) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Unbox w => MVector MVector (BYTES w) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Bounded a => Bounded (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

minBound :: BYTES a #

maxBound :: BYTES a #

Enum a => Enum (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

succ :: BYTES a -> BYTES a #

pred :: BYTES a -> BYTES a #

toEnum :: Int -> BYTES a #

fromEnum :: BYTES a -> Int #

enumFrom :: BYTES a -> [BYTES a] #

enumFromThen :: BYTES a -> BYTES a -> [BYTES a] #

enumFromTo :: BYTES a -> BYTES a -> [BYTES a] #

enumFromThenTo :: BYTES a -> BYTES a -> BYTES a -> [BYTES a] #

Eq a => Eq (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

(==) :: BYTES a -> BYTES a -> Bool #

(/=) :: BYTES a -> BYTES a -> Bool #

Integral a => Integral (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

quot :: BYTES a -> BYTES a -> BYTES a #

rem :: BYTES a -> BYTES a -> BYTES a #

div :: BYTES a -> BYTES a -> BYTES a #

mod :: BYTES a -> BYTES a -> BYTES a #

quotRem :: BYTES a -> BYTES a -> (BYTES a, BYTES a) #

divMod :: BYTES a -> BYTES a -> (BYTES a, BYTES a) #

toInteger :: BYTES a -> Integer #

Num a => Num (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

(+) :: BYTES a -> BYTES a -> BYTES a #

(-) :: BYTES a -> BYTES a -> BYTES a #

(*) :: BYTES a -> BYTES a -> BYTES a #

negate :: BYTES a -> BYTES a #

abs :: BYTES a -> BYTES a #

signum :: BYTES a -> BYTES a #

fromInteger :: Integer -> BYTES a #

Ord a => Ord (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

compare :: BYTES a -> BYTES a -> Ordering #

(<) :: BYTES a -> BYTES a -> Bool #

(<=) :: BYTES a -> BYTES a -> Bool #

(>) :: BYTES a -> BYTES a -> Bool #

(>=) :: BYTES a -> BYTES a -> Bool #

max :: BYTES a -> BYTES a -> BYTES a #

min :: BYTES a -> BYTES a -> BYTES a #

Real a => Real (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

toRational :: BYTES a -> Rational #

Show a => Show (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

showsPrec :: Int -> BYTES a -> ShowS #

show :: BYTES a -> String #

showList :: [BYTES a] -> ShowS #

Num a => Semigroup (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

(<>) :: BYTES a -> BYTES a -> BYTES a #

sconcat :: NonEmpty (BYTES a) -> BYTES a #

stimes :: Integral b => b -> BYTES a -> BYTES a #

Num a => Monoid (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

mempty :: BYTES a #

mappend :: BYTES a -> BYTES a -> BYTES a #

mconcat :: [BYTES a] -> BYTES a #

Storable a => Storable (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

sizeOf :: BYTES a -> Int #

alignment :: BYTES a -> Int #

peekElemOff :: Ptr (BYTES a) -> Int -> IO (BYTES a) #

pokeElemOff :: Ptr (BYTES a) -> Int -> BYTES a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (BYTES a) #

pokeByteOff :: Ptr b -> Int -> BYTES a -> IO () #

peek :: Ptr (BYTES a) -> IO (BYTES a) #

poke :: Ptr (BYTES a) -> BYTES a -> IO () #

Bits a => Bits (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

(.&.) :: BYTES a -> BYTES a -> BYTES a #

(.|.) :: BYTES a -> BYTES a -> BYTES a #

xor :: BYTES a -> BYTES a -> BYTES a #

complement :: BYTES a -> BYTES a #

shift :: BYTES a -> Int -> BYTES a #

rotate :: BYTES a -> Int -> BYTES a #

zeroBits :: BYTES a #

bit :: Int -> BYTES a #

setBit :: BYTES a -> Int -> BYTES a #

clearBit :: BYTES a -> Int -> BYTES a #

complementBit :: BYTES a -> Int -> BYTES a #

testBit :: BYTES a -> Int -> Bool #

bitSizeMaybe :: BYTES a -> Maybe Int #

bitSize :: BYTES a -> Int #

isSigned :: BYTES a -> Bool #

shiftL :: BYTES a -> Int -> BYTES a #

unsafeShiftL :: BYTES a -> Int -> BYTES a #

shiftR :: BYTES a -> Int -> BYTES a #

unsafeShiftR :: BYTES a -> Int -> BYTES a #

rotateL :: BYTES a -> Int -> BYTES a #

rotateR :: BYTES a -> Int -> BYTES a #

popCount :: BYTES a -> Int #

Unbox w => Unbox (BYTES w) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Equality a => Equality (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

Methods

eq :: BYTES a -> BYTES a -> Result Source #

LengthUnit (BYTES Int) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

EndianStore w => EndianStore (BYTES w) Source # 
Instance details

Defined in Raaz.Core.Types.Endian

Methods

store :: Ptr (BYTES w) -> BYTES w -> IO () Source #

load :: Ptr (BYTES w) -> IO (BYTES w) Source #

adjustEndian :: Ptr (BYTES w) -> Int -> IO () Source #

Encodable a => Encodable (BYTES a) Source # 
Instance details

Defined in Raaz.Core.Encode.Internal

newtype MVector s (BYTES w) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

newtype MVector s (BYTES w) = MV_BYTES (MVector s w)
newtype Vector (BYTES w) Source # 
Instance details

Defined in Raaz.Core.Types.Pointer

newtype Vector (BYTES w) = V_BYTES (Vector w)

newtype Dest a Source #

The destination of a copy operation. Besides the destination smart constructor, the functor instance allows to transform the internal type using the fmap (e.g. given an dptr :: Dest (Ptr Word8) shift it by an offset).

For FFI use: One can use this type directly in FFI interface by importing Raaz.Core.Types.Internal to get access to the constructor.

Constructors

Dest 

Fields

Instances

Instances details
Functor Dest Source # 
Instance details

Defined in Raaz.Core.Types.Copying

Methods

fmap :: (a -> b) -> Dest a -> Dest b #

(<$) :: a -> Dest b -> Dest a #

newtype Src a Source #

The source of a copy operation. Besides the source smart constructor, the functor instance allows to transform the internal type using the fmap (e.g. given an sptr :: Src (Ptr Word8) shift it by an offset).

For FFI use: One can use this type directly in FFI interface by importing Raaz.Core.Types.Internal to get access to the constructor.

Constructors

Src 

Fields

Instances

Instances details
Functor Src Source # 
Instance details

Defined in Raaz.Core.Types.Copying

Methods

fmap :: (a -> b) -> Src a -> Src b #

(<$) :: a -> Src b -> Src a #

Length encoded tuples

data Tuple (dim :: Nat) a Source #

Tuples that encode their length in their types. For tuples, we call the length its dimension.

Instances

Instances details
(Unbox a, Equality a) => Eq (Tuple dim a) Source #

Equality checking is timing safe.

Instance details

Defined in Raaz.Core.Types.Tuple

Methods

(==) :: Tuple dim a -> Tuple dim a -> Bool #

(/=) :: Tuple dim a -> Tuple dim a -> Bool #

(Show a, Unbox a) => Show (Tuple dim a) Source # 
Instance details

Defined in Raaz.Core.Types.Tuple

Methods

showsPrec :: Int -> Tuple dim a -> ShowS #

show :: Tuple dim a -> String #

showList :: [Tuple dim a] -> ShowS #

(Unbox a, Storable a, Dimension dim) => Storable (Tuple dim a) Source # 
Instance details

Defined in Raaz.Core.Types.Tuple

Methods

sizeOf :: Tuple dim a -> Int #

alignment :: Tuple dim a -> Int #

peekElemOff :: Ptr (Tuple dim a) -> Int -> IO (Tuple dim a) #

pokeElemOff :: Ptr (Tuple dim a) -> Int -> Tuple dim a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Tuple dim a) #

pokeByteOff :: Ptr b -> Int -> Tuple dim a -> IO () #

peek :: Ptr (Tuple dim a) -> IO (Tuple dim a) #

poke :: Ptr (Tuple dim a) -> Tuple dim a -> IO () #

(Unbox a, Equality a) => Equality (Tuple dim a) Source # 
Instance details

Defined in Raaz.Core.Types.Tuple

Methods

eq :: Tuple dim a -> Tuple dim a -> Result Source #

(Unbox a, EndianStore a, Dimension dim) => EndianStore (Tuple dim a) Source # 
Instance details

Defined in Raaz.Core.Types.Tuple

Methods

store :: Ptr (Tuple dim a) -> Tuple dim a -> IO () Source #

load :: Ptr (Tuple dim a) -> IO (Tuple dim a) Source #

adjustEndian :: Ptr (Tuple dim a) -> Int -> IO () Source #

type Dimension (dim :: Nat) = KnownNat dim Source #

The constaint on the dimension of the tuple (since base 4.7.0)

dimension :: Dimension dim => Tuple dim a -> Int Source #

Function that returns the dimension of the tuple. The dimension is calculated without inspecting the tuple and hence the term dimension (undefined :: Tuple 5 Int) will evaluate to 5.

dimension' :: Dimension dim => Proxy (Tuple dim a) -> Int Source #

Function that returns the dimension from the proxy of the tuple. This is useful when we only have a proxy of the tuple at hand. This is clearly possible because the dimension calculation works at the type level and does not require looking at the value of the tuple.

initial :: (Unbox a, Dimension dim0) => Tuple dim1 a -> Tuple dim0 a Source #

Computes the initial fragment of a tuple. No length needs to be given as it is infered from the types.

diagonal :: (Unbox a, Dimension dim) => a -> Tuple dim a Source #

The diagonal a gives a tuple, all of whose entries is a.

repeatM :: (Monad m, Unbox a, Dimension dim) => m a -> m (Tuple dim a) Source #

Construct a tuple by repeating a monadic action.

zipWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Tuple dim a -> Tuple dim b -> Tuple dim c Source #

A zipwith function for tuples

map :: (Unbox a, Unbox b) => (a -> b) -> Tuple dim a -> Tuple dim b Source #

Map function for tuples.

generateIO :: (Dimension dim, Unbox a) => IO a -> IO (Tuple dim a) Source #

Generate using the given action.

Unsafe operations

unsafeFromList :: (Unbox a, Dimension dim) => [a] -> Tuple dim a Source #

Construct a tuple out of the list. This function is unsafe and will result in run time error if the list is not of the correct dimension.

unsafeFromVector :: Vector a -> Tuple dim a Source #

Convert vector to tuple. This function is unsafe because it does not check whether length of the vector matches with the tuple dimension.

unsafeToVector :: Tuple dim a -> Vector a Source #

Convert the tuple to vector.