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

SDP.Shape

Description

SDP.Shape module provides Shape - class of generalized indices.

Synopsis

Exports

module SDP.Finite

module SDP.Tuple

module Data.Word

module Data.Int

Shapes

class Shape i where Source #

Shape is service class that constraints Index.

Rules:

rank i == rank   (j `asTypeOf` i)
rank i == length (sizes (i, i))
rank (lastDim E) = 0
rank (lastDim i) = 1
rank (initDim E) = 0
rank (lastDim i) = rank i - 1
fromGIndex . toGIndex = id
toGIndex . fromGIndex = id

Minimal complete definition

Nothing

Associated Types

type DimLast i :: Type Source #

Type of index top dimension.

type DimLast i = i

type DimInit i :: Type Source #

The type of subspace of rank n - 1, where n is the rank of the space specified by this Index type.

type DimInit i = E

Methods

fromGIndex :: GIndex i -> i Source #

Create index from generalized index.

default fromGIndex :: RANK1 i => GIndex i -> i Source #

toGIndex :: i -> GIndex i Source #

Create generalized index from index.

default toGIndex :: RANK1 i => i -> GIndex i Source #

rank :: i -> Int Source #

Count of dimensions in represented space (must be finite and constant).

consDim :: DimInit i -> DimLast i -> i Source #

Add new dimension.

default consDim :: DimLast i ~~ i => DimInit i -> DimLast i -> i Source #

initDim :: i -> DimInit i Source #

default initDim :: DimInit i ~~ E => i -> DimInit i Source #

lastDim :: i -> DimLast i Source #

default lastDim :: DimLast i ~~ i => i -> DimLast i Source #

unconsDim :: i -> (DimInit i, DimLast i) Source #

Instances

Instances details
Shape Char Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Char Source #

type DimInit Char Source #

Shape Int Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Int Source #

type DimInit Int Source #

Shape Int8 Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Int8 Source #

type DimInit Int8 Source #

Shape Int16 Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Int16 Source #

type DimInit Int16 Source #

Shape Int32 Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Int32 Source #

type DimInit Int32 Source #

Shape Int64 Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Int64 Source #

type DimInit Int64 Source #

Shape Integer Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Integer Source #

type DimInit Integer Source #

Shape Word Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Word Source #

type DimInit Word Source #

Shape Word8 Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Word8 Source #

type DimInit Word8 Source #

Shape Word16 Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Word16 Source #

type DimInit Word16 Source #

Shape Word32 Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Word32 Source #

type DimInit Word32 Source #

Shape Word64 Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast Word64 Source #

type DimInit Word64 Source #

Shape () Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast () Source #

type DimInit () Source #

Methods

fromGIndex :: GIndex () -> () Source #

toGIndex :: () -> GIndex () Source #

rank :: () -> Int Source #

consDim :: DimInit () -> DimLast () -> () Source #

initDim :: () -> DimInit () Source #

lastDim :: () -> DimLast () Source #

unconsDim :: () -> (DimInit (), DimLast ()) Source #

Shape CChar Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CChar Source #

type DimInit CChar Source #

Shape CSChar Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CSChar Source #

type DimInit CSChar Source #

Shape CUChar Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CUChar Source #

type DimInit CUChar Source #

Shape CShort Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CShort Source #

type DimInit CShort Source #

Shape CUShort Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CUShort Source #

type DimInit CUShort Source #

Shape CInt Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CInt Source #

type DimInit CInt Source #

Shape CUInt Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CUInt Source #

type DimInit CUInt Source #

Shape CLong Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CLong Source #

type DimInit CLong Source #

Shape CULong Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CULong Source #

type DimInit CULong Source #

Shape CLLong Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CLLong Source #

type DimInit CLLong Source #

Shape CULLong Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CULLong Source #

type DimInit CULLong Source #

Shape CBool Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CBool Source #

type DimInit CBool Source #

Shape CPtrdiff Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CPtrdiff Source #

type DimInit CPtrdiff Source #

Shape CSize Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CSize Source #

type DimInit CSize Source #

Shape CWchar Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CWchar Source #

type DimInit CWchar Source #

Shape CSigAtomic Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CSigAtomic Source #

type DimInit CSigAtomic Source #

Shape CIntPtr Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CIntPtr Source #

type DimInit CIntPtr Source #

Shape CUIntPtr Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CUIntPtr Source #

type DimInit CUIntPtr Source #

Shape CIntMax Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CIntMax Source #

