Safe Haskell | None |
---|
Documentation
Foreign representation is the heart of Yarr framework.
Internally it holds raw pointer (Ptr
), which makes indexing
foreign arrays not slower than GHC's built-in primitive arrays,
but without freeze/thaw boilerplate.
Foreign arrays are very permissible, for example you can easily
use them as source and target of Load
ing operation simultaneously,
achieving old good in-place C-
style array modifying:
loadS
fill
(dmap
sqrt
arr) arr
Foreign arrays are intented to hold all Storable
types and
vectors of them (because there is a conditional instance of Storalbe
class for Vector
s of Storable
s too).
(Shape sh, Storable a) => UTarget F L sh a | |
(Shape sh, Storable a) => USource F L sh a | |
Shape sh => Regular F L sh a | |
DefaultFusion F D L sh | |
(Shape sh, Storable a) => Manifest F F L sh a | |
Shape sh => DefaultIFusion F L D SH sh | |
(Shape sh, Vector v e, Storable e) => UVecTarget F FS L sh v e | |
(Shape sh, Vector v e, Storable e) => UVecSource F FS L sh v e | |
(Shape sh, Vector v e, Storable e) => VecRegular F FS L sh v e | |
(Shape sh, Vector v e, Storable e) => UVecSource (SE F) F L sh v e | |
Shape sh => NFData (UArray F L sh a) |
Foreign Slice representation, view slice representation
for F
oreign arrays.
To understand Foreign Slices,
suppose you have standard image
array of
type.
UArray
F
Dim2
(VecList
N3
Word8)
It's layout in memory (with array indices):
r g b | r g b | r g b | ... (0, 0) (0, 1) (0, 2) ...
let (VecList [reds, greens, blues]) = slices
image
-- reds, greens, blues :: UArray FS Dim2 Word8
Now blues
just indexes each third byte on the same underlying
memory block:
... b | ... b | ... b | ... (0, 0) (0, 1) (0, 2)...
(Shape sh, Storable e) => UTarget FS L sh e | |
(Shape sh, Storable e) => USource FS L sh e | |
Shape sh => Regular FS L sh e | |
DefaultFusion FS D L sh | |
Shape sh => DefaultIFusion FS L D SH sh | |
(Shape sh, Vector v e, Storable e) => UVecTarget F FS L sh v e | |
(Shape sh, Vector v e, Storable e) => UVecSource F FS L sh v e | |
(Shape sh, Vector v e, Storable e) => VecRegular F FS L sh v e | |
Shape sh => NFData (UArray FS L sh e) |
There are also ForeignArray
and ForeignSlice
UArray
family constructors,
which aren't presented in the docs because Haddock
doesn't support associated family constructors.
See source of Data.Yarr.Repr.Foreign module.
class Storable a
The member functions of this class facilitate writing values of primitive types to raw memory (which may have been allocated with the above mentioned routines) and reading values from blocks of raw memory. The class, furthermore, includes support for computing the storage requirements and alignment restrictions of storable types.
Memory addresses are represented as values of type
, for some
Ptr
aa
which is an instance of class Storable
. The type argument to
Ptr
helps provide some valuable type safety in FFI code (you can't
mix pointers of different types without an explicit cast), while
helping the Haskell type system figure out which marshalling method is
needed for a given pointer.
All marshalling between Haskell and a foreign language ultimately
boils down to translating Haskell data structures into the binary
representation of a corresponding data structure of the foreign
language and vice versa. To code this marshalling in Haskell, it is
necessary to manipulate primitive data types stored in unstructured
memory blocks. The class Storable
facilitates this manipulation on
all types for which it is instantiated, which are the standard basic
types of Haskell, the fixed size Int
types (Int8
, Int16
,
Int32
, Int64
), the fixed size Word
types (Word8
, Word16
,
Word32
, Word64
), StablePtr
, all types from Foreign.C.Types,
as well as Ptr
.
Minimal complete definition: sizeOf
, alignment
, one of peek
,
peekElemOff
and peekByteOff
, and one of poke
, pokeElemOff
and
pokeByteOff
.
Storable Bool | |
Storable Char | |
Storable Double | |
Storable Float | |
Storable Int | |
Storable Int8 | |
Storable Int16 | |
Storable Int32 | |
Storable Int64 | |
Storable Word | |
Storable Word8 | |
Storable Word16 | |
Storable Word32 | |
Storable Word64 | |
Storable Fingerprint | |
Storable (StablePtr a) | |
Storable (Ptr a) | |
Storable (FunPtr a) | |
(Storable e, Vector v e) => Storable (v e) |
Linear load type index. UArray
s with L
load type index
define linearIndex
and linearWrite
and leave index
and write
functions defined by default.
WorkIndex sh Int => PreferredWorkIndex L sh Int | |
(Shape sh, Storable e) => UTarget FS L sh e | |
(Shape sh, Storable a) => UTarget F L sh a | |
(Shape sh, NFData a) => UTarget MB L sh a | |
Shape sh => USource D L sh a | |
(Shape sh, Storable e) => USource FS L sh e | |
(Shape sh, Storable a) => USource F L sh a | |
(Shape sh, NFData a) => USource MB L sh a | |
(Shape sh, NFData a) => USource B L sh a | |
Shape sh => Regular D L sh a | |
Shape sh => Regular FS L sh e | |
Shape sh => Regular F L sh a | |
(Shape sh, NFData a) => Regular MB L sh a | |
(Shape sh, NFData a) => Regular B L sh a | |
DefaultFusion D D L sh | |
DefaultFusion FS D L sh | |
DefaultFusion F D L sh | |
DefaultFusion MB D L sh | |
DefaultFusion B D L sh | |
Fusion r D L sh | |
(Shape sh, Storable a) => Manifest F F L sh a | |
(Shape sh, NFData a) => Manifest B MB L sh a | |
Shape sh => DefaultIFusion D L D SH sh | |
Shape sh => DefaultIFusion FS L D SH sh | |
Shape sh => DefaultIFusion F L D SH sh | |
Shape sh => DefaultIFusion MB L D SH sh | |
Shape sh => DefaultIFusion B L D SH sh | |
(Shape sh, Vector v e, Storable e) => UVecTarget F FS L sh v e | |
(Shape sh, Vector v e) => UVecSource D D L sh v e | |
(Shape sh, Vector v e, Storable e) => UVecSource F FS L sh v e | |
(Shape sh, Vector v e) => VecRegular D D L sh v e | |
(Shape sh, Vector v e, Storable e) => VecRegular F FS L sh v e | |
Load r L tr SH sh a => RangeLoad r L tr SH sh a | |
Load r SH tr L sh a => RangeLoad r SH tr L sh a | |
Load r L tr L sh a => RangeLoad r L tr L sh a | |
(USource r L sh a, UTarget tr SH sh a) => Load r L tr SH sh a | |
(USource r SH sh a, UTarget tr L sh a) => Load r SH tr L sh a | |
(USource r L sh a, UTarget tr L sh a, WorkIndex sh Int) => Load r L tr L sh a | |
(VecLoad r slr L tr tslr SH sh v v2 e, RangeLoad slr L tslr SH sh e) => RangeVecLoad r slr L tr tslr SH sh v v2 e | |
(VecLoad r slr SH tr tslr L sh v v2 e, RangeLoad slr SH tslr L sh e) => RangeVecLoad r slr SH tr tslr L sh v v2 e | |
(VecLoad r slr L tr tslr L sh v v2 e, RangeLoad slr L tslr L sh e) => RangeVecLoad r slr L tr tslr L sh v v2 e | |
(UVecSource r slr L sh v e, UVecTarget tr tslr SH sh v2 e, Load slr L tslr SH sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr L tr tslr SH sh v v2 e | |
(UVecSource r slr SH sh v e, UVecTarget tr tslr L sh v2 e, Load slr SH tslr L sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr SH tr tslr L sh v v2 e | |
(UVecSource r slr L sh v e, UVecTarget tr tslr L sh v2 e, Load slr L tslr L sh e, ~ * (Dim v) (Dim v2)) => VecLoad r slr L tr tslr L sh v v2 e | |
(Shape sh, Vector v e, Storable e) => UVecSource (SE F) F L sh v e | |
(Shape sh, Vector v e, NFData e) => UVecSource (SE MB) MB L sh v e | |
(Shape sh, Vector v e, NFData e) => UVecSource (SE B) B L sh v e | |
Shape sh => NFData (UArray D L sh a) | |
Shape sh => NFData (UArray FS L sh e) | |
Shape sh => NFData (UArray F L sh a) | |
(Shape sh, NFData a) => NFData (UArray MB L sh a) | |
(Shape sh, NFData a) => NFData (UArray B L sh a) |
newEmpty :: (Shape sh, Storable a, Integral a) => sh -> IO (UArray F L sh a)Source
O(1) allocates zero-initialized foreign array.
Needed because common new
function allocates array with garbage.
toForeignPtr :: Shape sh => UArray F L sh a -> ForeignPtr aSource
O(1) Returns pointer to memory block used by the given foreign array.
May be useful to reuse memory if you don't longer need the given array in the program:
brandNewData <-unsafeFromForeignPtr
ext (castForeignPtr
(toForeignPtr arr))
unsafeFromForeignPtr :: Shape sh => sh -> ForeignPtr a -> IO (UArray F L sh a)Source
O(1) Wraps foreign ptr into foreign array.
The function is unsafe because it simply don't (and can't) check anything about correctness of produced array.