sdp-0.2: Simple Data Processing
Copyright(c) Andrey Mulik 2019
LicenseBSD-style
Maintainerwork.a.mulik@gmail.com
Portabilitynon-portable (GHC extensions)
Safe HaskellTrustworthy
LanguageHaskell2010

SDP.Index

Description

The Index class is a fork of Ix with a richer interface, more convenient function names and generalized indexes.

Synopsis

Shapes

module SDP.Shape

type family i :|: j where ... Source #

(:|:) is closed type family of shape differences.

Equations

i :|: E = i 
i :|: j = DimInit i :|: DimInit j 

type SubIndex = Sub Source #

SubIndex is service constraint that corresponds closed (internal) class Sub. SubIndex i j matches if Index type i is subspace of Index type j.

takeDim :: Sub i j => i -> j Source #

Take some dimensions.

>>> takeDim ([1, 2, 3, 4] :: I4 Int) :: I1 Int
[1]
>>> takeDim ([1, 2, 3, 4] :: I4 Int) :: E
E

dropDim :: Sub i j => i -> j -> i :|: j Source #

Drop some dimensions (second argument used as type variable).

>>> dropDim ([1, 2, 3, 4] :: I4 Int) ([] :: E)
[1, 2, 3, 4]
>>> dropDim ([1, 2, 3, 4] :: I4 Int) ([1, 2] :: I2 Int)
[3, 4]

joinDim :: Sub i j => j -> (i :|: j) -> i Source #

Join some dimensions.

>>> joinDim ([1, 2] :: I2 Int) [3] :: I3 Int
[1, 2, 3]
>>> joinDim ([1, 2] :: I2 Int) [3, 4] :: I4 Int
[1, 2, 3, 4]

splitDim :: SubIndex i j => i -> (i :|: j, j) Source #

splitDim returns pair of shape difference and subshape.

Indices

class (Ord i, Shape i, Shape (DimLast i), Shape (DimInit i), Shape (GIndex i)) => Index i where Source #

Index is service class based on base Ix and repa Shape.

Basic rules:

size bnds >= 0
size bnds == product (sizes bnds)
isEmpty bnds == (size bnds == 0)
isEmpty bnds == inRange bnds (safeElem bnds i)
isEmpty bnds => isOverflow  bnds i
isEmpty bnds => isUnderflow bnds i
inRange bnds i /= isEmpty     bnds
inRange bnds i /= isOverflow  bnds i
inRange bnds i /= isUnderflow bnds i
inRange bnds i == (safeElem bnds i == i)

Note:

  • E is (and should remain) the one and only one index of rank 0.
  • Index is a generalization of Enum, so all rank 1 indices must satisfy Enum laws.
  • The cardinality of the set of permissible values for indices mustn't exceed 1 (cardinality of a series of natural numbers), so Fractional types cannot be indices.

Minimal complete definition

Nothing

Methods

size :: (i, i) -> Int Source #

Returns the size of range.

default size :: Enum i => (i, i) -> Int Source #

sizes :: (i, i) -> [Int] Source #

Returns the sizes of range dimensionwise.

default sizes :: Index (GIndex i) => (i, i) -> [Int] Source #

safeElem :: (i, i) -> i -> i Source #

Returns the index belonging to the given range.

ordBounds :: (i, i) -> (i, i) Source #

Returns bounds of nonempty range (swaps bounds in each empty subshape).

defLimit :: i -> Integer Source #

Returns size of biggest range, that may be represented by this type.

default defLimit :: (Integral i, Bounded i) => i -> Integer Source #

defaultBounds :: Int -> (i, i) Source #

Returns default range by size.

unsafeIndex :: Int -> i Source #

Returns index by offset in default range.

default unsafeIndex :: Enum i => Int -> i Source #

isEmpty :: (i, i) -> Bool Source #

Checks if the bounds is empty.

inBounds :: (i, i) -> i -> InBounds Source #

Checks the index status in bounds.

isOverflow :: (i, i) -> i -> Bool Source #

Checks if the index is overflow.

isUnderflow :: (i, i) -> i -> Bool Source #

Checks if the index is underflow.

inRange :: (i, i) -> i -> Bool Source #

Checks if the index is in range.

prev :: (i, i) -> i -> i Source #

Returns previous index in range.

default prev :: Enum i => (i, i) -> i -> i Source #

next :: (i, i) -> i -> i Source #

Returns next index in range.

default next :: Enum i => (i, i) -> i -> i Source #

offset :: (i, i) -> i -> Int Source #

Returns offset (indent) of index in range.

default offset :: Enum i => (i, i) -> i -> Int Source #

index :: (i, i) -> Int -> i Source #

Returns index by this offset (indent) in range.

default index :: Enum i => (i, i) -> Int -> i Source #

range :: (i, i) -> [i] Source #

Returns the ordered list of indices in this range.

default range :: Enum i => (i, i) -> [i] Source #

subshape :: (Sub i j, Index (i :|: j)) => (i, i) -> (i :|: j) -> (j, j) Source #

subshape bnds ij returns subshape of bnds.

Checks if ij in bnds subshape, may throw IndexException.

slice :: (Sub i j, ij ~ (i :|: j), Index j) => (i, i) -> ij -> ((ij, ij), (j, j)) Source #

Instances

Instances details
Index Char Source # 
Instance details

Defined in SDP.Index

Methods

size :: (Char, Char) -> Int Source #

sizes :: (Char, Char) -> [Int] Source #

