dense-0.1.0.1: Mutable and immutable dense multidimensional arrays
Copyright(c) Christopher Chalmers
LicenseBSD3
MaintainerChristopher Chalmers
Stabilityprovisional
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Dense.Storable

Description

Storeable multidimentional arrays.

Synopsis

SArray types

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 Ptr a, for some a 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, (peek | peekElemOff | peekByteOff), (poke | pokeElemOff | pokeByteOff)

Instances

Instances details
Storable Bool

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Bool -> Int #

alignment :: Bool -> Int #

peekElemOff :: Ptr Bool -> Int -> IO Bool #

pokeElemOff :: Ptr Bool -> Int -> Bool -> IO () #

peekByteOff :: Ptr b -> Int -> IO Bool #

pokeByteOff :: Ptr b -> Int -> Bool -> IO () #

peek :: Ptr Bool -> IO Bool #

poke :: Ptr Bool -> Bool -> IO () #

Storable Char

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Char -> Int #

alignment :: Char -> Int #

peekElemOff :: Ptr Char -> Int -> IO Char #

pokeElemOff :: Ptr Char -> Int -> Char -> IO () #

peekByteOff :: Ptr b -> Int -> IO Char #

pokeByteOff :: Ptr b -> Int -> Char -> IO () #

peek :: Ptr Char -> IO Char #

poke :: Ptr Char -> Char -> IO () #

Storable Double

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Float

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Float -> Int #

alignment :: Float -> Int #

peekElemOff :: Ptr Float -> Int -> IO Float #

pokeElemOff :: Ptr Float -> Int -> Float -> IO () #

peekByteOff :: Ptr b -> Int -> IO Float #

pokeByteOff :: Ptr b -> Int -> Float -> IO () #

peek :: Ptr Float -> IO Float #

poke :: Ptr Float -> Float -> IO () #

Storable Int

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int -> Int #

alignment :: Int -> Int #

peekElemOff :: Ptr Int -> Int -> IO Int #

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

peekByteOff :: Ptr b -> Int -> IO Int #

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

peek :: Ptr Int -> IO Int #

poke :: Ptr Int -> Int -> IO () #

Storable Int8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int8 -> Int #

alignment :: Int8 -> Int #

peekElemOff :: Ptr Int8 -> Int -> IO Int8 #

pokeElemOff :: Ptr Int8 -> Int -> Int8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int8 #

pokeByteOff :: Ptr b -> Int -> Int8 -> IO () #

peek :: Ptr Int8 -> IO Int8 #

poke :: Ptr Int8 -> Int8 -> IO () #

Storable Int16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int16 -> Int #

alignment :: Int16 -> Int #

peekElemOff :: Ptr Int16 -> Int -> IO Int16 #

pokeElemOff :: Ptr Int16 -> Int -> Int16 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int16 #

pokeByteOff :: Ptr b -> Int -> Int16 -> IO () #

peek :: Ptr Int16 -> IO Int16 #

poke :: Ptr Int16 -> Int16 -> IO () #

Storable Int32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int32 -> Int #

alignment :: Int32 -> Int #

peekElemOff :: Ptr Int32 -> Int -> IO Int32 #

pokeElemOff :: Ptr Int32 -> Int -> Int32 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int32 #

pokeByteOff :: Ptr b -> Int -> Int32 -> IO () #

peek :: Ptr Int32 -> IO Int32 #

poke :: Ptr Int32 -> Int32 -> IO () #

Storable Int64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Int64 -> Int #

alignment :: Int64 -> Int #

peekElemOff :: Ptr Int64 -> Int -> IO Int64 #

pokeElemOff :: Ptr Int64 -> Int -> Int64 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Int64 #

pokeByteOff :: Ptr b -> Int -> Int64 -> IO () #

peek :: Ptr Int64 -> IO Int64 #

poke :: Ptr Int64 -> Int64 -> IO () #

Storable Word

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word -> Int #

alignment :: Word -> Int #

peekElemOff :: Ptr Word -> Int -> IO Word #

pokeElemOff :: Ptr Word -> Int -> Word -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word #

pokeByteOff :: Ptr b -> Int -> Word -> IO () #

peek :: Ptr Word -> IO Word #

poke :: Ptr Word -> Word -> IO () #

Storable Word8

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Word8 -> Int #

alignment :: Word8 -> Int #

peekElemOff :: Ptr Word8 -> Int -> IO Word8 #

pokeElemOff :: Ptr Word8 -> Int -> Word8 -> IO () #

peekByteOff :: Ptr b -> Int -> IO Word8 #

pokeByteOff :: Ptr b -> Int -> Word8 -> IO () #

peek :: Ptr Word8 -> IO Word8 #

poke :: Ptr Word8 -> Word8 -> IO () #

Storable Word16

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word32

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable Word64

Since: base-2.1

Instance details

