numerical-0.0.0.0: core package for Numerical Haskell project

Safe HaskellNone
LanguageHaskell2010

Numerical.Array.Layout.Dense

Synopsis

Documentation

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

DenseLayout only has instances for Dense array formats. this class will need some sprucing up for the beta, but its ok for now. NB that DenseLayout is really strictly meant to be used for optimization purposes, and not meant as a default api

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

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Column Strided rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Column InnerContiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

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

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Row Strided rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Row InnerContiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

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

Defined in Numerical.Array.Layout.Dense

DenseLayout (Format Direct Strided (S Z) rep) (S Z) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

data Locality Source #

Instances
Eq Locality Source # 
Instance details

Defined in Numerical.Array.Locality

Data Locality Source # 
Instance details

Defined in Numerical.Array.Locality

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Locality -> c Locality #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Locality #

toConstr :: Locality -> Constr #

dataTypeOf :: Locality -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Locality) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Locality) #

gmapT :: (forall b. Data b => b -> b) -> Locality -> Locality #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Locality -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Locality -> r #

gmapQ :: (forall d. Data d => d -> u) -> Locality -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Locality -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Locality -> m Locality #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Locality -> m Locality #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Locality -> m Locality #

Read Locality Source # 
Instance details

Defined in Numerical.Array.Locality

Show Locality Source # 
Instance details

Defined in Numerical.Array.Locality

data family Format lay (contiguity :: Locality) (rank :: Nat) rep Source #

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

Defined in Numerical.Array.Layout.Dense

(Data (Shape n Int), Typeable n, Typeable rep) => Data (Format Column Strided n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Format Column Strided n rep -> c (Format Column Strided n rep) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Format Column Strided n rep) #

toConstr :: Format Column Strided n rep -> Constr #

dataTypeOf :: Format Column Strided n rep -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Format Column Strided n rep)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Format Column Strided n rep)) #

gmapT :: (forall b. Data b => b -> b) -> Format Column Strided n rep -> Format Column Strided n rep #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format Column Strided n rep -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format Column Strided n rep -> r #

gmapQ :: (forall d. Data d => d -> u) -> Format Column Strided n rep -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Format Column Strided n rep -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Format Column Strided n rep -> m (Format Column Strided n rep) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Column Strided n rep -> m (Format Column Strided n rep) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Column Strided n rep -> m (Format Column Strided n rep) #

(Data (Shape n Int), Typeable n, Typeable rep) => Data (Format Column InnerContiguous n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Format Column InnerContiguous n rep -> c (Format Column InnerContiguous n rep) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Format Column InnerContiguous n rep) #

toConstr :: Format Column InnerContiguous n rep -> Constr #

dataTypeOf :: Format Column InnerContiguous n rep -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Format Column InnerContiguous n rep)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Format Column InnerContiguous n rep)) #

gmapT :: (forall b. Data b => b -> b) -> Format Column InnerContiguous n rep -> Format Column InnerContiguous n rep #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format Column InnerContiguous n rep -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format Column InnerContiguous n rep -> r #

gmapQ :: (forall d. Data d => d -> u) -> Format Column InnerContiguous n rep -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Format Column InnerContiguous n rep -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Format Column InnerContiguous n rep -> m (Format Column InnerContiguous n rep) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Column InnerContiguous n rep -> m (Format Column InnerContiguous n rep) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Column InnerContiguous n rep -> m (Format Column InnerContiguous n rep) #

Data rep => Data (Format Direct Contiguous (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Format Direct Contiguous (S Z) rep -> c (Format Direct Contiguous (S Z) rep) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Format Direct Contiguous (S Z) rep) #

toConstr :: Format Direct Contiguous (S Z) rep -> Constr #

dataTypeOf :: Format Direct Contiguous (S Z) rep -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Format Direct Contiguous (S Z) rep)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Format Direct Contiguous (S Z) rep)) #

gmapT :: (forall b. Data b => b -> b) -> Format Direct Contiguous (S Z) rep -> Format Direct Contiguous (S Z) rep #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format Direct Contiguous (S Z) rep -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format Direct Contiguous (S Z) rep -> r #

gmapQ :: (forall d. Data d => d -> u) -> Format Direct Contiguous (S Z) rep -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Format Direct Contiguous (S Z) rep -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Format Direct Contiguous (S Z) rep -> m (Format Direct Contiguous (S Z) rep) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Direct Contiguous (S Z) rep -> m (Format Direct Contiguous (S Z) rep) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Direct Contiguous (S Z) rep -> m (Format Direct Contiguous (S Z) rep) #