safeElem :: (Char, Char) -> Char -> Char Source #

ordBounds :: (Char, Char) -> (Char, Char) Source #

defLimit :: Char -> Integer Source #

defaultBounds :: Int -> (Char, Char) Source #

unsafeIndex :: Int -> Char Source #

isEmpty :: (Char, Char) -> Bool Source #

inBounds :: (Char, Char) -> Char -> InBounds Source #

isOverflow :: (Char, Char) -> Char -> Bool Source #

isUnderflow :: (Char, Char) -> Char -> Bool Source #

inRange :: (Char, Char) -> Char -> Bool Source #

prev :: (Char, Char) -> Char -> Char Source #

next :: (Char, Char) -> Char -> Char Source #

offset :: (Char, Char) -> Char -> Int Source #

index :: (Char, Char) -> Int -> Char Source #

range :: (Char, Char) -> [Char] Source #

subshape :: (Sub Char j, Index (Char :|: j)) => (Char, Char) -> (Char :|: j) -> (j, j) Source #

slice :: (Sub Char j, ij ~ (Char :|: j), Index j) => (Char, Char) -> ij -> ((ij, ij), (j, j)) Source #

Index Int Source # 
Instance details

Defined in SDP.Index

Methods

size :: (Int, Int) -> Int Source #

sizes :: (Int, Int) -> [Int] Source #

safeElem :: (Int, Int) -> Int -> Int Source #

ordBounds :: (Int, Int) -> (Int, Int) Source #

defLimit :: Int -> Integer Source #

defaultBounds :: Int -> (Int, Int) Source #

unsafeIndex :: Int -> Int Source #

isEmpty :: (Int, Int) -> Bool Source #

inBounds :: (Int, Int) -> Int -> InBounds Source #

isOverflow :: (Int, Int) -> Int -> Bool Source #

isUnderflow :: (Int, Int) -> Int -> Bool Source #

inRange :: (Int, Int) -> Int -> Bool Source #

prev :: (Int, Int) -> Int -> Int Source #

next :: (Int, Int) -> Int -> Int Source #

offset :: (Int, Int) -> Int -> Int Source #

index :: (Int, Int) -> Int -> Int Source #

range :: (Int, Int) -> [Int] Source #

subshape :: (Sub Int j, Index (Int :|: j)) => (Int, Int) -> (Int :|: j) -> (j, j) Source #

slice :: (Sub Int j, ij ~ (Int :|: j), Index j) => (Int, Int) -> ij -> ((ij, ij), (j, j)) Source #

Index Int8 Source # 
Instance details

Defined in SDP.Index

Methods

size :: (Int8, Int8) -> Int Source #

sizes :: (Int8, Int8) -> [Int] Source #

safeElem :: (Int8, Int8) -> Int8 -> Int8 Source #

ordBounds :: (Int8, Int8) -> (Int8, Int8) Source #

defLimit :: Int8 -> Integer Source #

defaultBounds :: Int -> (Int8, Int8) Source #

unsafeIndex :: Int -> Int8 Source #

isEmpty :: (Int8, Int8) -> Bool Source #

inBounds :: (Int8, Int8) -> Int8 -> InBounds Source #

isOverflow :: (Int8, Int8) -> Int8 -> Bool Source #

isUnderflow :: (Int8, Int8) -> Int8 -> Bool Source #

inRange :: (Int8, Int8) -> Int8 -> Bool Source #

prev :: (Int8, Int8) -> Int8 -> Int8 Source #

next :: (Int8, Int8) -> Int8 -> Int8 Source #

offset :: (Int8, Int8) -> Int8 -> Int Source #

index :: (Int8, Int8) -> Int -> Int8 Source #

range :: (Int8, Int8) -> [Int8] Source #

subshape :: (Sub Int8 j, Index (Int8 :|: j)) => (Int8, Int8) -> (Int8 :|: j) -> (j, j) Source #

slice :: (Sub Int8 j, ij ~ (Int8 :|: j), Index j) => (Int8, Int8) -> ij -> ((ij, ij), (j, j)) Source #

Index Int16 Source # 
Instance details

Defined in SDP.Index

Index Int32 Source # 
Instance details

Defined in SDP.Index

Index Int64 Source # 
Instance details

Defined in SDP.Index

Index Integer Source #

Note that Integer isn't Bounded, so it can't be used in multidimensional indices.

Instance details

Defined in SDP.Index

Index Word Source # 
Instance details

Defined in SDP.Index

Methods

size :: (Word, Word) -> Int Source #

sizes :: (Word, Word) -> [Int] Source #

safeElem :: (Word, Word) -> Word -> Word Source #

ordBounds :: (Word, Word) -> (Word, Word) Source #

defLimit :: Word -> Integer Source #

defaultBounds :: Int -> (Word, Word) Source #

unsafeIndex :: Int -> Word Source #

isEmpty :: (Word, Word) -> Bool Source #

inBounds :: (Word, Word) -> Word -> InBounds Source #

isOverflow :: (Word, Word) -> Word -> Bool Source #

isUnderflow :: (Word, Word) -> Word -> Bool Source #

inRange :: (Word, Word) -> Word -> Bool Source #

prev :: (Word, Word) -> Word -> Word Source #

next :: (Word, Word) -> Word -> Word Source #

offset :: (Word, Word) -> Word -> Int Source #

index :: (Word, Word) -> Int -> Word Source #

