Copyright | (c) Piyush P Kurur 2018 |
---|---|
License | Apache-2.0 OR BSD-3-Clause |
Maintainer | Piyush P Kurur <ppk@iitpkd.ac.in> |
Stability | experimental |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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
- newtype BlockCount p = BlockCount {
- unBlockCount :: Int
- newtype LE w = LE {
- unLE :: w
- newtype BE w = BE {
- unBE :: w
- newtype AlignedPtr (n :: Nat) a = AlignedPtr {
- forgetAlignment :: Ptr a
- newtype BYTES a = BYTES a
- newtype Src a = Src {
- unSrc :: a
- newtype Dest a = Dest {
- unDest :: a
- data Tuple (dim :: Nat) a
- type Dimension (dim :: Nat) = KnownNat dim
- dimension :: Dimension dim => Tuple dim a -> Int
- dimension' :: Dimension dim => Proxy (Tuple dim a) -> Int
- initial :: (Unbox a, Dimension dim0) => Tuple dim1 a -> Tuple dim0 a
- diagonal :: (Unbox a, Dimension dim) => a -> Tuple dim a
- repeatM :: (Monad m, Unbox a, Dimension dim) => m a -> m (Tuple dim a)
- zipWith :: (Unbox a, Unbox b, Unbox c) => (a -> b -> c) -> Tuple dim a -> Tuple dim b -> Tuple dim c
- map :: (Unbox a, Unbox b) => (a -> b) -> Tuple dim a -> Tuple dim b
- generateIO :: (Dimension dim, Unbox a) => IO a -> IO (Tuple dim a)
- unsafeFromList :: (Unbox a, Dimension dim) => [a] -> Tuple dim a
- unsafeFromVector :: Vector a -> Tuple dim a
- unsafeToVector :: Tuple dim a -> Vector a
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.
Instances
Little endian version of the word type w
Instances
Big endian version of the word type w
Instances
newtype AlignedPtr (n :: Nat) a Source #
The type AlignedPtr n
that captures pointers that are aligned
to n
byte boundary.
AlignedPtr | |
|
Instances
KnownNat n => Pointer (AlignedPtr n) Source # | |
Defined in Raaz.Core.Types.Pointer castPointer :: AlignedPtr n a -> AlignedPtr n b Source # allocaPointer :: BYTES Int -> (AlignedPtr n a -> IO b) -> IO b Source # unsafeRawPtr :: AlignedPtr n a -> Ptr a Source # |
Type safe lengths/offsets in units of bytes.
BYTES a |
Instances
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.
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.
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
(Unbox a, Storable a, Dimension dim) => Storable (Tuple dim a) Source # | |
Defined in Raaz.Core.Types.Tuple 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 () # | |
(Show a, Unbox a) => Show (Tuple dim a) Source # | |
(Unbox a, Equality a) => Eq (Tuple dim a) Source # | Equality checking is timing safe. |
(Unbox a, EndianStore a, Dimension dim) => EndianStore (Tuple dim a) Source # | |
(Unbox a, Equality a) => Equality (Tuple dim a) 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
will evaluate to 5.dimension
(undefined :: Tuple 5 Int)
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.