numerical-0.0.0.0: core package for Numerical Haskell project

Safe HaskellNone
LanguageHaskell2010

Numerical.Array.Layout.Builder

Documentation

data BatchInit v Source #

Constructors

BatchInit 

Fields

Instances
Functor BatchInit Source # 
Instance details

Defined in Numerical.Array.Layout.Builder

Methods

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

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

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

Defined in Numerical.Array.Layout.Builder

materializeBatchMV :: (PrimMonad m, MVector mv a) => BatchInit a -> m (mv (PrimState m) a) Source #

newtype AnyMV mv e Source #

Constructors

AMV (forall s. mv s e) 

newtype IntFun a Source #

Constructors

IntFun (forall m. PrimMonad m => Int -> m a) 
Instances
Functor IntFun Source # 
Instance details

Defined in Numerical.Array.Layout.Builder

Methods

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

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

fromVectorBI :: Vector v e => v e -> BatchInit e Source #

class Layout form (rank :: Nat) => LayoutBuilder form (rank :: Nat) | form -> rank where Source #

Methods

buildFormatM :: (store ~ FormatStorageRep form, Buffer store Int, Buffer store a, PrimMonad m) => Index rank -> proxy form -> a -> Maybe (BatchInit (Index rank, a)) -> m (form, BufferMut store (PrimState m) a) Source #

Instances
(Foldable (Shape r), Traversable (Shape r), Applicative (Shape r)) => LayoutBuilder (Format Column Contiguous r rep) r Source # 
Instance details

Defined in Numerical.Array.Layout.Builder

Methods

buildFormatM :: (store ~ FormatStorageRep (Format Column Contiguous r rep), Buffer store Int, Buffer store a, PrimMonad m) => Index r -> proxy (Format Column Contiguous r rep) -> a -> Maybe (BatchInit (Index r, a)) -> m (Format Column Contiguous r rep, BufferMut store (PrimState m) a) Source #

(Foldable (Shape r), Traversable (Shape r), Applicative (Shape r)) => LayoutBuilder (Format Row Contiguous r rep) r Source # 
Instance details

Defined in Numerical.Array.Layout.Builder

Methods

buildFormatM :: (store ~ FormatStorageRep (Format Row Contiguous r rep), Buffer store Int, Buffer store a, PrimMonad m) => Index r -> proxy (Format Row Contiguous r rep) -> a -> Maybe (BatchInit (Index r, a)) -> m (Format Row Contiguous r rep, BufferMut store (PrimState m) a) Source #

Buffer rep Int => LayoutBuilder (Format DirectSparse Contiguous (S Z) rep) (S Z) Source # 
Instance details

Defined in Numerical.Array.Layout.Builder

Methods

buildFormatM :: (store ~ FormatStorageRep (Format DirectSparse Contiguous (S Z) rep), Buffer store Int, Buffer store a, PrimMonad m) => Index (S Z) -> proxy (Format DirectSparse Contiguous (S Z) rep) -> a -> Maybe (BatchInit (Index (S Z), a)) -> m (Format DirectSparse Contiguous (S Z) rep, BufferMut store (PrimState m) a) Source #

Buffer rep Int => LayoutBuilder (Format CompressedSparseRow Contiguous (S (S Z)) rep) (S (S Z)) Source # 
Instance details

Defined in Numerical.Array.Layout.Builder

Methods

buildFormatM :: (store ~ FormatStorageRep (Format CompressedSparseRow Contiguous (S (S Z)) rep), Buffer store Int, Buffer store a, PrimMonad m) => Index (S (S Z)) -> proxy (Format CompressedSparseRow Contiguous (S (S Z)) rep) -> a -> Maybe (BatchInit (Index (S (S Z)), a)) -> m (Format CompressedSparseRow Contiguous (S (S Z)) rep, BufferMut store (PrimState m) a) Source #

LayoutBuilder (Format Direct Contiguous (S Z) rep) (S Z) Source # 
Instance details

Defined in Numerical.Array.Layout.Builder

Methods

buildFormatM :: (store ~ FormatStorageRep (Format Direct Contiguous (S Z) rep), Buffer store Int, Buffer store a, PrimMonad m) => Index (S Z) -> proxy (Format Direct Contiguous (S Z) rep) -> a -> Maybe (BatchInit (Index (S Z), a)) -> m (Format Direct Contiguous (S Z) rep, BufferMut store (PrimState m) a) Source #

buildFormatPure :: forall store form rank proxy m a. (LayoutBuilder form (rank :: Nat), store ~ FormatStorageRep form, Buffer store Int, Buffer store a, Monad m) => Index rank -> proxy form -> a -> Maybe (BatchInit (Index rank, a)) -> m (form, BufferPure store a) Source #

isStrictlyMonotonicV :: Vector v e => (e -> e -> Ordering) -> v e -> Maybe Int Source #

computeRunLengths :: (Vector v e, Eq e) => v e -> [(e, Int)] Source #

computeStarts :: (Enum a, Ord a, Num b) => [(a, b)] -> a -> a -> [(a, b)] Source #