| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Numerical.Array.Layout.Sparse
Synopsis
- class Layout form (rank :: Nat) | form -> rank where- basicLogicalShape :: form -> Shape rank Int
- basicLogicalForm :: logicalForm ~ LayoutLogicalFormat form => form -> logicalForm
- transposedLayout :: (form ~ Transposed transform, transform ~ Transposed form) => form -> transform
- basicCompareIndex :: p form -> Shape rank Int -> Shape rank Int -> Ordering
- basicAddressRange :: address ~ LayoutAddress form => form -> Maybe (Range address)
- basicToAddress :: address ~ LayoutAddress form => form -> Index rank -> Maybe address
- basicToIndex :: address ~ LayoutAddress form => form -> address -> Index rank
- basicNextAddress :: address ~ LayoutAddress form => form -> address -> Maybe address
- basicNextIndex :: address ~ LayoutAddress form => form -> Index rank -> Maybe address -> Maybe (Index rank, address)
- basicAddressPopCount :: address ~ LayoutAddress form => form -> Range address -> Int
- basicAddressAsInt :: address ~ LayoutAddress form => form -> address -> Int
- basicAffineAddressShift :: address ~ LayoutAddress form => form -> address -> Int -> Maybe address
 
- data DirectSparse
- type CSR = CompressedSparseRow
- type CSC = CompressedSparseColumn
- data CompressedSparseRow
- data CompressedSparseColumn
- data family Format lay (contiguity :: Locality) (rank :: Nat) rep
- data ContiguousCompressedSparseMatrix rep = FormatContiguousCompressedSparseInternal {}
- data InnerContiguousCompressedSparseMatrix rep = FormatInnerContiguousCompressedSparseInternal {- _outerDimInnerContiguousSparseFormat :: !Int
- _innerDimInnerContiguousSparseFormat :: !Int
- _innerDimIndexShiftInnerContiguousSparseFormat :: !Int
- _innerDimIndexInnerContiguousSparseFormat :: !(BufferPure rep Int)
- _outerDim2InnerDimStartInnerContiguousSparseFormat :: !(BufferPure rep Int)
- _outerDim2InnerDimEndInnerContiguousSparseFormat :: !(BufferPure rep Int)
 
- module Numerical.Array.Layout.Base
Documentation
class Layout form (rank :: Nat) | form -> rank where Source #
the Layout type class
Minimal complete definition
basicToAddress, basicToIndex, basicNextAddress, basicNextIndex, basicAddressRange, basicLogicalShape, basicCompareIndex, transposedLayout, basicAddressPopCount, basicLogicalForm, basicAffineAddressShift
Methods
basicLogicalShape :: form -> Shape rank Int Source #
basicLogicalShape gives the extent of the format
basicLogicalForm :: logicalForm ~ LayoutLogicalFormat form => form -> logicalForm Source #
basicLogicalForm converts a given format into its "contiguous" analogue
 this is useful for supporting various address translation manipulation tricks
 efficiently. Note that any valid  simple format should strive to ensure this is an O(1) operation.
 though certain composite Layout instances may provide a slower implementation.
transposedLayout :: (form ~ Transposed transform, transform ~ Transposed form) => form -> transform Source #
transposedLayout transposes the format data type
basicCompareIndex :: p form -> Shape rank Int -> Shape rank Int -> Ordering Source #
basicCompareIndex lets you compare where two (presumably inbounds)
 Index values are in a formats ordering. The logical Shape of the array
 is not needed
basicAddressRange :: address ~ LayoutAddress form => form -> Maybe (Range address) Source #
the (possibly empty) min and max of the valid addresses for a given format.
 minAddress = fmap _RangeMin . rangedFormatAddress
 and maxAddress = fmap _RangeMax . rangedFormatAddress
 FIXME : This also is a terrible name
basicToAddress :: address ~ LayoutAddress form => form -> Index rank -> Maybe address Source #
basicToAddress takes an Index, and tries to translate it to an address if its in bounds
basicToIndex :: address ~ LayoutAddress form => form -> address -> Index rank Source #
basicToIndex takes an address, and always successfully translates it to
 a valid index. Behavior of invalid addresses constructed by a library user
 is unspecified.
basicNextAddress :: address ~ LayoutAddress form => form -> address -> Maybe address Source #
basicNextAddress takes an address, and tries to compute the next valid
 address, or returns Nothing if there is no subsequent valid address.
basicNextIndex :: address ~ LayoutAddress form => form -> Index rank -> Maybe address -> Maybe (Index rank, address) Source #
basicNextIndex form ix mbeAddressix if it exists. It takes a Maybe address
basicAddressPopCount :: address ~ LayoutAddress form => form -> Range address -> Int Source #
basicAddressAsInt :: address ~ LayoutAddress form => form -> address -> Int Source #
This operation is REALLY unsafe This should ONLY be used on Formats that are directly paired with a Buffer or Mutable Buffer (ie a Vector) This operation being in this class is also kinda a hack but lets leave it here for now
basicAffineAddressShift :: address ~ LayoutAddress form => form -> address -> Int -> Maybe address Source #
The semantics of basicAffineAddressShift form addr stepbasicNextAddress step times.
 However, the step size can be negative, which means it can
Instances
data DirectSparse Source #
Instances
type CSR = CompressedSparseRow Source #
type CSC = CompressedSparseColumn Source #
data CompressedSparseRow Source #
Instances
data CompressedSparseColumn Source #
Instances
data family Format lay (contiguity :: Locality) (rank :: Nat) rep Source #
Instances
data ContiguousCompressedSparseMatrix rep Source #
Constructors
| FormatContiguousCompressedSparseInternal | |
| Fields | |
Instances
| Show (BufferPure rep Int) => Show (ContiguousCompressedSparseMatrix rep) Source # | |
| Defined in Numerical.Array.Layout.Sparse Methods showsPrec :: Int -> ContiguousCompressedSparseMatrix rep -> ShowS # show :: ContiguousCompressedSparseMatrix rep -> String # showList :: [ContiguousCompressedSparseMatrix rep] -> ShowS # | |
data InnerContiguousCompressedSparseMatrix rep Source #
Constructors
Instances
| Show (BufferPure rep Int) => Show (InnerContiguousCompressedSparseMatrix rep) Source # | |
| Defined in Numerical.Array.Layout.Sparse Methods showsPrec :: Int -> InnerContiguousCompressedSparseMatrix rep -> ShowS # show :: InnerContiguousCompressedSparseMatrix rep -> String # showList :: [InnerContiguousCompressedSparseMatrix rep] -> ShowS # | |
module Numerical.Array.Layout.Base