range :: (Word, Word) -> [Word] Source #

subshape :: (Sub Word j, Index (Word :|: j)) => (Word, Word) -> (Word :|: j) -> (j, j) Source #

slice :: (Sub Word j, ij ~ (Word :|: j), Index j) => (Word, Word) -> ij -> ((ij, ij), (j, j)) Source #

Index Word8 Source # 
Instance details

Defined in SDP.Index

Index Word16 Source # 
Instance details

Defined in SDP.Index

Index Word32 Source # 
Instance details

Defined in SDP.Index

Index Word64 Source # 
Instance details

Defined in SDP.Index

Index () Source # 
Instance details

Defined in SDP.Index

Methods

size :: ((), ()) -> Int Source #

sizes :: ((), ()) -> [Int] Source #

safeElem :: ((), ()) -> () -> () Source #

ordBounds :: ((), ()) -> ((), ()) Source #

defLimit :: () -> Integer Source #

defaultBounds :: Int -> ((), ()) Source #

unsafeIndex :: Int -> () Source #

isEmpty :: ((), ()) -> Bool Source #

inBounds :: ((), ()) -> () -> InBounds Source #

isOverflow :: ((), ()) -> () -> Bool Source #

isUnderflow :: ((), ()) -> () -> Bool Source #

inRange :: ((), ()) -> () -> Bool Source #

prev :: ((), ()) -> () -> () Source #

next :: ((), ()) -> () -> () Source #

offset :: ((), ()) -> () -> Int Source #

index :: ((), ()) -> Int -> () Source #

range :: ((), ()) -> [()] Source #

subshape :: (Sub () j, Index (() :|: j)) => ((), ()) -> (() :|: j) -> (j, j) Source #

slice :: (Sub () j, ij ~ (() :|: j), Index j) => ((), ()) -> ij -> ((ij, ij), (j, j)) Source #

Index CChar Source # 
Instance details

Defined in SDP.Index

Index CSChar Source # 
Instance details

Defined in SDP.Index

Index CUChar Source # 
Instance details

Defined in SDP.Index

Index CShort Source # 
Instance details

Defined in SDP.Index

Index CUShort Source # 
Instance details

Defined in SDP.Index

Index CInt Source # 
Instance details

Defined in SDP.Index

Methods

size :: (CInt, CInt) -> Int Source #

sizes :: (CInt, CInt) -> [Int] Source #

safeElem :: (CInt, CInt) -> CInt -> CInt Source #

ordBounds :: (CInt, CInt) -> (CInt, CInt) Source #

defLimit :: CInt -> Integer Source #

defaultBounds :: Int -> (CInt, CInt) Source #

unsafeIndex :: Int -> CInt Source #

isEmpty :: (CInt, CInt) -> Bool Source #

inBounds :: (CInt, CInt) -> CInt -> InBounds Source #

isOverflow :: (CInt, CInt) -> CInt -> Bool Source #

isUnderflow :: (CInt, CInt) -> CInt -> Bool Source #

inRange :: (CInt, CInt) -> CInt -> Bool Source #

prev :: (CInt, CInt) -> CInt -> CInt Source #

next :: (CInt, CInt) -> CInt -> CInt Source #

offset :: (CInt, CInt) -> CInt -> Int Source #

index :: (CInt, CInt) -> Int -> CInt Source #

range :: (CInt, CInt) -> [CInt] Source #

subshape :: (Sub CInt j, Index (CInt :|: j)) => (CInt, CInt) -> (CInt :|: j) -> (j, j) Source #

slice :: (Sub CInt j, ij ~ (CInt :|: j), Index j) => (CInt, CInt) -> ij -> ((ij, ij), (j, j)) Source #

Index CUInt Source # 
Instance details

Defined in SDP.Index

Index CLong Source # 
Instance details

Defined in SDP.Index

Index CULong Source # 
Instance details

Defined in SDP.Index

Index CLLong Source # 
Instance details

Defined in SDP.Index

Index CULLong Source # 
Instance details

Defined in SDP.Index

Index CBool Source # 
Instance details

Defined in SDP.Index

Index CPtrdiff Source # 
Instance details

Defined in SDP.Index

Index CSize Source # 
Instance details

Defined in SDP.Index

Index CWchar Source # 
Instance details

Defined in SDP.Index

Index CSigAtomic Source # 
Instance details

Defined in SDP.Index

Index CIntPtr Source # 
Instance details

Defined in SDP.Index

Index CUIntPtr Source # 
Instance details

Defined in SDP.Index

Index CIntMax Source # 
Instance details

Defined in SDP.Index

Index CUIntMax Source # 
Instance details

Defined in SDP.Index

Index E Source # 
Instance details

Defined in SDP.Index

Methods

size :: (E, E) -> Int Source #

sizes :: (E, E) -> [Int] Source #

safeElem :: (E, E) -> E -> E Source #

ordBounds :: (E, E) -> (E, E) Source #

defLimit :: E -> Integer Source #

defaultBounds :: Int -> (E, E) Source #

unsafeIndex :: Int -> E Source #

isEmpty :: (E, E) -> Bool Source #

inBounds :: (E, E) -> E -> InBounds Source #

isOverflow :: (E, E) -> E -> Bool Source #

isUnderflow :: (E, E) -> E -> Bool Source #

inRange :: (E, E) -> E -> Bool Source #

prev :: (E, E) -> E -> E Source #

next :: (E, E) -> E -> E Source #

