comfort-array-0.0.1.1: Arrays where the index type is a function of the shape type

Safe HaskellNone
LanguageHaskell98

Data.Array.Comfort.Shape

Synopsis

Documentation

class C sh where Source #

Minimal complete definition

indices, size, (sizeOffset | offset), inBounds

Associated Types

type Index sh :: * Source #

Methods

indices :: sh -> [Index sh] Source #

offset :: sh -> Index sh -> Int Source #

uncheckedOffset :: sh -> Index sh -> Int Source #

inBounds :: sh -> Index sh -> Bool Source #

size :: sh -> Int Source #

uncheckedSize :: sh -> Int Source #

sizeOffset :: sh -> Index sh -> (Int, Int) Source #

uncheckedSizeOffset :: sh -> Index sh -> (Int, Int) Source #

Instances
C () Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index () :: * Source #

Methods

indices :: () -> [Index ()] Source #

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

uncheckedOffset :: () -> Index () -> Int Source #

inBounds :: () -> Index () -> Bool Source #

size :: () -> Int Source #

uncheckedSize :: () -> Int Source #

sizeOffset :: () -> Index () -> (Int, Int) Source #

uncheckedSizeOffset :: () -> Index () -> (Int, Int) Source #

Integral n => C (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Shifted n) :: * Source #

Ix n => C (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Range n) :: * Source #

