massiv-1.0.0.0: Massiv (Массив) is an Array Library.
Copyright(c) Alexey Kuleshevich 2018-2021
LicenseBSD3
MaintainerAlexey Kuleshevich <lehins@yandex.ru>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Massiv.Array.Manifest.Vector

Description

 
Synopsis

Documentation

fromVectorM Source #

Arguments

:: (MonadThrow m, Typeable v, Vector v a, Manifest r a, Load (ARepr v) ix a, Load r ix a) 
=> Comp 
-> Sz ix

Resulting size of the array

-> v a

Source Vector

-> m (Array r ix a) 

In case when resulting array representation matches the one of vector's it will do a O(1) - conversion using castFromVector, otherwise Vector elements will be copied into a new array. Will throw an error if length of resulting array doesn't match the source vector length.

Since: 0.3.0

fromVector' Source #

Arguments

:: (HasCallStack, Typeable v, Vector v a, Load (ARepr v) ix a, Load r ix a, Manifest r a) 
=> Comp 
-> Sz ix

Resulting size of the array

-> v a

Source Vector

-> Array r ix a 

Just like fromVectorM, but will throw an exception on a mismatched size.

Since: 0.3.0

castFromVector Source #

Arguments

:: forall v r ix e. (Vector v e, Typeable v, Index ix, ARepr v ~ r) 
=> Comp 
-> Sz ix

Size of the result Array

-> v e

Source Vector

-> Maybe (Array r ix e) 

O(1) - conversion from vector to an array with a corresponding representation. Will return Nothing if there is a size mismatch or if some non-standard vector type is supplied. Is suppplied is the boxed Vector then it's all elements will be evaluated toWHNF, therefore complexity will be O(n)

toVector :: forall r ix e v. (Manifest r e, Load r ix e, Manifest (ARepr v) e, Vector v e, VRepr (ARepr v) ~ v) => Array r ix e -> v e Source #

Convert an array into a vector. Will perform a cast if resulting vector is of compatible representation, otherwise memory copy will occur.

Examples

Expand

In this example a Storable Array is created and then casted into a Storable Vector in costant time:

>>> import Data.Massiv.Array as A
>>> import Data.Massiv.Array.Manifest.Vector (toVector)
>>> import qualified Data.Vector.Storable as VS
>>> toVector (makeArrayR S Par (Sz2 5 6) (\(i :. j) -> i + j)) :: VS.Vector Int
[0,1,2,3,4,5,1,2,3,4,5,6,2,3,4,5,6,7,3,4,5,6,7,8,4,5,6,7,8,9]

While in this example Storable Array will first be converted into Unboxed representation in Parallel and only after that will be coverted into Unboxed Vector in constant time.

>>> import qualified Data.Vector.Unboxed as VU
>>> toVector (makeArrayR S Par (Sz2 5 6) (\(i :. j) -> i + j)) :: VU.Vector Int
[0,1,2,3,4,5,1,2,3,4,5,6,2,3,4,5,6,7,3,4,5,6,7,8,4,5,6,7,8,9]

castToVector :: forall v r ix e. (Manifest r e, Index ix, VRepr r ~ v) => Array r ix e -> Maybe (v e) Source #

O(1) - conversion from Mutable array to a corresponding vector. Will return Nothing only if source array representation was not one of B, N, P, S or U.

type family ARepr (v :: Type -> Type) :: Type where ... Source #

Match vector type to array representation

Equations

ARepr Vector = U 
ARepr Vector = S 
ARepr Vector = P 
ARepr Vector = BL 

type family VRepr r :: Type -> Type where ... Source #

Match array representation to a vector type