offset :: (E, E) -> E -> Int Source #

index :: (E, E) -> Int -> E Source #

range :: (E, E) -> [E] Source #

subshape :: (Sub E j, Index (E :|: j)) => (E, E) -> (E :|: j) -> (j, j) Source #

slice :: (Sub E j, ij ~ (E :|: j), Index j) => (E, E) -> ij -> ((ij, ij), (j, j)) Source #

Index IntAs64 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Index IntAs32 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Index IntAs16 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Index IntAs8 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Index WordAs64 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

Index WordAs32 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

Index WordAs16 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

Index WordAs8 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

(Ord i, Index i, Enum i, Bounded i) => Index (T15 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T15 i, T15 i) -> Int Source #

sizes :: (T15 i, T15 i) -> [Int] Source #

safeElem :: (T15 i, T15 i) -> T15 i -> T15 i Source #

ordBounds :: (T15 i, T15 i) -> (T15 i, T15 i) Source #

defLimit :: T15 i -> Integer Source #

defaultBounds :: Int -> (T15 i, T15 i) Source #

unsafeIndex :: Int -> T15 i Source #

isEmpty :: (T15 i, T15 i) -> Bool Source #

inBounds :: (T15 i, T15 i) -> T15 i -> InBounds Source #

isOverflow :: (T15 i, T15 i) -> T15 i -> Bool Source #

isUnderflow :: (T15 i, T15 i) -> T15 i -> Bool Source #

inRange :: (T15 i, T15 i) -> T15 i -> Bool Source #

prev :: (T15 i, T15 i) -> T15 i -> T15 i Source #

next :: (T15 i, T15 i) -> T15 i -> T15 i Source #

offset :: (T15 i, T15 i) -> T15 i -> Int Source #

index :: (T15 i, T15 i) -> Int -> T15 i Source #

range :: (T15 i, T15 i) -> [T15 i] Source #

subshape :: (Sub (T15 i) j, Index (T15 i :|: j)) => (T15 i, T15 i) -> (T15 i :|: j) -> (j, j) Source #

slice :: (Sub (T15 i) j, ij ~ (T15 i :|: j), Index j) => (T15 i, T15 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T14 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T14 i, T14 i) -> Int Source #

sizes :: (T14 i, T14 i) -> [Int] Source #

safeElem :: (T14 i, T14 i) -> T14 i -> T14 i Source #

ordBounds :: (T14 i, T14 i) -> (T14 i, T14 i) Source #

defLimit :: T14 i -> Integer Source #

defaultBounds :: Int -> (T14 i, T14 i) Source #

unsafeIndex :: Int -> T14 i Source #

isEmpty :: (T14 i, T14 i) -> Bool Source #

inBounds :: (T14 i, T14 i) -> T14 i -> InBounds Source #

isOverflow :: (T14 i, T14 i) -> T14 i -> Bool Source #

isUnderflow :: (T14 i, T14 i) -> T14 i -> Bool Source #

inRange :: (T14 i, T14 i) -> T14 i -> Bool Source #

prev :: (T14 i, T14 i) -> T14 i -> T14 i Source #

next :: (T14 i, T14 i) -> T14 i -> T14 i Source #

offset :: (T14 i, T14 i) -> T14 i -> Int Source #

index :: (T14 i, T14 i) -> Int -> T14 i Source #

range :: (T14 i, T14 i) -> [T14 i] Source #

subshape :: (Sub (T14 i) j, Index (T14 i :|: j)) => (T14 i, T14 i) -> (T14 i :|: j) -> (j, j) Source #

slice :: (Sub (T14 i) j, ij ~ (T14 i :|: j), Index j) => (T14 i, T14 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T13 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T13 i, T13 i) -> Int Source #

sizes :: (T13 i, T13 i) -> [Int] Source #

safeElem :: (T13 i, T13 i) -> T13 i -> T13 i Source #

ordBounds :: (T13 i, T13 i) -> (T13 i, T13 i) Source #

defLimit :: T13 i -> Integer Source #

defaultBounds :: Int -> (T13 i, T13 i) Source #

unsafeIndex :: Int -> T13 i Source #

isEmpty :: (T13 i, T13 i) -> Bool Source #

inBounds :: (T13 i, T13 i) -> T13 i -> InBounds Source #

isOverflow :: (T13 i, T13 i) -> T13 i -> Bool Source #

isUnderflow :: (T13 i, T13 i) -> T13 i -> Bool Source #

inRange :: (T13 i, T13 i) -> T13 i -> Bool Source #

prev :: (T13 i, T13 i) -> T13 i -> T13 i Source #

next :: (T13 i, T13 i) -> T13 i -> T13 i Source #

offset :: (T13 i, T13 i) -> T13 i -> Int Source #

index :: (T13 i, T13 i) -> Int -> T13 i Source #

range :: (T13 i, T13 i) -> [T13 i] Source #

subshape :: (Sub (T13 i) j, Index (T13 i :|: j)) => (T13 i, T13 i) -> (T13 i :|: j) -> (j, j) Source #

slice :: (Sub (T13 i) j, ij ~ (T13 i :|: j), Index j) => (T13 i, T13 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T12 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T12 i, T12 i) -> Int Source #

sizes :: (T12 i, T12 i) -> [Int] Source #

safeElem :: (T12 i, T12 i) -> T12 i -> T12 i Source #

ordBounds :: (T12 i, T12 i) -> (T12 i, T12 i) Source #