Show (BufferPure rep Int) => Show (Format DirectSparse Contiguous (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

Show (ContiguousCompressedSparseMatrix rep) => Show (Format CompressedSparseColumn Contiguous (S (S Z)) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

Show (InnerContiguousCompressedSparseMatrix rep) => Show (Format CompressedSparseColumn InnerContiguous (S (S Z)) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

Show (ContiguousCompressedSparseMatrix rep) => Show (Format CompressedSparseRow Contiguous (S (S Z)) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

Show (InnerContiguousCompressedSparseMatrix rep) => Show (Format CompressedSparseRow InnerContiguous (S (S Z)) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

Show (Shape n Int) => Show (Format Column Strided n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Show (Shape n Int) => Show (Format Column InnerContiguous n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

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

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Column Contiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Column Strided rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Column InnerContiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

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

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Row Strided rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Row InnerContiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Column Contiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Column Contiguous rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> logicalForm Source #

transposedLayout :: (Format Column Contiguous rank rep ~ Transposed transform, transform ~ Transposed (Format Column Contiguous rank rep)) => Format Column Contiguous rank rep -> transform Source #

basicCompareIndex :: p (Format Column Contiguous rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> address -> Int -> Maybe address Source #

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Column Strided rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Column Strided rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Column Strided rank rep) => Format Column Strided rank rep -> logicalForm Source #

transposedLayout :: (Format Column Strided rank rep ~ Transposed transform, transform ~ Transposed (Format Column Strided rank rep)) => Format Column Strided rank rep -> transform Source #

basicCompareIndex :: p (Format Column Strided rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> address -> Int -> Maybe address Source #

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Column InnerContiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Column InnerContiguous rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> logicalForm Source #

transposedLayout :: (Format Column InnerContiguous rank rep ~ Transposed transform, transform ~ Transposed (Format Column InnerContiguous rank rep)) => Format Column InnerContiguous rank rep -> transform Source #

basicCompareIndex :: p (Format Column InnerContiguous rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> address -> Int -> Maybe address Source #

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Row Contiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Row Contiguous rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> logicalForm Source #

transposedLayout :: (Format Row Contiguous rank rep ~ Transposed transform, transform ~ Transposed (Format Row Contiguous rank rep)) => Format Row Contiguous rank rep -> transform Source #

basicCompareIndex :: p (Format Row Contiguous rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> address -> Int -> Maybe address Source #

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Row Strided rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Row Strided rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Row Strided rank rep) => Format Row Strided rank rep -> logicalForm Source #

transposedLayout :: (Format Row Strided rank rep ~ Transposed transform, transform ~ Transposed (Format Row Strided rank rep)) => Format Row Strided rank rep -> transform Source #

basicCompareIndex :: p (Format Row Strided rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> address -> Int -> Maybe address Source #

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Row InnerContiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Row InnerContiguous rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> logicalForm Source #

transposedLayout :: (Format Row InnerContiguous rank rep ~ Transposed transform, transform ~ Transposed (Format Row InnerContiguous rank rep)) => Format Row InnerContiguous rank rep -> transform Source #

basicCompareIndex :: p (Format Row InnerContiguous rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> address -> Int -> Maybe address Source #

(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 #

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

Defined in Numerical.Array.Layout.Dense

DenseLayout (Format Direct Strided (S Z) rep) (S Z) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Vector (BufferPure rep) Int => Layout (Format DirectSparse Contiguous (S Z) rep) (S Z) Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

Methods

basicLogicalShape :: Format DirectSparse Contiguous (S Z) rep -> Shape (S Z) Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format DirectSparse Contiguous (S Z) rep) => Format DirectSparse Contiguous (S Z) rep -> logicalForm Source #

transposedLayout :: (Format DirectSparse Contiguous (S Z) rep ~ Transposed transform, transform ~ Transposed (Format DirectSparse Contiguous (S Z) rep)) => Format DirectSparse Contiguous (S Z) rep -> transform Source #

basicCompareIndex :: p (Format DirectSparse Contiguous (S Z) rep) -> Shape (S Z) Int -> Shape (S Z) Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format DirectSparse Contiguous (S Z) rep) => Format DirectSparse Contiguous (S Z) rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format DirectSparse Contiguous (S Z) rep) => Format DirectSparse Contiguous (S Z) rep -> Index (S Z) -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format DirectSparse Contiguous (S Z) rep) => Format DirectSparse Contiguous (S Z) rep -> address -> Index (S Z) Source #

basicNextAddress :: address ~ LayoutAddress (Format DirectSparse Contiguous (S Z) rep) => Format DirectSparse Contiguous (S Z) rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format DirectSparse Contiguous (S Z) rep) => Format DirectSparse Contiguous (S Z) rep -> Index (S Z) -> Maybe address -> Maybe (Index (S Z), address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format DirectSparse Contiguous (S Z) rep) => Format DirectSparse Contiguous (S Z) rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format DirectSparse Contiguous (S Z) rep) => Format DirectSparse Contiguous (S Z) rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format DirectSparse Contiguous (S Z) rep) => Format DirectSparse Contiguous (S Z) rep -> address -> Int -> Maybe address Source #

Vector (BufferPure rep) Int => Layout (Format CompressedSparseRow Contiguous (S (S Z)) rep) (S (S Z)) Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

Methods

basicLogicalShape :: Format CompressedSparseRow Contiguous (S (S Z)) rep -> Shape (S (S Z)) Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format CompressedSparseRow Contiguous (S (S Z)) rep) => Format CompressedSparseRow Contiguous (S (S Z)) rep -> logicalForm Source #

transposedLayout :: (Format CompressedSparseRow Contiguous (S (S Z)) rep ~ Transposed transform, transform ~ Transposed (Format CompressedSparseRow Contiguous (S (S Z)) rep)) => Format CompressedSparseRow Contiguous (S (S Z)) rep -> transform Source #

basicCompareIndex :: p (Format CompressedSparseRow Contiguous (S (S Z)) rep) -> Shape (S (S Z)) Int -> Shape (S (S Z)) Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format CompressedSparseRow Contiguous (S (S Z)) rep) => Format CompressedSparseRow Contiguous (S (S Z)) rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format CompressedSparseRow Contiguous (S (S Z)) rep) => Format CompressedSparseRow Contiguous (S (S Z)) rep -> Index (S (S Z)) -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format CompressedSparseRow Contiguous (S (S Z)) rep) => Format CompressedSparseRow Contiguous (S (S Z)) rep -> address -> Index (S (S Z)) Source #

basicNextAddress :: address ~ LayoutAddress (Format CompressedSparseRow Contiguous (S (S Z)) rep) => Format CompressedSparseRow Contiguous (S (S Z)) rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format CompressedSparseRow Contiguous (S (S Z)) rep) => Format CompressedSparseRow Contiguous (S (S Z)) rep -> Index (S (S Z)) -> Maybe address -> Maybe (Index (S (S Z)), address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format CompressedSparseRow Contiguous (S (S Z)) rep) => Format CompressedSparseRow Contiguous (S (S Z)) rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format CompressedSparseRow Contiguous (S (S Z)) rep) => Format CompressedSparseRow Contiguous (S (S Z)) rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format CompressedSparseRow Contiguous (S (S Z)) rep) => Format CompressedSparseRow Contiguous (S (S Z)) rep -> address -> Int -> Maybe address Source #

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

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Direct Contiguous (S Z) rep -> Shape (S Z) Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> logicalForm Source #