type DimInit CIntMax Source #

Shape CUIntMax Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast CUIntMax Source #

type DimInit CUIntMax Source #

Shape E Source # 
Instance details

Defined in SDP.Shape

Associated Types

type DimLast E Source #

type DimInit E Source #

Shape IntAs64 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Associated Types

type DimLast IntAs64 Source #

type DimInit IntAs64 Source #

Shape IntAs32 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Associated Types

type DimLast IntAs32 Source #

type DimInit IntAs32 Source #

Shape IntAs16 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Associated Types

type DimLast IntAs16 Source #

type DimInit IntAs16 Source #

Shape IntAs8 Source # 
Instance details

Defined in SDP.Unboxed.IntAs

Associated Types

type DimLast IntAs8 Source #

type DimInit IntAs8 Source #

Shape WordAs64 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

Associated Types

type DimLast WordAs64 Source #

type DimInit WordAs64 Source #

Shape WordAs32 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

Associated Types

type DimLast WordAs32 Source #

type DimInit WordAs32 Source #

Shape WordAs16 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

Associated Types

type DimLast WordAs16 Source #

type DimInit WordAs16 Source #

Shape WordAs8 Source # 
Instance details

Defined in SDP.Unboxed.WordAs

Associated Types

type DimLast WordAs8 Source #

type DimInit WordAs8 Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T15 i) Source #

type DimInit (T15 i) Source #

Methods

fromGIndex :: GIndex (T15 i) -> T15 i Source #

toGIndex :: T15 i -> GIndex (T15 i) Source #

rank :: T15 i -> Int Source #

consDim :: DimInit (T15 i) -> DimLast (T15 i) -> T15 i Source #

initDim :: T15 i -> DimInit (T15 i) Source #

lastDim :: T15 i -> DimLast (T15 i) Source #