defLimit :: T12 i -> Integer Source #

defaultBounds :: Int -> (T12 i, T12 i) Source #

unsafeIndex :: Int -> T12 i Source #

isEmpty :: (T12 i, T12 i) -> Bool Source #

inBounds :: (T12 i, T12 i) -> T12 i -> InBounds Source #

isOverflow :: (T12 i, T12 i) -> T12 i -> Bool Source #

isUnderflow :: (T12 i, T12 i) -> T12 i -> Bool Source #

inRange :: (T12 i, T12 i) -> T12 i -> Bool Source #

prev :: (T12 i, T12 i) -> T12 i -> T12 i Source #

next :: (T12 i, T12 i) -> T12 i -> T12 i Source #

offset :: (T12 i, T12 i) -> T12 i -> Int Source #

index :: (T12 i, T12 i) -> Int -> T12 i Source #

range :: (T12 i, T12 i) -> [T12 i] Source #

subshape :: (Sub (T12 i) j, Index (T12 i :|: j)) => (T12 i, T12 i) -> (T12 i :|: j) -> (j, j) Source #

slice :: (Sub (T12 i) j, ij ~ (T12 i :|: j), Index j) => (T12 i, T12 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T11 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T11 i, T11 i) -> Int Source #

sizes :: (T11 i, T11 i) -> [Int] Source #

safeElem :: (T11 i, T11 i) -> T11 i -> T11 i Source #

ordBounds :: (T11 i, T11 i) -> (T11 i, T11 i) Source #

defLimit :: T11 i -> Integer Source #

defaultBounds :: Int -> (T11 i, T11 i) Source #

unsafeIndex :: Int -> T11 i Source #

isEmpty :: (T11 i, T11 i) -> Bool Source #

inBounds :: (T11 i, T11 i) -> T11 i -> InBounds Source #

isOverflow :: (T11 i, T11 i) -> T11 i -> Bool Source #

isUnderflow :: (T11 i, T11 i) -> T11 i -> Bool Source #

inRange :: (T11 i, T11 i) -> T11 i -> Bool Source #

prev :: (T11 i, T11 i) -> T11 i -> T11 i Source #

next :: (T11 i, T11 i) -> T11 i -> T11 i Source #

offset :: (T11 i, T11 i) -> T11 i -> Int Source #

index :: (T11 i, T11 i) -> Int -> T11 i Source #

range :: (T11 i, T11 i) -> [T11 i] Source #

subshape :: (Sub (T11 i) j, Index (T11 i :|: j)) => (T11 i, T11 i) -> (T11 i :|: j) -> (j, j) Source #

slice :: (Sub (T11 i) j, ij ~ (T11 i :|: j), Index j) => (T11 i, T11 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T10 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T10 i, T10 i) -> Int Source #

sizes :: (T10 i, T10 i) -> [Int] Source #

safeElem :: (T10 i, T10 i) -> T10 i -> T10 i Source #

ordBounds :: (T10 i, T10 i) -> (T10 i, T10 i) Source #

defLimit :: T10 i -> Integer Source #

defaultBounds :: Int -> (T10 i, T10 i) Source #

unsafeIndex :: Int -> T10 i Source #

isEmpty :: (T10 i, T10 i) -> Bool Source #

inBounds :: (T10 i, T10 i) -> T10 i -> InBounds Source #

isOverflow :: (T10 i, T10 i) -> T10 i -> Bool Source #

isUnderflow :: (T10 i, T10 i) -> T10 i -> Bool Source #

inRange :: (T10 i, T10 i) -> T10 i -> Bool Source #

prev :: (T10 i, T10 i) -> T10 i -> T10 i Source #

next :: (T10 i, T10 i) -> T10 i -> T10 i Source #

offset :: (T10 i, T10 i) -> T10 i -> Int Source #

index :: (T10 i, T10 i) -> Int -> T10 i Source #

range :: (T10 i, T10 i) -> [T10 i] Source #

subshape :: (Sub (T10 i) j, Index (T10 i :|: j)) => (T10 i, T10 i) -> (T10 i :|: j) -> (j, j) Source #

slice :: (Sub (T10 i) j, ij ~ (T10 i :|: j), Index j) => (T10 i, T10 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T9 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T9 i, T9 i) -> Int Source #

sizes :: (T9 i, T9 i) -> [Int] Source #

safeElem :: (T9 i, T9 i) -> T9 i -> T9 i Source #

ordBounds :: (T9 i, T9 i) -> (T9 i, T9 i) Source #

defLimit :: T9 i -> Integer Source #

defaultBounds :: Int -> (T9 i, T9 i) Source #

unsafeIndex :: Int -> T9 i Source #

isEmpty :: (T9 i, T9 i) -> Bool Source #

inBounds :: (T9 i, T9 i) -> T9 i -> InBounds Source #

isOverflow :: (T9 i, T9 i) -> T9 i -> Bool Source #

isUnderflow :: (T9 i, T9 i) -> T9 i -> Bool Source #

inRange :: (T9 i, T9 i) -> T9 i -> Bool Source #

prev :: (T9 i, T9 i) -> T9 i -> T9 i Source #

next :: (T9 i, T9 i) -> T9 i -> T9 i Source #

offset :: (T9 i, T9 i) -> T9 i -> Int Source #

index :: (T9 i, T9 i) -> Int -> T9 i Source #

range :: (T9 i, T9 i) -> [T9 i] Source #