Integral n => C (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (OneBased n) :: * Source #

Integral n => C (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (ZeroBased n) :: * Source #

(C sh0, C sh1) => C (sh0, sh1) Source #

Row-major composition of two dimensions.

Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (sh0, sh1) :: * Source #

Methods

indices :: (sh0, sh1) -> [Index (sh0, sh1)] Source #

offset :: (sh0, sh1) -> Index (sh0, sh1) -> Int Source #

uncheckedOffset :: (sh0, sh1) -> Index (sh0, sh1) -> Int Source #

inBounds :: (sh0, sh1) -> Index (sh0, sh1) -> Bool Source #

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

uncheckedSize :: (sh0, sh1) -> Int Source #

sizeOffset :: (sh0, sh1) -> Index (sh0, sh1) -> (Int, Int) Source #

uncheckedSizeOffset :: (sh0, sh1) -> Index (sh0, sh1) -> (Int, Int) Source #

(C sh0, C sh1) => C (sh0 :+: sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (sh0 :+: sh1) :: * Source #

Methods

indices :: (sh0 :+: sh1) -> [Index (sh0 :+: sh1)] Source #

offset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Int Source #

uncheckedOffset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Int Source #

inBounds :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Bool Source #

size :: (sh0 :+: sh1) -> Int Source #

uncheckedSize :: (sh0 :+: sh1) -> Int Source #

sizeOffset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> (Int, Int) Source #

uncheckedSizeOffset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> (Int, Int) Source #

(C sh0, C sh1, C sh2) => C (sh0, sh1, sh2) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (sh0, sh1, sh2) :: * Source #

Methods

indices :: (sh0, sh1, sh2) -> [Index (sh0, sh1, sh2)] Source #

offset :: (sh0, sh1, sh2) -> Index (sh0, sh1, sh2) -> Int Source #

uncheckedOffset :: (sh0, sh1, sh2) -> Index (sh0, sh1, sh2) -> Int Source #

inBounds :: (sh0, sh1, sh2) -> Index (sh0, sh1, sh2) -> Bool Source #

size :: (sh0, sh1, sh2) -> Int Source #

uncheckedSize :: (sh0, sh1, sh2) -> Int Source #

sizeOffset :: (sh0, sh1, sh2) -> Index (sh0, sh1, sh2) -> (Int, Int) Source #

uncheckedSizeOffset :: (sh0, sh1, sh2) -> Index (sh0, sh1, sh2) -> (Int, Int) Source #

newtype ZeroBased n Source #

ZeroBased denotes a range starting at zero and has a certain length.

Constructors

ZeroBased 

Fields

Instances
Eq n => Eq (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: ZeroBased n -> ZeroBased n -> Bool #

(/=) :: ZeroBased n -> ZeroBased n -> Bool #

Show n => Show (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Integral n => C (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (ZeroBased n) :: * Source #

type Index (ZeroBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (ZeroBased n) = n

newtype OneBased n Source #

OneBased denotes a range starting at one and has a certain length.

Constructors

OneBased 

Fields

Instances
Eq n => Eq (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: OneBased n -> OneBased n -> Bool #

(/=) :: OneBased n -> OneBased n -> Bool #

Show n => Show (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> OneBased n -> ShowS #

show :: OneBased n -> String #

showList :: [OneBased n] -> ShowS #

Integral n => C (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (OneBased n) :: * Source #

type Index (OneBased n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (OneBased n) = n

data Range n Source #

Range denotes an inclusive range like those of the Haskell 98 standard Array type from the array package. E.g. the shape type (Range Int32, Range Int64) is equivalent to the ix type (Int32, Int64) for Arrays.

Constructors

Range 

Fields

Instances
Eq n => Eq (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: Range n -> Range n -> Bool #

(/=) :: Range n -> Range n -> Bool #

Show n => Show (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Range n -> ShowS #

show :: Range n -> String #

showList :: [Range n] -> ShowS #

Storable n => Storable (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

sizeOf :: Range n -> Int #

alignment :: Range n -> Int #

peekElemOff :: Ptr (Range n) -> Int -> IO (Range n) #

pokeElemOff :: Ptr (Range n) -> Int -> Range n -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Range n) #

pokeByteOff :: Ptr b -> Int -> Range n -> IO () #

peek :: Ptr (Range n) -> IO (Range n) #

poke :: Ptr (Range n) -> Range n -> IO () #

Ix n => C (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Range n) :: * Source #

type Index (Range n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Range n) = n

data Shifted n Source #

Shifted denotes a range defined by the start index and the length.

Constructors

Shifted 
Instances
Eq n => Eq (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: Shifted n -> Shifted n -> Bool #

(/=) :: Shifted n -> Shifted n -> Bool #

Show n => Show (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> Shifted n -> ShowS #

show :: Shifted n -> String #

showList :: [Shifted n] -> ShowS #

Storable n => Storable (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

sizeOf :: Shifted n -> Int #

alignment :: Shifted n -> Int #

peekElemOff :: Ptr (Shifted n) -> Int -> IO (Shifted n) #

pokeElemOff :: Ptr (Shifted n) -> Int -> Shifted n -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Shifted n) #

pokeByteOff :: Ptr b -> Int -> Shifted n -> IO () #

peek :: Ptr (Shifted n) -> IO (Shifted n) #

poke :: Ptr (Shifted n) -> Shifted n -> IO () #

Integral n => C (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (Shifted n) :: * Source #

type Index (Shifted n) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (Shifted n) = n

data sh0 :+: sh1 infixr 5 Source #

Constructors

sh0 :+: sh1 infixr 5 
Instances
(Eq sh0, Eq sh1) => Eq (sh0 :+: sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

(==) :: (sh0 :+: sh1) -> (sh0 :+: sh1) -> Bool #

(/=) :: (sh0 :+: sh1) -> (sh0 :+: sh1) -> Bool #

(Show sh0, Show sh1) => Show (sh0 :+: sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Methods

showsPrec :: Int -> (sh0 :+: sh1) -> ShowS #

show :: (sh0 :+: sh1) -> String #

showList :: [sh0 :+: sh1] -> ShowS #

(C sh0, C sh1) => C (sh0 :+: sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

Associated Types

type Index (sh0 :+: sh1) :: * Source #

Methods

indices :: (sh0 :+: sh1) -> [Index (sh0 :+: sh1)] Source #

offset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Int Source #

uncheckedOffset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Int Source #

inBounds :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> Bool Source #

size :: (sh0 :+: sh1) -> Int Source #

uncheckedSize :: (sh0 :+: sh1) -> Int Source #

sizeOffset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> (Int, Int) Source #

uncheckedSizeOffset :: (sh0 :+: sh1) -> Index (sh0 :+: sh1) -> (Int, Int) Source #

type Index (sh0 :+: sh1) Source # 
Instance details

Defined in Data.Array.Comfort.Shape

type Index (sh0 :+: sh1) = Either (Index sh0) (Index sh1)