Defined in Foreign.Storable

Storable ()

Since: base-4.9.0.0

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: () -> Int #

alignment :: () -> Int #

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

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

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

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

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

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

Storable Fingerprint

Since: base-4.4.0.0

Instance details

Defined in Foreign.Storable

(Storable a, Integral a) => Storable (Ratio a)

Since: base-4.8.0.0

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ratio a -> Int #

alignment :: Ratio a -> Int #

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

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

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

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

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

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

Storable (StablePtr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: StablePtr a -> Int #

alignment :: StablePtr a -> Int #

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

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

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

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

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

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

Storable (Ptr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: Ptr a -> Int #

alignment :: Ptr a -> Int #

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

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

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

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

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

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

Storable (FunPtr a)

Since: base-2.1

Instance details

Defined in Foreign.Storable

Methods

sizeOf :: FunPtr a -> Int #

alignment :: FunPtr a -> Int #

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

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

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

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

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

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

Storable a => Storable (Complex a)

Since: base-4.8.0.0

Instance details

Defined in Data.Complex

Methods

sizeOf :: Complex a -> Int #

alignment :: Complex a -> Int #

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

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

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

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

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

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

Storable a => Storable (Identity a)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Identity

Methods

sizeOf :: Identity a -> Int #

alignment :: Identity a -> Int #

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

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

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

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

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

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

Storable a => Storable (Down a)

Since: base-4.14.0.0

Instance details

Defined in Data.Ord

Methods

sizeOf :: Down a -> Int #

alignment :: Down a -> Int #

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

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

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

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

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

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

Storable a => Storable (Plucker a) 
Instance details

Defined in Linear.Plucker

Methods

sizeOf :: Plucker a -> Int #

alignment :: Plucker a -> Int #

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

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

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

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

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

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

Storable a => Storable (Quaternion a) 
Instance details

Defined in Linear.Quaternion

Methods

sizeOf :: Quaternion a -> Int #

alignment :: Quaternion a -> Int #

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

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

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

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

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

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

Storable (V0 a) 
Instance details

Defined in Linear.V0

Methods

sizeOf :: V0 a -> Int #

alignment :: V0 a -> Int #

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

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

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

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

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

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

Storable a => Storable (V4 a) 
Instance details

Defined in Linear.V4

Methods

sizeOf :: V4 a -> Int #

alignment :: V4 a -> Int #

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

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

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

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

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

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

Storable a => Storable (V3 a) 
Instance details

Defined in Linear.V3

Methods

sizeOf :: V3 a -> Int #

alignment :: V3 a -> Int #

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

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

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

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

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

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

Storable a => Storable (V2 a) 
Instance details

Defined in Linear.V2

Methods

sizeOf :: V2 a -> Int #

alignment :: V2 a -> Int #

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

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

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

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

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

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

Storable a => Storable (V1 a) 
Instance details

Defined in Linear.V1

Methods

sizeOf :: V1 a -> Int #

alignment :: V1 a -> Int #

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

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

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

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

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

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

Prim a => Storable (PrimStorable a) 
Instance details

Defined in Data.Primitive.Types

Storable a => Storable (Const a b)

Since: base-4.9.0.0

Instance details

Defined in Data.Functor.Const

Methods

sizeOf :: Const a b -> Int #

alignment :: Const a b -> Int #

peekElemOff :: Ptr (Const a b) -> Int -> IO (Const a b) #

pokeElemOff :: Ptr (Const a b) -> Int -> Const a b -> IO () #

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

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

peek :: Ptr (Const a b) -> IO (Const a b) #

poke :: Ptr (Const a b) -> Const a b -> IO () #

Storable a => Storable (Tagged s a) 
Instance details

Defined in Data.Tagged

Methods

sizeOf :: Tagged s a -> Int #

alignment :: Tagged s a -> Int #

peekElemOff :: Ptr (Tagged s a) -> Int -> IO (Tagged s a) #

pokeElemOff :: Ptr (Tagged s a) -> Int -> Tagged s a -> IO () #

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

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

peek :: Ptr (Tagged s a) -> IO (Tagged s a) #

poke :: Ptr (Tagged s a) -> Tagged s a -> IO () #

(Dim n, Storable a) => Storable (V n a) 
Instance details

Defined in Linear.V

Methods

sizeOf :: V n a -> Int #

alignment :: V n a -> Int #

peekElemOff :: Ptr (V n a) -> Int -> IO (V n a) #

pokeElemOff :: Ptr (V n a) -> Int -> V n a -> IO () #

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

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

peek :: Ptr (V n a) -> IO (V n a) #

poke :: Ptr (V n a) -> V n a -> IO () #

class (Eq1 f, Additive f, Traversable f) => Shape f Source #

Class for types that can be converted to and from linear indexes.

Instances

Instances details
Shape V0 Source # 
Instance details

Defined in Data.Dense.Index

Shape V4 Source # 
Instance details

Defined in Data.Dense.Index

Shape V3 Source # 
Instance details

Defined in Data.Dense.Index

Shape V2 Source # 
Instance details

Defined in Data.Dense.Index

Shape V1 Source # 
Instance details

Defined in Data.Dense.Index

Layout of an array

class Shape f => HasLayout f a | a -> f where Source #

Class of things that have a Layout. This means we can use the same functions for the various different arrays in the library.

Minimal complete definition

Nothing

Methods

layout :: Lens' a (Layout f) Source #

Lens onto the Layout of something.

default layout :: a ~ f Int => (Layout f -> g (Layout f)) -> a -> g a Source #

Instances

Instances details
i ~ Int => HasLayout V0 (V0 i) Source # 
Instance details

Defined in Data.Dense.Index

Methods

layout :: Lens' (V0 i) (Layout V0) Source #

i ~ Int => HasLayout V4 (V4 i) Source # 
Instance details

Defined in Data.Dense.Index

Methods

layout :: Lens' (V4 i) (Layout V4) Source #

i ~ Int => HasLayout V3 (V3 i) Source # 
Instance details

Defined in Data.Dense.Index

Methods

layout :: Lens' (V3 i) (Layout V3) Source #

i ~ Int => HasLayout V2 (V2 i) Source # 
Instance details

Defined in Data.Dense.Index

Methods

layout :: Lens' (V2 i) (Layout V2) Source #

i ~ Int => HasLayout V1 (V1 i) Source # 
Instance details

Defined in Data.Dense.Index

Methods

layout :: Lens' (V1 i) (Layout V1) Source #

Shape f => HasLayout f (Focused f a) Source #

The size of the layout must remain the same or an error is thrown.

Instance details

Defined in Data.Dense.Base

Methods

layout :: Lens' (Focused f a) (Layout f) Source #

Shape f => HasLayout f (Delayed f a) Source #

The size of the layout must remain the same or an error is thrown.

Instance details

Defined in Data.Dense.Base

Methods

layout :: Lens' (Delayed f a) (Layout f) Source #

Shape f => HasLayout f (Array v f a) Source #

The size of the layout must remain the same or an error is thrown.

Instance details

Defined in Data.Dense.Base

Methods

layout :: Lens' (Array v f a) (Layout f) Source #

Shape f => HasLayout f (MArray v f s a) Source # 
Instance details

Defined in Data.Dense.Mutable

Methods

layout :: Lens' (MArray v f s a) (Layout f) Source #

type Layout f = f Int Source #

A Layout is the full size of an array. This alias is used to help distinguish between the layout of an array and an index (usually just l Int) in a type signature.

Extracting size

extent :: HasLayout f a => a -> f Int Source #

Get the extent of an array.

extent :: Array v f a    -> f Int
extent :: MArray v f s a -> f Int
extent :: Delayed f a    -> f Int
extent :: Focused f a    -> f Int

size :: HasLayout f a => a -> Int Source #

Get the total number of elements in an array.

size :: Array v f a    -> Int
size :: MArray v f s a -> Int
size :: Delayed f a    -> Int
size :: Focused f a    -> Int

Folds over indexes

indexes :: HasLayout f a => IndexedFold Int a (f Int) Source #

Indexed fold for all the indexes in the layout.

indexesFrom :: HasLayout f a => f Int -> IndexedFold Int a (f Int) Source #

Indexed fold starting starting from some point, where the index is the linear index for the original layout.

indexesBetween :: HasLayout f a => f Int -> f Int -> IndexedFold Int a (f Int) Source #

Indexed fold between the two indexes where the index is the linear index for the original layout.

Underlying vector

vector :: (Storable a, Storable b) => IndexedLens (Layout f) (SArray f a) (SArray f b) (Vector a) (Vector b) Source #

Indexed lens over the underlying vector of an array. The index is the extent of the array. You must _not_ change the length of the vector, otherwise an error will be thrown (even for V1 layouts, use flat for V1).

Traversals

values :: (Shape f, Storable a, Storable b) => IndexedTraversal (f Int) (SArray f a) (SArray f b) a b Source #

Same as values but restrictive in the vector type.

values' :: (Shape f, Storable a, Storable b) => IndexedTraversal (f Int) (SArray f a) (SArray f b) a b Source #

Same as values but restrictive in the vector type.

valuesBetween :: (Shape f, Storable a) => f Int -> f Int -> IndexedTraversal' (f Int) (SArray f a) a Source #

Same as values but restrictive in the vector type.

Construction

Flat arrays

flat :: Storable b => Iso (SArray V1 a) (SArray V1 b) (Vector a) (Vector b) Source #

1D arrays are just vectors. You are free to change the length of the vector when going over this Iso (unlike linear).

Note that V1 arrays are an instance of Vector so you can use any of the functions in Generic on them without needing to convert.

fromList :: Storable a => [a] -> SArray V1 a Source #

Contruct a flat array from a list. (This is just fromList from Generic.)

From lists

fromListInto :: (Shape f, Storable a) => Layout f -> [a] -> Maybe (SArray f a) Source #

O(n) Convert the first n elements of a list to an SArrayith the given shape. Returns Nothing if there are not enough elements in the list.

fromListInto_ :: (Shape f, Storable a) => Layout f -> [a] -> SArray f a Source #

O(n) Convert the first n elements of a list to an SArrayith the given shape. Throw an error if the list is not long enough.

From vectors

fromVectorInto :: (Shape f, Storable a) => Layout f -> Vector a -> Maybe (SArray f a) Source #

Create an array from a vector and a layout. Return Nothing if the vector is not the right shape.

fromVectorInto_ :: (Shape f, Storable a) => Layout f -> Vector a -> SArray f a Source #

Create an array from a vector and a layout. Throws an error if the vector is not the right shape.

Initialisation

replicate :: (Shape f, Storable a) => f Int -> a -> SArray f a Source #

O(n) SArray of the given shape with the same value in each position.

generate :: (Shape f, Storable a) => Layout f -> (f Int -> a) -> SArray f a Source #

O(n) Construct an array of the given shape by applying the function to each index.

linearGenerate :: (Shape f, Storable a) => Layout f -> (Int -> a) -> SArray f a Source #

O(n) Construct an array of the given shape by applying the function to each index.

Monadic initialisation

create :: Storable a => (forall s. ST s (SMArray f s a)) -> SArray f a Source #

Execute the monadic action and freeze the resulting array.

replicateM :: (Monad m, Shape f, Storable a) => Layout f -> m a -> m (SArray f a) Source #

O(n) Construct an array of the given shape by filling each position with the monadic value.

generateM :: (Monad m, Shape f, Storable a) => Layout f -> (f Int -> m a) -> m (SArray f a) Source #

O(n) Construct an array of the given shape by applying the monadic function to each index.

linearGenerateM :: (Monad m, Shape f, Storable a) => Layout f -> (Int -> m a) -> m (SArray f a) Source #

O(n) Construct an array of the given shape by applying the monadic function to each index.

Functions on arrays

Empty arrays

empty :: (Storable a, Additive f) => SArray f a Source #

The empty SArray with a zero shape.

null :: Foldable f => SArray f a -> Bool Source #

Test is if the array is empty.

Indexing

(!) :: (Shape f, Storable a) => SArray f a -> f Int -> a Source #

Index an element of an array. Throws IndexOutOfBounds if the index is out of bounds.

(!?) :: (Shape f, Storable a) => SArray f a -> f Int -> Maybe a Source #

Safe index of an element.

unsafeIndex :: (Shape f, Storable a) => SArray f a -> f Int -> a Source #

Index an element of an array without bounds checking.

linearIndex :: Storable a => SArray f a -> Int -> a Source #

Index an element of an array while ignoring its shape.

unsafeLinearIndex :: Storable a => SArray f a -> Int -> a Source #

Index an element of an array while ignoring its shape, without bounds checking.

Monadic indexing

indexM :: (Shape f, Storable a, Monad m) => SArray f a -> f Int -> m a Source #

O(1) Indexing in a monad.

The monad allows operations to be strict in the vector when necessary. Suppose vector copying is implemented like this:

copy mv v = ... write mv i (v ! i) ...

For lazy vectors, v ! i would not be evaluated which means that mv would unnecessarily retain a reference to v in each element written.

With indexM, copying can be implemented like this instead:

copy mv v = ... do
  x <- indexM v i
  write mv i x

Here, no references to v are retained because indexing (but not the elements) is evaluated eagerly.

Throws an error if the index is out of range.

unsafeIndexM :: (Shape f, Storable a, Monad m) => SArray f a -> f Int -> m a Source #

O(1) Indexing in a monad without bounds checks. See indexM for an explanation of why this is useful.

linearIndexM :: (Shape f, Storable a, Monad m) => SArray f a -> Int -> m a Source #

O(1) Indexing in a monad. Throws an error if the index is out of range.

unsafeLinearIndexM :: (Storable a, Monad m) => SArray f a -> Int -> m a Source #

O(1) Indexing in a monad without bounds checks. See indexM for an explanation of why this is useful.

Modifying arrays

Bulk updates

(//) :: (Storable a, Shape f) => SArray f a -> [(f Int, a)] -> SArray f a Source #

For each pair (i,a) from the list, replace the array element at position i by a.

Accumulations

accum Source #

Arguments

:: (Shape f, Storable a) 
=> (a -> b -> a)

accumulating function f

-> SArray f a

initial array

-> [(f Int, b)]

list of index/value pairs (of length n)

-> SArray f a 

O(m+n) For each pair (i,b) from the list, replace the array element a at position i by f a b.

Mapping

map :: (Storable a, Storable b) => (a -> b) -> SArray f a -> SArray f b Source #

O(n) Map a function over an array

imap :: (Shape f, Storable a, Storable b) => (f Int -> a -> b) -> SArray f a -> SArray f b Source #

O(n) Apply a function to every element of a vector and its index

Zipping

Zip with function

zipWith :: (Shape f, Storable a, Storable b, Storable c) => (a -> b -> c) -> SArray f a -> SArray f b -> SArray f c Source #

Zip two arrays using the given function. If the array's don't have the same shape, the new array with be the intersection of the two shapes.

zipWith3 :: (Shape f, Storable a, Storable b, Storable c, Storable d) => (a -> b -> c -> d) -> SArray f a -> SArray f b -> SArray f c -> SArray f d Source #

Zip three arrays using the given function. If the array's don't have the same shape, the new array with be the intersection of the two shapes.

izipWith :: (Shape f, Storable a, Storable b, Storable c) => (f Int -> a -> b -> c) -> SArray f a -> SArray f b -> SArray f c Source #

Zip two arrays using the given function with access to the index. If the array's don't have the same shape, the new array with be the intersection of the two shapes.

izipWith3 :: (Shape f, Storable a, Storable b, Storable c, Storable d) => (f Int -> a -> b -> c -> d) -> SArray f a -> SArray f b -> SArray f c -> SArray f d Source #

Zip two arrays using the given function with access to the index. If the array's don't have the same shape, the new array with be the intersection of the two shapes.

Slices

Matrix

ixRow :: Storable a => Int -> IndexedTraversal' Int (SArray V2 a) (Vector a) Source #

Affine traversal over a single row in a matrix.

>>> traverseOf_ rows print $ m & ixRow 1 . each +~ 2
[1,2,3]
[6,7,8]

The row vector should remain the same size to satisfy traversal laws but give reasonable behaviour if the size differs:

>>> traverseOf_ rows print $ m & ixRow 1 .~ V.fromList [0,1]
[1,2,3]
[0,1,6]
>>> traverseOf_ rows print $ m & ixRow 1 .~ V.fromList [0..100]
[1,2,3]
[0,1,2]

rows :: (Storable a, Storable b) => IndexedTraversal Int (SArray V2 a) (SArray V2 b) (Vector a) (Vector b) Source #

Indexed traversal over the rows of a matrix. Each row is an efficient slice of the original vector.

>>> traverseOf_ rows print m
[1,2,3]
[4,5,6]

ixColumn :: Storable a => Int -> IndexedTraversal' Int (SArray V2 a) (Vector a) Source #

Affine traversal over a single column in a matrix.

>>> traverseOf_ rows print $ m & ixColumn 2 . each *~ 10
[1,2,30]
[4,5,60]

columns :: (Storable a, Storable b) => IndexedTraversal Int (SArray V2 a) (SArray V2 b) (Vector a) (Vector b) Source #

Indexed traversal over the columns of a matrix. Unlike rows, each column is a new separate vector.

>>> traverseOf_ columns print m
[1,4]
[2,5]
[3,6]
>>> traverseOf_ rows print $ m & columns . indices odd . each .~ 0
[1,0,3]
[4,0,6]

The vectors should be the same size to be a valid traversal. If the vectors are different sizes, the number of rows in the new array will be the length of the smallest vector.

3D

ixPlane :: Storable a => ALens' (V3 Int) (V2 Int) -> Int -> IndexedTraversal' Int (SArray V3 a) (SArray V2 a) Source #

Traversal over a single plane of a 3D array given a lens onto that plane (like _xy, _yz, _zx).

planes :: (Storable a, Storable b) => ALens' (V3 Int) (V2 Int) -> IndexedTraversal Int (SArray V3 a) (SArray V3 b) (SArray V2 a) (SArray V2 b) Source #

Traversal over all planes of 3D array given a lens onto that plane (like _xy, _yz, _zx).

flattenPlane :: (Storable a, Storable b) => ALens' (V3 Int) (V2 Int) -> (Vector a -> b) -> SArray V3 a -> SArray V2 b Source #

Flatten a plane by reducing a vector in the third dimension to a single value.

Ordinals

unsafeOrdinals :: (Storable a, Shape f) => [f Int] -> IndexedTraversal' (f Int) (SArray f a) a Source #

This Traversal should not have any duplicates in the list of indices.

Mutable

type SMArray = MArray MVector Source #

Storable mutable array.

thaw :: (PrimMonad m, Storable a) => SArray f a -> m (SMArray f (PrimState m) a) Source #

O(n) Yield an immutable copy of the mutable array.

freeze :: (PrimMonad m, Storable a) => SMArray f (PrimState m) a -> m (SArray f a) Source #

O(n) Yield a mutable copy of the immutable vector.

unsafeThaw :: (PrimMonad m, Storable a) => SArray f a -> m (SMArray f (PrimState m) a) Source #

O(1) Unsafely convert an immutable array to a mutable one without copying. The immutable array may not be used after this operation.

unsafeFreeze :: (PrimMonad m, Storable a) => SMArray f (PrimState m) a -> m (SArray f a) Source #

O(1) Unsafe convert a mutable array to an immutable one without copying. The mutable array may not be used after this operation.

Delayed

data Delayed f a Source #

A delayed representation of an array. This useful for mapping over an array in parallel.

Instances

Instances details
Shape f => HasLayout f (Delayed f a) Source #

The size of the layout must remain the same or an error is thrown.

Instance details

Defined in Data.Dense.Base

Methods

layout :: Lens' (Delayed f a) (Layout f) Source #

Functor (Delayed f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

fmap :: (a -> b) -> Delayed f a -> Delayed f b #

(<$) :: a -> Delayed f b -> Delayed f a #

Shape f => Foldable (Delayed f) Source #

foldMap in parallel.

Instance details

Defined in Data.Dense.Base

Methods

fold :: Monoid m => Delayed f m -> m #

foldMap :: Monoid m => (a -> m) -> Delayed f a -> m #

foldMap' :: Monoid m => (a -> m) -> Delayed f a -> m #

foldr :: (a -> b -> b) -> b -> Delayed f a -> b #

foldr' :: (a -> b -> b) -> b -> Delayed f a -> b #

foldl :: (b -> a -> b) -> b -> Delayed f a -> b #

foldl' :: (b -> a -> b) -> b -> Delayed f a -> b #

foldr1 :: (a -> a -> a) -> Delayed f a -> a #

foldl1 :: (a -> a -> a) -> Delayed f a -> a #

toList :: Delayed f a -> [a] #

null :: Delayed f a -> Bool #

length :: Delayed f a -> Int #

elem :: Eq a => a -> Delayed f a -> Bool #

maximum :: Ord a => Delayed f a -> a #

minimum :: Ord a => Delayed f a -> a #

sum :: Num a => Delayed f a -> a #

product :: Num a => Delayed f a -> a #

Shape f => Traversable (Delayed f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Delayed f a -> f0 (Delayed f b) #

sequenceA :: Applicative f0 => Delayed f (f0 a) -> f0 (Delayed f a) #

mapM :: Monad m => (a -> m b) -> Delayed f a -> m (Delayed f b) #

sequence :: Monad m => Delayed f (m a) -> m (Delayed f a) #

Shape f => Apply (Delayed f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

(<.>) :: Delayed f (a -> b) -> Delayed f a -> Delayed f b #

(.>) :: Delayed f a -> Delayed f b -> Delayed f b #

(<.) :: Delayed f a -> Delayed f b -> Delayed f a #

liftF2 :: (a -> b -> c) -> Delayed f a -> Delayed f b -> Delayed f c #

Shape f => Metric (Delayed f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

dot :: Num a => Delayed f a -> Delayed f a -> a #

quadrance :: Num a => Delayed f a -> a #

qd :: Num a => Delayed f a -> Delayed f a -> a #

distance :: Floating a => Delayed f a -> Delayed f a -> a #

norm :: Floating a => Delayed f a -> a #

signorm :: Floating a => Delayed f a -> Delayed f a #

Shape f => Additive (Delayed f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

zero :: Num a => Delayed f a #

(^+^) :: Num a => Delayed f a -> Delayed f a -> Delayed f a #

(^-^) :: Num a => Delayed f a -> Delayed f a -> Delayed f a #

lerp :: Num a => a -> Delayed f a -> Delayed f a -> Delayed f a #

liftU2 :: (a -> a -> a) -> Delayed f a -> Delayed f a -> Delayed f a #

liftI2 :: (a -> b -> c) -> Delayed f a -> Delayed f b -> Delayed f c #

FunctorWithIndex (f Int) (Delayed f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

imap :: (f Int -> a -> b) -> Delayed f a -> Delayed f b #

imapped :: IndexedSetter (f Int) (Delayed f a) (Delayed f b) a b #

Shape f => FoldableWithIndex (f Int) (Delayed f) Source #

ifoldMap in parallel.

Instance details

Defined in Data.Dense.Base

Methods

ifoldMap :: Monoid m => (f Int -> a -> m) -> Delayed f a -> m #

ifolded :: IndexedFold (f Int) (Delayed f a) a #

ifoldr :: (f Int -> a -> b -> b) -> b -> Delayed f a -> b #

ifoldl :: (f Int -> b -> a -> b) -> b -> Delayed f a -> b #

ifoldr' :: (f Int -> a -> b -> b) -> b -> Delayed f a -> b #

ifoldl' :: (f Int -> b -> a -> b) -> b -> Delayed f a -> b #

Shape f => TraversableWithIndex (f Int) (Delayed f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

itraverse :: Applicative f0 => (f Int -> a -> f0 b) -> Delayed f a -> f0 (Delayed f b) #

itraversed :: IndexedTraversal (f Int) (Delayed f a) (Delayed f b) a b #

(Shape f, Show1 f, Show a) => Show (Delayed f a) Source # 
Instance details

Defined in Data.Dense.Base

Methods

showsPrec :: Int -> Delayed f a -> ShowS #

show :: Delayed f a -> String #

showList :: [Delayed f a] -> ShowS #

Shape f => Ixed (Delayed f a) Source # 
Instance details

Defined in Data.Dense.Base

Methods

ix :: Index (Delayed f a) -> Traversal' (Delayed f a) (IxValue (Delayed f a)) #

Shape f => AsEmpty (Delayed f a) Source # 
Instance details

Defined in Data.Dense.Base

Methods

_Empty :: Prism' (Delayed f a) () #

Shape f => Each (Delayed f a) (Delayed f b) a b Source # 
Instance details

Defined in Data.Dense.Base

Methods

each :: Traversal (Delayed f a) (Delayed f b) a b #

type Index (Delayed f a) Source # 
Instance details

Defined in Data.Dense.Base

type Index (Delayed f a) = f Int
type IxValue (Delayed f a) Source # 
Instance details

Defined in Data.Dense.Base

type IxValue (Delayed f a) = a

Generating delayed

delayed :: (Storable a, Storable b, Shape f, Shape k) => Iso (SArray f a) (SArray k b) (Delayed f a) (Delayed k b) Source #

Isomorphism between an array and its delayed representation. Conversion to the array is done in parallel.

seqDelayed :: (Storable a, Storable b, Shape f, Shape k) => Iso (SArray f a) (SArray k b) (Delayed f a) (Delayed k b) Source #

Isomorphism between an array and its delayed representation. Conversion to the array is done in sequence.

delay :: (Storable a, Shape f) => SArray f a -> Delayed f a Source #

Turn a material array into a delayed one with the same shape.

manifest :: (Storable a, Shape f) => Delayed f a -> SArray f a Source #

Parallel manifestation of a delayed array into a material one.

seqManifest :: (Storable a, Shape f) => Delayed f a -> SArray f a Source #

Sequential manifestation of a delayed array.

genDelayed :: Layout f -> (f Int -> a) -> Delayed f a Source #

Generate a Delayed array using the given Layout and construction function.

indexDelayed :: Shape f => Delayed f a -> f Int -> a Source #

Index a delayed array, returning a IndexOutOfBounds exception if the index is out of range.

affirm :: (Shape f, Storable a) => Delayed f a -> Delayed f a Source #

manifest an array to a SArray and delay again.

seqAffirm :: (Shape f, Storable a) => Delayed f a -> Delayed f a Source #

seqManifest an array to a SArray and delay again.

Focused

data Focused f a Source #

A delayed representation of an array with a focus on a single element. This element is the target of extract.

Instances

Instances details
Shape f => HasLayout f (Focused f a) Source #

The size of the layout must remain the same or an error is thrown.

Instance details

Defined in Data.Dense.Base

Methods

layout :: Lens' (Focused f a) (Layout f) Source #

Functor (Focused f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

fmap :: (a -> b) -> Focused f a -> Focused f b #

(<$) :: a -> Focused f b -> Focused f a #

Shape f => Foldable (Focused f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

fold :: Monoid m => Focused f m -> m #

foldMap :: Monoid m => (a -> m) -> Focused f a -> m #

foldMap' :: Monoid m => (a -> m) -> Focused f a -> m #

foldr :: (a -> b -> b) -> b -> Focused f a -> b #

foldr' :: (a -> b -> b) -> b -> Focused f a -> b #

foldl :: (b -> a -> b) -> b -> Focused f a -> b #

foldl' :: (b -> a -> b) -> b -> Focused f a -> b #

foldr1 :: (a -> a -> a) -> Focused f a -> a #

foldl1 :: (a -> a -> a) -> Focused f a -> a #

toList :: Focused f a -> [a] #

null :: Focused f a -> Bool #

length :: Focused f a -> Int #

elem :: Eq a => a -> Focused f a -> Bool #

maximum :: Ord a => Focused f a -> a #

minimum :: Ord a => Focused f a -> a #

sum :: Num a => Focused f a -> a #

product :: Num a => Focused f a -> a #

Shape f => Traversable (Focused f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

traverse :: Applicative f0 => (a -> f0 b) -> Focused f a -> f0 (Focused f b) #

sequenceA :: Applicative f0 => Focused f (f0 a) -> f0 (Focused f a) #

mapM :: Monad m => (a -> m b) -> Focused f a -> m (Focused f b) #

sequence :: Monad m => Focused f (m a) -> m (Focused f a) #

Shape f => Comonad (Focused f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

extract :: Focused f a -> a #

duplicate :: Focused f a -> Focused f (Focused f a) #

extend :: (Focused f a -> b) -> Focused f a -> Focused f b #

Shape f => Extend (Focused f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

duplicated :: Focused f a -> Focused f (Focused f a) #

extended :: (Focused f a -> b) -> Focused f a -> Focused f b #

Shape f => ComonadStore (f Int) (Focused f) Source # 
Instance details

Defined in Data.Dense.Base

Methods

pos :: Focused f a -> f Int #

peek :: f Int -> Focused f a -> a #

peeks :: (f Int -> f Int) -> Focused f a -> a #

seek :: f Int -> Focused f a -> Focused f a #

seeks :: (f Int -> f Int) -> Focused f a -> Focused f a #

experiment :: Functor f0 => (f Int -> f0 (f Int)) -> Focused f a -> f0 a #

Shape f => FunctorWithIndex (f Int) (Focused f) Source #

Index relative to focus.

Instance details

Defined in Data.Dense.Base

Methods

imap :: (f Int -> a -> b) -> Focused f a -> Focused f b #

imapped :: IndexedSetter (f Int) (Focused f a) (Focused f b) a b #

Shape f => FoldableWithIndex (f Int) (Focused f) Source #

Index relative to focus.

Instance details

Defined in Data.Dense.Base

Methods

ifoldMap :: Monoid m => (f Int -> a -> m) -> Focused f a -> m #

ifolded :: IndexedFold (f Int) (Focused f a) a #

ifoldr :: (f Int -> a -> b -> b) -> b -> Focused f a -> b #

ifoldl :: (f Int -> b -> a -> b) -> b -> Focused f a -> b #

ifoldr' :: (f Int -> a -> b -> b) -> b -> Focused f a -> b #

ifoldl' :: (f Int -> b -> a -> b) -> b -> Focused f a -> b #

Shape f => TraversableWithIndex (f Int) (Focused f) Source #

Index relative to focus.

Instance details

Defined in Data.Dense.Base

Methods

itraverse :: Applicative f0 => (f Int -> a -> f0 b) -> Focused f a -> f0 (Focused f b) #

itraversed :: IndexedTraversal (f Int) (Focused f a) (Focused f b) a b #

(Shape f, Show1 f, Show a) => Show (Focused f a) Source # 
Instance details

Defined in Data.Dense.Base

Methods

showsPrec :: Int -> Focused f a -> ShowS #

show :: Focused f a -> String #

showList :: [Focused f a] -> ShowS #

Shape f => Ixed (Focused f a) Source #

Index relative to focus.

Instance details

Defined in Data.Dense.Base

Methods

ix :: Index (Focused f a) -> Traversal' (Focused f a) (IxValue (Focused f a)) #

type Index (Focused f a) Source # 
Instance details

Defined in Data.Dense.Base

type Index (Focused f a) = f Int
type IxValue (Focused f a) Source # 
Instance details

Defined in Data.Dense.Base

type IxValue (Focused f a) = a

Generating focused

focusOn :: f Int -> Delayed f a -> Focused f a Source #

Focus on a particular element of a delayed array.

unfocus :: Focused f a -> Delayed f a Source #

Discard the focus to retrieve the delayed array.

unfocused :: IndexedLens (f Int) (Focused f a) (Focused f b) (Delayed f a) (Delayed f b) Source #

Indexed lens onto the delayed array, indexed at the focus.

extendFocus :: Shape f => (Focused f a -> b) -> Delayed f a -> Delayed f b Source #

Modify a Delayed array by extracting a value from a Focused each point.

Focus location

locale :: ComonadStore s w => Lens' (w a) s Source #

Lens onto the position of a ComonadStore.

locale :: Lens' (Focused l a) (l Int)

shiftFocus :: Applicative f => f Int -> Focused f a -> Focused f a Source #

Focus on a neighbouring element, relative to the current focus.

Pointers

unsafeWithPtr :: Storable a => SArray f a -> (Ptr a -> IO b) -> IO b Source #

Pass a pointer to the array's data to the IO action. Modifying data through the Ptr is unsafe.

unsafeToForeignPtr :: Storable a => SArray f a -> ForeignPtr a Source #

Yield the underlying ForeignPtr. Modifying the data through the ForeignPtr is unsafe.

unsafeFromForeignPtr :: (Shape f, Storable a) => Layout f -> ForeignPtr a -> SArray f a Source #

O(1) Create an array from a layout and ForeignPtr. It is assumed the pointer points directly to the data (no offset). Modifying data through the ForeignPtr afterwards is unsafe.