subshape :: (Sub (T9 i) j, Index (T9 i :|: j)) => (T9 i, T9 i) -> (T9 i :|: j) -> (j, j) Source #

slice :: (Sub (T9 i) j, ij ~ (T9 i :|: j), Index j) => (T9 i, T9 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T8 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T8 i, T8 i) -> Int Source #

sizes :: (T8 i, T8 i) -> [Int] Source #

safeElem :: (T8 i, T8 i) -> T8 i -> T8 i Source #

ordBounds :: (T8 i, T8 i) -> (T8 i, T8 i) Source #

defLimit :: T8 i -> Integer Source #

defaultBounds :: Int -> (T8 i, T8 i) Source #

unsafeIndex :: Int -> T8 i Source #

isEmpty :: (T8 i, T8 i) -> Bool Source #

inBounds :: (T8 i, T8 i) -> T8 i -> InBounds Source #

isOverflow :: (T8 i, T8 i) -> T8 i -> Bool Source #

isUnderflow :: (T8 i, T8 i) -> T8 i -> Bool Source #

inRange :: (T8 i, T8 i) -> T8 i -> Bool Source #

prev :: (T8 i, T8 i) -> T8 i -> T8 i Source #

next :: (T8 i, T8 i) -> T8 i -> T8 i Source #

offset :: (T8 i, T8 i) -> T8 i -> Int Source #

index :: (T8 i, T8 i) -> Int -> T8 i Source #

range :: (T8 i, T8 i) -> [T8 i] Source #

subshape :: (Sub (T8 i) j, Index (T8 i :|: j)) => (T8 i, T8 i) -> (T8 i :|: j) -> (j, j) Source #

slice :: (Sub (T8 i) j, ij ~ (T8 i :|: j), Index j) => (T8 i, T8 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T7 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T7 i, T7 i) -> Int Source #

sizes :: (T7 i, T7 i) -> [Int] Source #

safeElem :: (T7 i, T7 i) -> T7 i -> T7 i Source #

ordBounds :: (T7 i, T7 i) -> (T7 i, T7 i) Source #

defLimit :: T7 i -> Integer Source #

defaultBounds :: Int -> (T7 i, T7 i) Source #

unsafeIndex :: Int -> T7 i Source #

isEmpty :: (T7 i, T7 i) -> Bool Source #

inBounds :: (T7 i, T7 i) -> T7 i -> InBounds Source #

isOverflow :: (T7 i, T7 i) -> T7 i -> Bool Source #

isUnderflow :: (T7 i, T7 i) -> T7 i -> Bool Source #

inRange :: (T7 i, T7 i) -> T7 i -> Bool Source #

prev :: (T7 i, T7 i) -> T7 i -> T7 i Source #

next :: (T7 i, T7 i) -> T7 i -> T7 i Source #

offset :: (T7 i, T7 i) -> T7 i -> Int Source #

index :: (T7 i, T7 i) -> Int -> T7 i Source #

range :: (T7 i, T7 i) -> [T7 i] Source #

subshape :: (Sub (T7 i) j, Index (T7 i :|: j)) => (T7 i, T7 i) -> (T7 i :|: j) -> (j, j) Source #

slice :: (Sub (T7 i) j, ij ~ (T7 i :|: j), Index j) => (T7 i, T7 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T6 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T6 i, T6 i) -> Int Source #

sizes :: (T6 i, T6 i) -> [Int] Source #

safeElem :: (T6 i, T6 i) -> T6 i -> T6 i Source #

ordBounds :: (T6 i, T6 i) -> (T6 i, T6 i) Source #

defLimit :: T6 i -> Integer Source #

defaultBounds :: Int -> (T6 i, T6 i) Source #

unsafeIndex :: Int -> T6 i Source #

isEmpty :: (T6 i, T6 i) -> Bool Source #

inBounds :: (T6 i, T6 i) -> T6 i -> InBounds Source #

isOverflow :: (T6 i, T6 i) -> T6 i -> Bool Source #

isUnderflow :: (T6 i, T6 i) -> T6 i -> Bool Source #

inRange :: (T6 i, T6 i) -> T6 i -> Bool Source #

prev :: (T6 i, T6 i) -> T6 i -> T6 i Source #

next :: (T6 i, T6 i) -> T6 i -> T6 i Source #

offset :: (T6 i, T6 i) -> T6 i -> Int Source #

index :: (T6 i, T6 i) -> Int -> T6 i Source #

range :: (T6 i, T6 i) -> [T6 i] Source #

subshape :: (Sub (T6 i) j, Index (T6 i :|: j)) => (T6 i, T6 i) -> (T6 i :|: j) -> (j, j) Source #

slice :: (Sub (T6 i) j, ij ~ (T6 i :|: j), Index j) => (T6 i, T6 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T5 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T5 i, T5 i) -> Int Source #

sizes :: (T5 i, T5 i) -> [Int] Source #

safeElem :: (T5 i, T5 i) -> T5 i -> T5 i Source #

ordBounds :: (T5 i, T5 i) -> (T5 i, T5 i) Source #

defLimit :: T5 i -> Integer Source #

defaultBounds :: Int -> (T5 i, T5 i) Source #

unsafeIndex :: Int -> T5 i Source #

isEmpty :: (T5 i, T5 i) -> Bool Source #

inBounds :: (T5 i, T5 i) -> T5 i -> InBounds Source #

isOverflow :: (T5 i, T5 i) -> T5 i -> Bool Source #