transposedLayout :: (Format Direct Contiguous (S Z) rep ~ Transposed transform, transform ~ Transposed (Format Direct Contiguous (S Z) rep)) => Format Direct Contiguous (S Z) rep -> transform Source #

basicCompareIndex :: p (Format Direct Contiguous (S Z) rep) -> Shape (S Z) Int -> Shape (S Z) Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> Index (S Z) -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> address -> Index (S Z) Source #

basicNextAddress :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> Index (S Z) -> Maybe address -> Maybe (Index (S Z), address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> address -> Int -> Maybe address Source #

Layout (Format Direct Strided (S Z) rep) (S Z) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Direct Strided (S Z) rep -> Shape (S Z) Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> logicalForm Source #

transposedLayout :: (Format Direct Strided (S Z) rep ~ Transposed transform, transform ~ Transposed (Format Direct Strided (S Z) rep)) => Format Direct Strided (S Z) rep -> transform Source #

basicCompareIndex :: p (Format Direct Strided (S Z) rep) -> Shape (S Z) Int -> Shape (S Z) Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> Index (S Z) -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> address -> Index (S Z) Source #

basicNextAddress :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> Index (S Z) -> Maybe address -> Maybe (Index (S Z), address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> address -> Int -> Maybe address 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 #

data Format Column Contiguous n rep Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

data Format Column Strided n rep Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

data Format Column InnerContiguous n rep Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

data Format Row Contiguous n rep Source #

Format Row Contiguous n is a rank n Array

Instance details

Defined in Numerical.Array.Layout.Dense

data Format Row Strided n rep Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

data Format Row InnerContiguous n rep Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

data Format DirectSparse Contiguous (S Z) rep Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

data Format CompressedSparseColumn Contiguous (S (S Z)) rep Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

data Format CompressedSparseColumn InnerContiguous (S (S Z)) rep Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

data Format CompressedSparseRow Contiguous (S (S Z)) rep Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

data Format CompressedSparseRow InnerContiguous (S (S Z)) rep Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

data Format Direct Contiguous (S Z) rep Source #

Format Direct Contiguous (S Z) is a 1dim array Layout with unit stride

Instance details

Defined in Numerical.Array.Layout.Dense

data Format Direct Strided (S Z) rep Source #

Format Direct Strided (S Z) is a 1dim array Layout with a regular stride >= 1

Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutLogicalFormat (Format Column cont n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutLogicalFormat (Format Row cont n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutLogicalFormat (Format Direct cont (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

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

Defined in Numerical.Array.Layout.Dense

type LayoutAddress (Format DirectSparse Contiguous (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

type LayoutAddress (Format CompressedSparseRow Contiguous (S (S Z)) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

type LayoutAddress (Format Column locality rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutAddress (Format Column locality rank rep) = Address
type LayoutAddress (Format Row locality rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutAddress (Format Row locality rank rep) = Address
type LayoutAddress (Format Direct Contiguous (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutAddress (Format Direct Strided (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type Transposed (Format DirectSparse Contiguous (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

type Transposed (Format CompressedSparseRow Contiguous (S (S Z)) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Sparse

type Transposed (Format Column Contiguous rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type Transposed (Format Column Strided rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type Transposed (Format Column Strided rank rep) = Format Row Strided rank rep
type Transposed (Format Column InnerContiguous rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type Transposed (Format Row Contiguous rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type Transposed (Format Row Strided rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type Transposed (Format Row Strided rank rep) = Format Column Strided rank rep
type Transposed (Format Row InnerContiguous rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

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

Defined in Numerical.Array.Layout.Dense

type Transposed (Format Direct Strided (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type FormatStorageRep (Format lay ctg rnk rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Base

type FormatStorageRep (Format lay ctg rnk rep) = rep

data Row Source #

Instances
(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Row Contiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Row Strided rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Row InnerContiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Row Contiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Row Contiguous rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> logicalForm Source #

transposedLayout :: (Format Row Contiguous rank rep ~ Transposed transform, transform ~ Transposed (Format Row Contiguous rank rep)) => Format Row Contiguous rank rep -> transform Source #

basicCompareIndex :: p (Format Row Contiguous rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Row Contiguous rank rep) => Format Row Contiguous rank rep -> address -> Int -> Maybe address Source #

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Row Strided rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Row Strided rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Row Strided rank rep) => Format Row Strided rank rep -> logicalForm Source #

transposedLayout :: (Format Row Strided rank rep ~ Transposed transform, transform ~ Transposed (Format Row Strided rank rep)) => Format Row Strided rank rep -> transform Source #

basicCompareIndex :: p (Format Row Strided rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Row Strided rank rep) => Format Row Strided rank rep -> address -> Int -> Maybe address Source #

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Row InnerContiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Row InnerContiguous rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> logicalForm Source #

transposedLayout :: (Format Row InnerContiguous rank rep ~ Transposed transform, transform ~ Transposed (Format Row InnerContiguous rank rep)) => Format Row InnerContiguous rank rep -> transform Source #

basicCompareIndex :: p (Format Row InnerContiguous rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Row InnerContiguous rank rep) => Format Row InnerContiguous rank rep -> address -> Int -> Maybe address 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 #

data Format Row Contiguous n rep Source #

Format Row Contiguous n is a rank n Array

Instance details

Defined in Numerical.Array.Layout.Dense

data Format Row Strided n rep Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

data Format Row InnerContiguous n rep Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutLogicalFormat (Format Row cont n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutAddress (Format Row locality rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutAddress (Format Row locality rank rep) = Address
type Transposed (Format Row Contiguous rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type Transposed (Format Row Strided rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type Transposed (Format Row Strided rank rep) = Format Column Strided rank rep
type Transposed (Format Row InnerContiguous rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

data Column Source #

Instances
(Data (Shape n Int), Typeable n, Typeable rep) => Data (Format Column Strided n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Format Column Strided n rep -> c (Format Column Strided n rep) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Format Column Strided n rep) #

toConstr :: Format Column Strided n rep -> Constr #

dataTypeOf :: Format Column Strided n rep -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Format Column Strided n rep)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Format Column Strided n rep)) #

gmapT :: (forall b. Data b => b -> b) -> Format Column Strided n rep -> Format Column Strided n rep #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format Column Strided n rep -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format Column Strided n rep -> r #

gmapQ :: (forall d. Data d => d -> u) -> Format Column Strided n rep -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Format Column Strided n rep -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Format Column Strided n rep -> m (Format Column Strided n rep) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Column Strided n rep -> m (Format Column Strided n rep) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Column Strided n rep -> m (Format Column Strided n rep) #

(Data (Shape n Int), Typeable n, Typeable rep) => Data (Format Column InnerContiguous n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Format Column InnerContiguous n rep -> c (Format Column InnerContiguous n rep) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Format Column InnerContiguous n rep) #

toConstr :: Format Column InnerContiguous n rep -> Constr #

dataTypeOf :: Format Column InnerContiguous n rep -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Format Column InnerContiguous n rep)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Format Column InnerContiguous n rep)) #

gmapT :: (forall b. Data b => b -> b) -> Format Column InnerContiguous n rep -> Format Column InnerContiguous n rep #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format Column InnerContiguous n rep -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format Column InnerContiguous n rep -> r #

gmapQ :: (forall d. Data d => d -> u) -> Format Column InnerContiguous n rep -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Format Column InnerContiguous n rep -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Format Column InnerContiguous n rep -> m (Format Column InnerContiguous n rep) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Column InnerContiguous n rep -> m (Format Column InnerContiguous n rep) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Column InnerContiguous n rep -> m (Format Column InnerContiguous n rep) #

Show (Shape n Int) => Show (Format Column Strided n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Show (Shape n Int) => Show (Format Column InnerContiguous n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Column Contiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Column Strided rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Foldable (Shape rank), Traversable (Shape rank)) => DenseLayout (Format Column InnerContiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Column Contiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Column Contiguous rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> logicalForm Source #

transposedLayout :: (Format Column Contiguous rank rep ~ Transposed transform, transform ~ Transposed (Format Column Contiguous rank rep)) => Format Column Contiguous rank rep -> transform Source #

basicCompareIndex :: p (Format Column Contiguous rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Column Contiguous rank rep) => Format Column Contiguous rank rep -> address -> Int -> Maybe address Source #

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Column Strided rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Column Strided rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Column Strided rank rep) => Format Column Strided rank rep -> logicalForm Source #

transposedLayout :: (Format Column Strided rank rep ~ Transposed transform, transform ~ Transposed (Format Column Strided rank rep)) => Format Column Strided rank rep -> transform Source #

basicCompareIndex :: p (Format Column Strided rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Column Strided rank rep) => Format Column Strided rank rep -> address -> Int -> Maybe address Source #

(Applicative (Shape rank), Traversable (Shape rank)) => Layout (Format Column InnerContiguous rank rep) rank Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Column InnerContiguous rank rep -> Shape rank Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> logicalForm Source #

transposedLayout :: (Format Column InnerContiguous rank rep ~ Transposed transform, transform ~ Transposed (Format Column InnerContiguous rank rep)) => Format Column InnerContiguous rank rep -> transform Source #

basicCompareIndex :: p (Format Column InnerContiguous rank rep) -> Shape rank Int -> Shape rank Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> Index rank -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> address -> Index rank Source #

basicNextAddress :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Column InnerContiguous rank rep) => Format Column InnerContiguous rank rep -> address -> Int -> Maybe address Source #

(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 #

data Format Column Contiguous n rep Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

data Format Column Strided n rep Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

data Format Column InnerContiguous n rep Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutLogicalFormat (Format Column cont n rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutAddress (Format Column locality rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutAddress (Format Column locality rank rep) = Address
type Transposed (Format Column Contiguous rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type Transposed (Format Column Strided rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

type Transposed (Format Column Strided rank rep) = Format Row Strided rank rep
type Transposed (Format Column InnerContiguous rank rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

data Direct Source #

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

Defined in Numerical.Array.Layout.Dense

Data rep => Data (Format Direct Contiguous (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Format Direct Contiguous (S Z) rep -> c (Format Direct Contiguous (S Z) rep) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Format Direct Contiguous (S Z) rep) #

toConstr :: Format Direct Contiguous (S Z) rep -> Constr #

dataTypeOf :: Format Direct Contiguous (S Z) rep -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Format Direct Contiguous (S Z) rep)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Format Direct Contiguous (S Z) rep)) #

gmapT :: (forall b. Data b => b -> b) -> Format Direct Contiguous (S Z) rep -> Format Direct Contiguous (S Z) rep #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Format Direct Contiguous (S Z) rep -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Format Direct Contiguous (S Z) rep -> r #

gmapQ :: (forall d. Data d => d -> u) -> Format Direct Contiguous (S Z) rep -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Format Direct Contiguous (S Z) rep -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Format Direct Contiguous (S Z) rep -> m (Format Direct Contiguous (S Z) rep) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Direct Contiguous (S Z) rep -> m (Format Direct Contiguous (S Z) rep) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Format Direct Contiguous (S Z) rep -> m (Format Direct Contiguous (S Z) rep) #

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

Defined in Numerical.Array.Layout.Dense

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

Defined in Numerical.Array.Layout.Dense

DenseLayout (Format Direct Strided (S Z) rep) (S Z) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

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

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Direct Contiguous (S Z) rep -> Shape (S Z) Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> logicalForm Source #

transposedLayout :: (Format Direct Contiguous (S Z) rep ~ Transposed transform, transform ~ Transposed (Format Direct Contiguous (S Z) rep)) => Format Direct Contiguous (S Z) rep -> transform Source #

basicCompareIndex :: p (Format Direct Contiguous (S Z) rep) -> Shape (S Z) Int -> Shape (S Z) Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> Index (S Z) -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> address -> Index (S Z) Source #

basicNextAddress :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> Index (S Z) -> Maybe address -> Maybe (Index (S Z), address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Direct Contiguous (S Z) rep) => Format Direct Contiguous (S Z) rep -> address -> Int -> Maybe address Source #

Layout (Format Direct Strided (S Z) rep) (S Z) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

Methods

basicLogicalShape :: Format Direct Strided (S Z) rep -> Shape (S Z) Int Source #

basicLogicalForm :: logicalForm ~ LayoutLogicalFormat (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> logicalForm Source #

transposedLayout :: (Format Direct Strided (S Z) rep ~ Transposed transform, transform ~ Transposed (Format Direct Strided (S Z) rep)) => Format Direct Strided (S Z) rep -> transform Source #

basicCompareIndex :: p (Format Direct Strided (S Z) rep) -> Shape (S Z) Int -> Shape (S Z) Int -> Ordering Source #

basicAddressRange :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> Maybe (Range address) Source #

basicToAddress :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> Index (S Z) -> Maybe address Source #

basicToIndex :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> address -> Index (S Z) Source #

basicNextAddress :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> address -> Maybe address Source #

basicNextIndex :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> Index (S Z) -> Maybe address -> Maybe (Index (S Z), address) Source #

basicAddressPopCount :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> Range address -> Int Source #

basicAddressAsInt :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> address -> Int Source #

basicAffineAddressShift :: address ~ LayoutAddress (Format Direct Strided (S Z) rep) => Format Direct Strided (S Z) rep -> address -> Int -> Maybe address 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 #

data Format Direct Contiguous (S Z) rep Source #

Format Direct Contiguous (S Z) is a 1dim array Layout with unit stride

Instance details

Defined in Numerical.Array.Layout.Dense

data Format Direct Strided (S Z) rep Source #

Format Direct Strided (S Z) is a 1dim array Layout with a regular stride >= 1

Instance details

Defined in Numerical.Array.Layout.Dense

type LayoutLogicalFormat (Format Direct cont (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

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

Defined in Numerical.Array.Layout.Dense

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

Defined in Numerical.Array.Layout.Dense

type LayoutAddress (Format Direct Strided (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense

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

Defined in Numerical.Array.Layout.Dense

type Transposed (Format Direct Strided (S Z) rep) Source # 
Instance details

Defined in Numerical.Array.Layout.Dense