unconsDim :: T15 i -> (DimInit (T15 i), DimLast (T15 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T14 i) Source #

type DimInit (T14 i) Source #

Methods

fromGIndex :: GIndex (T14 i) -> T14 i Source #

toGIndex :: T14 i -> GIndex (T14 i) Source #

rank :: T14 i -> Int Source #

consDim :: DimInit (T14 i) -> DimLast (T14 i) -> T14 i Source #

initDim :: T14 i -> DimInit (T14 i) Source #

lastDim :: T14 i -> DimLast (T14 i) Source #

unconsDim :: T14 i -> (DimInit (T14 i), DimLast (T14 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T13 i) Source #

type DimInit (T13 i) Source #

Methods

fromGIndex :: GIndex (T13 i) -> T13 i Source #

toGIndex :: T13 i -> GIndex (T13 i) Source #

rank :: T13 i -> Int Source #

consDim :: DimInit (T13 i) -> DimLast (T13 i) -> T13 i Source #

initDim :: T13 i -> DimInit (T13 i) Source #

lastDim :: T13 i -> DimLast (T13 i) Source #

unconsDim :: T13 i -> (DimInit (T13 i), DimLast (T13 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T12 i) Source #

type DimInit (T12 i) Source #

Methods

fromGIndex :: GIndex (T12 i) -> T12 i Source #

toGIndex :: T12 i -> GIndex (T12 i) Source #

rank :: T12 i -> Int Source #

consDim :: DimInit (T12 i) -> DimLast (T12 i) -> T12 i Source #

initDim :: T12 i -> DimInit (T12 i) Source #

lastDim :: T12 i -> DimLast (T12 i) Source #

unconsDim :: T12 i -> (DimInit (T12 i), DimLast (T12 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T11 i) Source #

type DimInit (T11 i) Source #

Methods

fromGIndex :: GIndex (T11 i) -> T11 i Source #

toGIndex :: T11 i -> GIndex (T11 i) Source #

rank :: T11 i -> Int Source #

consDim :: DimInit (T11 i) -> DimLast (T11 i) -> T11 i Source #

initDim :: T11 i -> DimInit (T11 i) Source #

lastDim :: T11 i -> DimLast (T11 i) Source #

unconsDim :: T11 i -> (DimInit (T11 i), DimLast (T11 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T10 i) Source #

type DimInit (T10 i) Source #

Methods

fromGIndex :: GIndex (T10 i) -> T10 i Source #

toGIndex :: T10 i -> GIndex (T10 i) Source #

rank :: T10 i -> Int Source #

consDim :: DimInit (T10 i) -> DimLast (T10 i) -> T10 i Source #

initDim :: T10 i -> DimInit (T10 i) Source #

lastDim :: T10 i -> DimLast (T10 i) Source #

unconsDim :: T10 i -> (DimInit (T10 i), DimLast (T10 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T9 i) Source #

type DimInit (T9 i) Source #

Methods

fromGIndex :: GIndex (T9 i) -> T9 i Source #

toGIndex :: T9 i -> GIndex (T9 i) Source #

rank :: T9 i -> Int Source #

consDim :: DimInit (T9 i) -> DimLast (T9 i) -> T9 i Source #

initDim :: T9 i -> DimInit (T9 i) Source #

lastDim :: T9 i -> DimLast (T9 i) Source #

unconsDim :: T9 i -> (DimInit (T9 i), DimLast (T9 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T8 i) Source #

type DimInit (T8 i) Source #

Methods

fromGIndex :: GIndex (T8 i) -> T8 i Source #

toGIndex :: T8 i -> GIndex (T8 i) Source #

rank :: T8 i -> Int Source #

consDim :: DimInit (T8 i) -> DimLast (T8 i) -> T8 i Source #

initDim :: T8 i -> DimInit (T8 i) Source #

lastDim :: T8 i -> DimLast (T8 i) Source #

unconsDim :: T8 i -> (DimInit (T8 i), DimLast (T8 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T7 i) Source #

type DimInit (T7 i) Source #

Methods

fromGIndex :: GIndex (T7 i) -> T7 i Source #

toGIndex :: T7 i -> GIndex (T7 i) Source #

rank :: T7 i -> Int Source #

consDim :: DimInit (T7 i) -> DimLast (T7 i) -> T7 i Source #

initDim :: T7 i -> DimInit (T7 i) Source #

lastDim :: T7 i -> DimLast (T7 i) Source #

unconsDim :: T7 i -> (DimInit (T7 i), DimLast (T7 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T6 i) Source #

type DimInit (T6 i) Source #

Methods

fromGIndex :: GIndex (T6 i) -> T6 i Source #

toGIndex :: T6 i -> GIndex (T6 i) Source #

rank :: T6 i -> Int Source #

consDim :: DimInit (T6 i) -> DimLast (T6 i) -> T6 i Source #

initDim :: T6 i -> DimInit (T6 i) Source #

lastDim :: T6 i -> DimLast (T6 i) Source #

unconsDim :: T6 i -> (DimInit (T6 i), DimLast (T6 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T5 i) Source #

type DimInit (T5 i) Source #

Methods

fromGIndex :: GIndex (T5 i) -> T5 i Source #

toGIndex :: T5 i -> GIndex (T5 i) Source #

rank :: T5 i -> Int Source #

consDim :: DimInit (T5 i) -> DimLast (T5 i) -> T5 i Source #

initDim :: T5 i -> DimInit (T5 i) Source #

lastDim :: T5 i -> DimLast (T5 i) Source #

unconsDim :: T5 i -> (DimInit (T5 i), DimLast (T5 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T4 i) Source #

type DimInit (T4 i) Source #

Methods

fromGIndex :: GIndex (T4 i) -> T4 i Source #

toGIndex :: T4 i -> GIndex (T4 i) Source #

rank :: T4 i -> Int Source #

consDim :: DimInit (T4 i) -> DimLast (T4 i) -> T4 i Source #

initDim :: T4 i -> DimInit (T4 i) Source #

lastDim :: T4 i -> DimLast (T4 i) Source #

unconsDim :: T4 i -> (DimInit (T4 i), DimLast (T4 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T3 i) Source #

type DimInit (T3 i) Source #

Methods

fromGIndex :: GIndex (T3 i) -> T3 i Source #

toGIndex :: T3 i -> GIndex (T3 i) Source #

rank :: T3 i -> Int Source #

consDim :: DimInit (T3 i) -> DimLast (T3 i) -> T3 i Source #

initDim :: T3 i -> DimInit (T3 i) Source #

lastDim :: T3 i -> DimLast (T3 i) Source #

unconsDim :: T3 i -> (DimInit (T3 i), DimLast (T3 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (T2 i) Source #

type DimInit (T2 i) Source #

Methods

fromGIndex :: GIndex (T2 i) -> T2 i Source #

toGIndex :: T2 i -> GIndex (T2 i) Source #

rank :: T2 i -> Int Source #

consDim :: DimInit (T2 i) -> DimLast (T2 i) -> T2 i Source #

initDim :: T2 i -> DimInit (T2 i) Source #

lastDim :: T2 i -> DimLast (T2 i) Source #

unconsDim :: T2 i -> (DimInit (T2 i), DimLast (T2 i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast ((i' :& i) :& i) Source #

type DimInit ((i' :& i) :& i) Source #

Methods

fromGIndex :: GIndex ((i' :& i) :& i) -> (i' :& i) :& i Source #

toGIndex :: ((i' :& i) :& i) -> GIndex ((i' :& i) :& i) Source #

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

consDim :: DimInit ((i' :& i) :& i) -> DimLast ((i' :& i) :& i) -> (i' :& i) :& i Source #

initDim :: ((i' :& i) :& i) -> DimInit ((i' :& i) :& i) Source #

lastDim :: ((i' :& i) :& i) -> DimLast ((i' :& i) :& i) Source #

unconsDim :: ((i' :& i) :& i) -> (DimInit ((i' :& i) :& i), DimLast ((i' :& i) :& i)) Source #

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

Defined in SDP.Shape

Associated Types

type DimLast (E :& i) Source #

type DimInit (E :& i) Source #

Methods

fromGIndex :: GIndex (E :& i) -> E :& i Source #

toGIndex :: (E :& i) -> GIndex (E :& i) Source #

rank :: (E :& i) -> Int Source #

consDim :: DimInit (E :& i) -> DimLast (E :& i) -> E :& i Source #

initDim :: (E :& i) -> DimInit (E :& i) Source #

lastDim :: (E :& i) -> DimLast (E :& i) Source #

unconsDim :: (E :& i) -> (DimInit (E :& i), DimLast (E :& i)) Source #

type family GIndex i where ... Source #

Type operator GIndex returns generalized equivalent of index.

Equations

GIndex E = E 
GIndex (i' :& i) = i' :& i 
GIndex i = GIndex (DimInit i) :& DimLast i 

toGBounds :: Shape i => (i, i) -> (GIndex i, GIndex i) Source #

Convert any index type bounds to generalized index bounds.

fromGBounds :: Shape i => (GIndex i, GIndex i) -> (i, i) Source #

Convert generalized index bounds to any index type bounds.

Rank constraints

type RANK0 i = i ~~ E Source #

A constraint corresponding to rank 0 indices (E).

type RANK1 i = GIndex i ~~ (E :& i) Source #

The restriction corresponding to rank indices 1 (сhecks GIndex).

type RANK2 i = GIndex i ~~ I2 i Source #

The restriction corresponding to rank indices 2 (сhecks GIndex).

type RANK3 i = GIndex i ~~ I3 i Source #

The restriction corresponding to rank indices 3 (сhecks GIndex).

type RANK4 i = GIndex i ~~ I4 i Source #

The restriction corresponding to rank indices 4 (сhecks GIndex).

type RANK5 i = GIndex i ~~ I5 i Source #

The restriction corresponding to rank indices 5 (сhecks GIndex).

type RANK6 i = GIndex i ~~ I6 i Source #

The restriction corresponding to rank indices 6 (сhecks GIndex).

type RANK7 i = GIndex i ~~ I7 i Source #

The restriction corresponding to rank indices 7 (сhecks GIndex).

type RANK8 i = GIndex i ~~ I8 i Source #

The restriction corresponding to rank indices 8 (сhecks GIndex).

type RANK9 i = GIndex i ~~ I9 i Source #

The restriction corresponding to rank indices 9 (сhecks GIndex).

type RANK10 i = GIndex i ~~ I10 i Source #

The restriction corresponding to rank indices 10 (сhecks GIndex).

type RANK11 i = GIndex i ~~ I11 i Source #

The restriction corresponding to rank indices 11 (сhecks GIndex).

type RANK12 i = GIndex i ~~ I12 i Source #

The restriction corresponding to rank indices 12 (сhecks GIndex).

type RANK13 i = GIndex i ~~ I13 i Source #

The restriction corresponding to rank indices 13 (сhecks GIndex).

type RANK14 i = GIndex i ~~ I14 i Source #

The restriction corresponding to rank indices 14 (сhecks GIndex).

type RANK15 i = GIndex i ~~ I15 i Source #

The restriction corresponding to rank indices 15 (сhecks GIndex).