isUnderflow :: (T5 i, T5 i) -> T5 i -> Bool Source #

inRange :: (T5 i, T5 i) -> T5 i -> Bool Source #

prev :: (T5 i, T5 i) -> T5 i -> T5 i Source #

next :: (T5 i, T5 i) -> T5 i -> T5 i Source #

offset :: (T5 i, T5 i) -> T5 i -> Int Source #

index :: (T5 i, T5 i) -> Int -> T5 i Source #

range :: (T5 i, T5 i) -> [T5 i] Source #

subshape :: (Sub (T5 i) j, Index (T5 i :|: j)) => (T5 i, T5 i) -> (T5 i :|: j) -> (j, j) Source #

slice :: (Sub (T5 i) j, ij ~ (T5 i :|: j), Index j) => (T5 i, T5 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T4 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T4 i, T4 i) -> Int Source #

sizes :: (T4 i, T4 i) -> [Int] Source #

safeElem :: (T4 i, T4 i) -> T4 i -> T4 i Source #

ordBounds :: (T4 i, T4 i) -> (T4 i, T4 i) Source #

defLimit :: T4 i -> Integer Source #

defaultBounds :: Int -> (T4 i, T4 i) Source #

unsafeIndex :: Int -> T4 i Source #

isEmpty :: (T4 i, T4 i) -> Bool Source #

inBounds :: (T4 i, T4 i) -> T4 i -> InBounds Source #

isOverflow :: (T4 i, T4 i) -> T4 i -> Bool Source #

isUnderflow :: (T4 i, T4 i) -> T4 i -> Bool Source #

inRange :: (T4 i, T4 i) -> T4 i -> Bool Source #

prev :: (T4 i, T4 i) -> T4 i -> T4 i Source #

next :: (T4 i, T4 i) -> T4 i -> T4 i Source #

offset :: (T4 i, T4 i) -> T4 i -> Int Source #

index :: (T4 i, T4 i) -> Int -> T4 i Source #

range :: (T4 i, T4 i) -> [T4 i] Source #

subshape :: (Sub (T4 i) j, Index (T4 i :|: j)) => (T4 i, T4 i) -> (T4 i :|: j) -> (j, j) Source #

slice :: (Sub (T4 i) j, ij ~ (T4 i :|: j), Index j) => (T4 i, T4 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T3 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T3 i, T3 i) -> Int Source #

sizes :: (T3 i, T3 i) -> [Int] Source #

safeElem :: (T3 i, T3 i) -> T3 i -> T3 i Source #

ordBounds :: (T3 i, T3 i) -> (T3 i, T3 i) Source #

defLimit :: T3 i -> Integer Source #

defaultBounds :: Int -> (T3 i, T3 i) Source #

unsafeIndex :: Int -> T3 i Source #

isEmpty :: (T3 i, T3 i) -> Bool Source #

inBounds :: (T3 i, T3 i) -> T3 i -> InBounds Source #

isOverflow :: (T3 i, T3 i) -> T3 i -> Bool Source #

isUnderflow :: (T3 i, T3 i) -> T3 i -> Bool Source #

inRange :: (T3 i, T3 i) -> T3 i -> Bool Source #

prev :: (T3 i, T3 i) -> T3 i -> T3 i Source #

next :: (T3 i, T3 i) -> T3 i -> T3 i Source #

offset :: (T3 i, T3 i) -> T3 i -> Int Source #

index :: (T3 i, T3 i) -> Int -> T3 i Source #

range :: (T3 i, T3 i) -> [T3 i] Source #

subshape :: (Sub (T3 i) j, Index (T3 i :|: j)) => (T3 i, T3 i) -> (T3 i :|: j) -> (j, j) Source #

slice :: (Sub (T3 i) j, ij ~ (T3 i :|: j), Index j) => (T3 i, T3 i) -> ij -> ((ij, ij), (j, j)) Source #

(Ord i, Index i, Enum i, Bounded i) => Index (T2 i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (T2 i, T2 i) -> Int Source #

sizes :: (T2 i, T2 i) -> [Int] Source #

safeElem :: (T2 i, T2 i) -> T2 i -> T2 i Source #

ordBounds :: (T2 i, T2 i) -> (T2 i, T2 i) Source #

defLimit :: T2 i -> Integer Source #

defaultBounds :: Int -> (T2 i, T2 i) Source #

unsafeIndex :: Int -> T2 i Source #

isEmpty :: (T2 i, T2 i) -> Bool Source #

inBounds :: (T2 i, T2 i) -> T2 i -> InBounds Source #

isOverflow :: (T2 i, T2 i) -> T2 i -> Bool Source #

isUnderflow :: (T2 i, T2 i) -> T2 i -> Bool Source #

inRange :: (T2 i, T2 i) -> T2 i -> Bool Source #

prev :: (T2 i, T2 i) -> T2 i -> T2 i Source #

next :: (T2 i, T2 i) -> T2 i -> T2 i Source #

offset :: (T2 i, T2 i) -> T2 i -> Int Source #

index :: (T2 i, T2 i) -> Int -> T2 i Source #

range :: (T2 i, T2 i) -> [T2 i] Source #

subshape :: (Sub (T2 i) j, Index (T2 i :|: j)) => (T2 i, T2 i) -> (T2 i :|: j) -> (j, j) Source #

slice :: (Sub (T2 i) j, ij ~ (T2 i :|: j), Index j) => (T2 i, T2 i) -> ij -> ((ij, ij), (j, j)) Source #

(Index i, Enum i, Bounded i, Index (i' :& i)) => Index ((i' :& i) :& i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: ((i' :& i) :& i, (i' :& i) :& i) -> Int Source #

sizes :: ((i' :& i) :& i, (i' :& i) :& i) -> [Int] Source #

safeElem :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> (i' :& i) :& i Source #

ordBounds :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i, (i' :& i) :& i) Source #

defLimit :: ((i' :& i) :& i) -> Integer Source #

defaultBounds :: Int -> ((i' :& i) :& i, (i' :& i) :& i) Source #

unsafeIndex :: Int -> (i' :& i) :& i Source #

isEmpty :: ((i' :& i) :& i, (i' :& i) :& i) -> Bool Source #

inBounds :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> InBounds Source #

isOverflow :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> Bool Source #

isUnderflow :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> Bool Source #

inRange :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> Bool Source #

prev :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> (i' :& i) :& i Source #

next :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> (i' :& i) :& i Source #

offset :: ((i' :& i) :& i, (i' :& i) :& i) -> ((i' :& i) :& i) -> Int Source #

index :: ((i' :& i) :& i, (i' :& i) :& i) -> Int -> (i' :& i) :& i Source #

range :: ((i' :& i) :& i, (i' :& i) :& i) -> [(i' :& i) :& i] Source #

subshape :: (Sub ((i' :& i) :& i) j, Index (((i' :& i) :& i) :|: j)) => ((i' :& i) :& i, (i' :& i) :& i) -> (((i' :& i) :& i) :|: j) -> (j, j) Source #

slice :: (Sub ((i' :& i) :& i) j, ij ~ (((i' :& i) :& i) :|: j), Index j) => ((i' :& i) :& i, (i' :& i) :& i) -> ij -> ((ij, ij), (j, j)) Source #

Index i => Index (E :& i) Source # 
Instance details

Defined in SDP.Index

Methods

size :: (E :& i, E :& i) -> Int Source #

sizes :: (E :& i, E :& i) -> [Int] Source #

safeElem :: (E :& i, E :& i) -> (E :& i) -> E :& i Source #

ordBounds :: (E :& i, E :& i) -> (E :& i, E :& i) Source #

defLimit :: (E :& i) -> Integer Source #

defaultBounds :: Int -> (E :& i, E :& i) Source #

unsafeIndex :: Int -> E :& i Source #

isEmpty :: (E :& i, E :& i) -> Bool Source #

inBounds :: (E :& i, E :& i) -> (E :& i) -> InBounds Source #

isOverflow :: (E :& i, E :& i) -> (E :& i) -> Bool Source #

isUnderflow :: (E :& i, E :& i) -> (E :& i) -> Bool Source #

inRange :: (E :& i, E :& i) -> (E :& i) -> Bool Source #

prev :: (E :& i, E :& i) -> (E :& i) -> E :& i Source #

next :: (E :& i, E :& i) -> (E :& i) -> E :& i Source #

offset :: (E :& i, E :& i) -> (E :& i) -> Int Source #

index :: (E :& i, E :& i) -> Int -> E :& i Source #

range :: (E :& i, E :& i) -> [E :& i] Source #

subshape :: (Sub (E :& i) j, Index ((E :& i) :|: j)) => (E :& i, E :& i) -> ((E :& i) :|: j) -> (j, j) Source #

slice :: (Sub (E :& i) j, ij ~ ((E :& i) :|: j), Index j) => (E :& i, E :& i) -> ij -> ((ij, ij), (j, j)) Source #

Helpers

data InBounds Source #

InBounds - service type that specifies index and bounds status.

Constructors

ER

Empty range

UR

Underflow range

IN

Index in range

OR

Overflow range

Instances

Instances details
Enum InBounds Source # 
Instance details

Defined in SDP.Index

Eq InBounds Source # 
Instance details

Defined in SDP.Index

Read InBounds Source # 
Instance details

Defined in SDP.Index

Show InBounds Source # 
Instance details

Defined in SDP.Index

offsetIntegral :: (Index i, Integral i) => (i, i) -> i -> Int Source #

Default offset for Integral types.

defaultBoundsUnsign :: (Index i, Bounded i) => Int -> (i, i) Source #

Default defaultBounds for unsigned types.

Orphan instances

Index i => Estimate (i, i) Source # 
Instance details

Methods

(<.=>) :: (i, i) -> Int -> Ordering Source #

(<==>) :: Compare (i, i) Source #

(.==) :: (i, i) -> Int -> Bool Source #

(./=) :: (i, i) -> Int -> Bool Source #

(.<=) :: (i, i) -> Int -> Bool Source #

(.>=) :: (i, i) -> Int -> Bool Source #

(.<) :: (i, i) -> Int -> Bool Source #

(.>) :: (i, i) -> Int -> Bool Source #

(.<.) :: (i, i) -> (i, i) -> Bool Source #

(.>.) :: (i, i) -> (i, i) -> Bool Source #

(.<=.) :: (i, i) -> (i, i) -> Bool Source #

(.>=.) :: (i, i) -> (i, i) -> Bool Source #

(.==.) :: (i, i) -> (i, i) -> Bool Source #

(./=.) :: (i, i) -> (i, i) -> Bool Source #

Index i => Nullable (i, i) Source # 
Instance details

Methods

lzero :: (i, i) Source #

isNull :: (i, i) -> Bool Source #