easytensor-1.0.0.1: Pure, type-indexed haskell vector, matrix, and tensor library.

Safe HaskellNone
LanguageHaskell2010

Numeric.DataFrame.Type

Contents

Synopsis

Data types

data family DataFrame (t :: l) (xs :: [k]) Source #

Keep data in a primitive data frame and maintain information about Dimensions in the type system

Instances
Dim3 (DataFrame l2 :: [XNat] -> *) (d1 ': (d2 ': (d3 ': ds)) :: [XNat]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim3 :: DataFrame l2 (d1 ': (d2 ': (d3 ': ds))) -> Dim (Head (Tail (Tail (d1 ': (d2 ': (d3 ': ds)))))) Source #

Dim2 (DataFrame l2 :: [XNat] -> *) (d1 ': (d2 ': ds) :: [XNat]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim2 :: DataFrame l2 (d1 ': (d2 ': ds)) -> Dim (Head (Tail (d1 ': (d2 ': ds)))) Source #

Dim1 (DataFrame l2 :: [XNat] -> *) (d ': ds :: [XNat]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim1 :: DataFrame l2 (d ': ds) -> Dim (Head (d ': ds)) Source #

(PrimArray t (Array t ds), PrimBytes t) => PrimArray t (DataFrame t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

broadcast :: t -> DataFrame t ds Source #

ix# :: Int# -> DataFrame t ds -> t Source #

gen# :: Int# -> (s -> (#s, t#)) -> s -> (#s, DataFrame t ds#) Source #

upd# :: Int# -> Int# -> t -> DataFrame t ds -> DataFrame t ds Source #

elemOffset :: DataFrame t ds -> Int# Source #

elemSize0 :: DataFrame t ds -> Int# Source #

fromElems :: Int# -> Int# -> ByteArray# -> DataFrame t ds Source #

Bounded (Array t ds) => Bounded (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

minBound :: DataFrame t ds #

maxBound :: DataFrame t ds #

Enum (Array t ds) => Enum (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

succ :: DataFrame t ds -> DataFrame t ds #

pred :: DataFrame t ds -> DataFrame t ds #

toEnum :: Int -> DataFrame t ds #

fromEnum :: DataFrame t ds -> Int #

enumFrom :: DataFrame t ds -> [DataFrame t ds] #

enumFromThen :: DataFrame t ds -> DataFrame t ds -> [DataFrame t ds] #

enumFromTo :: DataFrame t ds -> DataFrame t ds -> [DataFrame t ds] #

enumFromThenTo :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds -> [DataFrame t ds] #

ImplAllows Eq ts ds => Eq (DataFrame ts ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

(==) :: DataFrame ts ds -> DataFrame ts ds -> Bool #

(/=) :: DataFrame ts ds -> DataFrame ts ds -> Bool #

Eq (Array t ds) => Eq (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

(==) :: DataFrame t ds -> DataFrame t ds -> Bool #

(/=) :: DataFrame t ds -> DataFrame t ds -> Bool #

(AllTypes Eq t, DataFrameInference t) => Eq (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

(==) :: DataFrame t ds -> DataFrame t ds -> Bool #

(/=) :: DataFrame t ds -> DataFrame t ds -> Bool #

Floating (Array t ds) => Floating (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

pi :: DataFrame t ds #

exp :: DataFrame t ds -> DataFrame t ds #

log :: DataFrame t ds -> DataFrame t ds #

sqrt :: DataFrame t ds -> DataFrame t ds #

(**) :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

logBase :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

sin :: DataFrame t ds -> DataFrame t ds #

cos :: DataFrame t ds -> DataFrame t ds #

tan :: DataFrame t ds -> DataFrame t ds #

asin :: DataFrame t ds -> DataFrame t ds #

acos :: DataFrame t ds -> DataFrame t ds #

atan :: DataFrame t ds -> DataFrame t ds #

sinh :: DataFrame t ds -> DataFrame t ds #

cosh :: DataFrame t ds -> DataFrame t ds #

tanh :: DataFrame t ds -> DataFrame t ds #

asinh :: DataFrame t ds -> DataFrame t ds #

acosh :: DataFrame t ds -> DataFrame t ds #

atanh :: DataFrame t ds -> DataFrame t ds #

log1p :: DataFrame t ds -> DataFrame t ds #

expm1 :: DataFrame t ds -> DataFrame t ds #

log1pexp :: DataFrame t ds -> DataFrame t ds #

log1mexp :: DataFrame t ds -> DataFrame t ds #

Fractional (Array t ds) => Fractional (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

(/) :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

recip :: DataFrame t ds -> DataFrame t ds #

fromRational :: Rational -> DataFrame t ds #

Integral (Array t ds) => Integral (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

quot :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

rem :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

div :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

mod :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

quotRem :: DataFrame t ds -> DataFrame t ds -> (DataFrame t ds, DataFrame t ds) #

divMod :: DataFrame t ds -> DataFrame t ds -> (DataFrame t ds, DataFrame t ds) #

toInteger :: DataFrame t ds -> Integer #

Num (Array t ds) => Num (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

(+) :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

(-) :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

(*) :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

negate :: DataFrame t ds -> DataFrame t ds #

abs :: DataFrame t ds -> DataFrame t ds #

signum :: DataFrame t ds -> DataFrame t ds #

fromInteger :: Integer -> DataFrame t ds #

Ord (Array t ds) => Ord (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

compare :: DataFrame t ds -> DataFrame t ds -> Ordering #

(<) :: DataFrame t ds -> DataFrame t ds -> Bool #

(<=) :: DataFrame t ds -> DataFrame t ds -> Bool #

(>) :: DataFrame t ds -> DataFrame t ds -> Bool #

(>=) :: DataFrame t ds -> DataFrame t ds -> Bool #

max :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

min :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

(Read (Array t ds), Dimensions ds) => Read (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Real (Array t ds) => Real (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

toRational :: DataFrame t ds -> Rational #

RealFloat (Array t ds) => RealFloat (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

RealFrac (Array t ds) => RealFrac (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

properFraction :: Integral b => DataFrame t ds -> (b, DataFrame t ds) #

truncate :: Integral b => DataFrame t ds -> b #

round :: Integral b => DataFrame t ds -> b #

ceiling :: Integral b => DataFrame t ds -> b #

floor :: Integral b => DataFrame t ds -> b #

(Dimensions ds, ImplAllows Show ts ds) => Show (DataFrame ts ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

showsPrec :: Int -> DataFrame ts ds -> ShowS #

show :: DataFrame ts ds -> String #

showList :: [DataFrame ts ds] -> ShowS #

(Show (Array t ds), Dimensions ds) => Show (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

showsPrec :: Int -> DataFrame t ds -> ShowS #

show :: DataFrame t ds -> String #

showList :: [DataFrame t ds] -> ShowS #

(AllTypes Show t, DataFrameInference t) => Show (DataFrame t xns) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

showsPrec :: Int -> DataFrame t xns -> ShowS #

show :: DataFrame t xns -> String #

showList :: [DataFrame t xns] -> ShowS #

PrimBytes (DataFrame t ds) => Storable (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

sizeOf :: DataFrame t ds -> Int #

alignment :: DataFrame t ds -> Int #

peekElemOff :: Ptr (DataFrame t ds) -> Int -> IO (DataFrame t ds) #

pokeElemOff :: Ptr (DataFrame t ds) -> Int -> DataFrame t ds -> IO () #

peekByteOff :: Ptr b -> Int -> IO (DataFrame t ds) #

pokeByteOff :: Ptr b -> Int -> DataFrame t ds -> IO () #

peek :: Ptr (DataFrame t ds) -> IO (DataFrame t ds) #

poke :: Ptr (DataFrame t ds) -> DataFrame t ds -> IO () #

PrimBytes (Array t ds) => PrimBytes (DataFrame t ds) Source # 
Instance details

Defined in Numeric.DataFrame.Type

data DataFrame (t :: Type) (ns :: [Nat]) Source #

Single frame

Instance details

Defined in Numeric.DataFrame.Type

data DataFrame (t :: Type) (ns :: [Nat]) = SingleFrame {}
data DataFrame (ts :: l) (xns :: [XNat]) Source #

Data frame with some dimensions missing at compile time. Pattern-match against its constructor to get a Nat-indexed data frame.

Instance details

Defined in Numeric.DataFrame.Type

data DataFrame (ts :: l) (xns :: [XNat]) where
data DataFrame (ts :: [Type]) (ns :: [Nat]) Source #

Multiple "columns" of data frames of the same shape

Instance details

Defined in Numeric.DataFrame.Type

data DataFrame (ts :: [Type]) (ns :: [Nat]) = MultiFrame {}

data SomeDataFrame (t :: l) Source #

Data frame that has an unknown dimensionality at compile time. Pattern-match against its constructor to get a Nat-indexed data frame

Constructors

(Dimensions ns, ArraySingletons t ns) => SomeDataFrame (DataFrame t ns) 

data DataFrame' (xs :: [k]) (t :: l) Source #

DataFrame with its type arguments swapped.

pattern (:*:) :: forall (xs :: [Type]) (ns :: [Nat]). () => forall (y :: Type) (ys :: [Type]). xs ~ (y ': ys) => DataFrame y ns -> DataFrame ys ns -> DataFrame xs ns infixr 6 Source #

Constructing a MultiFrame using DataFrame columns

pattern Z :: forall (xs :: [Type]) (ns :: [Nat]). () => xs ~ '[] => DataFrame xs ns Source #

Empty MultiFrame

Infer type class instances

type family AllTypes (f :: Type -> Constraint) (ts :: l) :: Constraint where ... Source #

Equations

AllTypes f (t :: Type) = f t 
AllTypes f (ts :: [Type]) = All f ts 

type family ImplAllows (f :: Type -> Constraint) (ts :: l) (ds :: [Nat]) :: Constraint where ... Source #

Equations

ImplAllows f (t :: Type) ds = f (Array t ds) 
ImplAllows _ ('[] :: [Type]) _ = () 
ImplAllows f (t ': ts :: [Type]) ds = (f (Array t ds), ImplAllows f ts ds) 

type family ArraySingletons (ts :: l) (ns :: [Nat]) :: Constraint where ... Source #

Equations

ArraySingletons (t :: Type) ns = ArraySingleton t ns 
ArraySingletons ('[] :: [Type]) _ = () 
ArraySingletons (t ': ts :: [Type]) ns = (ArraySingleton t ns, ArraySingletons ts ns) 

type family PrimFrames (ts :: l) (ns :: [Nat]) :: Constraint where ... Source #

Equations

PrimFrames (t :: Type) ns = (PrimBytes (DataFrame t ns), PrimArray t (DataFrame t ns)) 
PrimFrames ('[] :: [Type]) _ = () 
PrimFrames (t ': ts :: [Type]) ns = (PrimBytes (DataFrame t ns), PrimArray t (DataFrame t ns), PrimFrames ts ns) 

class DataFrameInference (t :: l) where Source #

Minimal complete definition

inferASing, inferEq, inferShow, inferPrim, inferPrimElem

Methods

inferASing :: (AllTypes PrimBytes t, Dimensions ds) => DataFrame t ds -> Evidence (ArraySingletons t ds) Source #

Bring an evidence of ArraySingleton instance into a scope at runtime. This is often used to let GHC infer other complex type class instances, such as SubSpace.

inferEq :: (AllTypes Eq t, ArraySingletons t ds) => DataFrame t ds -> Evidence (Eq (DataFrame t ds)) Source #

inferShow :: (AllTypes Show t, ArraySingletons t ds, Dimensions ds) => DataFrame t ds -> Evidence (Show (DataFrame t ds)) Source #

inferPrim :: (AllTypes PrimBytes t, ArraySingletons t ds, Dimensions ds) => DataFrame t ds -> Evidence (PrimFrames t ds) Source #

inferPrimElem :: (ArraySingletons t ds, ds ~ (Head ds ': Tail ds)) => DataFrame t ds -> Evidence (AllTypes PrimBytes t) Source #

This is a special function, because Scalar does not require PrimBytes. That is why the dimension list in the argument nust not be empty.

inferOrd :: forall t ds. (Ord t, ArraySingleton t ds) => DataFrame t ds -> Evidence (Ord (DataFrame t ds)) Source #

inferNum :: forall t ds. (Num t, ArraySingletons t ds) => DataFrame t ds -> Evidence (Num (DataFrame t ds)) Source #

inferFloating :: forall t ds. (Floating t, ArraySingleton t ds) => DataFrame t ds -> Evidence (Floating (DataFrame t ds)) Source #

inferOrd' :: forall t ds. (Ord t, ArraySingleton t ds) => Evidence (Ord (DataFrame t ds)) Source #

inferNum' :: forall t ds. (Num t, ArraySingletons t ds) => Evidence (Num (DataFrame t ds)) Source #

inferPrimElem' :: forall t ds. (DataFrameInference t, ArraySingletons t ds, ds ~ (Head ds ': Tail ds)) => Evidence (AllTypes PrimBytes t) Source #

Misc

ixOff :: PrimArray t a => Int -> a -> t Source #

Index array by an integer offset (starting from 0).

unsafeFromFlatList :: PrimArray t a => Int -> [t] -> a Source #

Construct an array from a flat list and length

class Dim1 (t :: [k] -> Type) (ds :: [k]) where Source #

Minimal complete definition

dim1

Methods

dim1 :: t ds -> Dim (Head ds) Source #

Instances
Dimensions (d ': ds) => Dim1 (t :: [k] -> Type) (d ': ds :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim1 :: t (d ': ds) -> Dim (Head (d ': ds)) Source #

Dim1 (TypedList (Dim :: k -> *) :: [k] -> *) (d ': ds :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim1 :: TypedList Dim (d ': ds) -> Dim (Head (d ': ds)) Source #

Dim1 (DataFrame l2 :: [XNat] -> *) (d ': ds :: [XNat]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim1 :: DataFrame l2 (d ': ds) -> Dim (Head (d ': ds)) Source #

class Dim2 (t :: [k] -> Type) (ds :: [k]) where Source #

Minimal complete definition

dim2

Methods

dim2 :: t ds -> Dim (Head (Tail ds)) Source #

Instances
Dimensions (d1 ': (d2 ': ds)) => Dim2 (t :: [k] -> Type) (d1 ': (d2 ': ds) :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim2 :: t (d1 ': (d2 ': ds)) -> Dim (Head (Tail (d1 ': (d2 ': ds)))) Source #

Dim2 (TypedList (Dim :: k -> *) :: [k] -> *) (d1 ': (d2 ': ds) :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim2 :: TypedList Dim (d1 ': (d2 ': ds)) -> Dim (Head (Tail (d1 ': (d2 ': ds)))) Source #

Dim2 (DataFrame l2 :: [XNat] -> *) (d1 ': (d2 ': ds) :: [XNat]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim2 :: DataFrame l2 (d1 ': (d2 ': ds)) -> Dim (Head (Tail (d1 ': (d2 ': ds)))) Source #

class Dim3 (t :: [k] -> Type) (ds :: [k]) where Source #

Minimal complete definition

dim3

Methods

dim3 :: t ds -> Dim (Head (Tail (Tail ds))) Source #

Instances
Dimensions (d1 ': (d2 ': (d3 ': ds))) => Dim3 (t :: [k] -> Type) (d1 ': (d2 ': (d3 ': ds)) :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim3 :: t (d1 ': (d2 ': (d3 ': ds))) -> Dim (Head (Tail (Tail (d1 ': (d2 ': (d3 ': ds)))))) Source #

Dim3 (TypedList (Dim :: k -> *) :: [k] -> *) (d1 ': (d2 ': (d3 ': ds)) :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim3 :: TypedList Dim (d1 ': (d2 ': (d3 ': ds))) -> Dim (Head (Tail (Tail (d1 ': (d2 ': (d3 ': ds)))))) Source #

Dim3 (DataFrame l2 :: [XNat] -> *) (d1 ': (d2 ': (d3 ': ds)) :: [XNat]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim3 :: DataFrame l2 (d1 ': (d2 ': (d3 ': ds))) -> Dim (Head (Tail (Tail (d1 ': (d2 ': (d3 ': ds)))))) Source #

dimSize1 :: Dim1 t ds => t ds -> Word Source #

Number of elements along the 1st dimension.

dimSize2 :: Dim2 t ds => t ds -> Word Source #

Number of elements along the 2nd dimension.

dimSize3 :: Dim3 t ds => t ds -> Word Source #

Number of elements along the 3rd dimension.

bSizeOf :: PrimBytes a => a -> Int Source #

A wrapper on byteSize

bAlignOf :: PrimBytes a => a -> Int Source #

A wrapper on byteAlign

Re-exports from dimensions

data Dim (x :: k) :: forall k. k -> * where #

Singleton type to store type-level dimension value.

On the one hand, it can be used to let type-inference system know relations between type-level naturals. On the other hand, this is just a newtype wrapper on the Word type.

Usually, the type parameter of Dim is either Nat or XNat. If dimensionality of your data is known in advance, use Nat; if you know the size of some dimensions, but do not know the size of others, use XNats to represent them.

Bundled Patterns

pattern D :: forall (n :: Nat). () => KnownDim n => Dim n

Same as Dim pattern, but constrained to Nat kind.

pattern Dim :: forall k (n :: k). () => KnownDim n => Dim n

Independently of the kind of type-level number, construct an instance of KnownDim from it.

Match against this pattern to bring KnownDim instance into scope when you don't know the kind of the Dim parameter.

pattern Dx :: forall (xn :: XNat). KnownXNatType xn => forall (n :: Nat) (m :: Nat). (KnownDim n, MinDim m n, xn ~ XN m) => Dim n -> Dim xn

XNat that is unknown at compile time. Same as SomeNat, but for a dimension: Hide dimension size inside, but allow specifying its minimum possible value.

pattern Dn :: forall (xn :: XNat). KnownXNatType xn => forall (n :: Nat). (KnownDim n, xn ~ N n) => Dim n -> Dim xn

Statically known XNat

Instances
Dim3 (TypedList (Dim :: k -> *) :: [k] -> *) (d1 ': (d2 ': (d3 ': ds)) :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim3 :: TypedList Dim (d1 ': (d2 ': (d3 ': ds))) -> Dim (Head (Tail (Tail (d1 ': (d2 ': (d3 ': ds)))))) Source #

Dim2 (TypedList (Dim :: k -> *) :: [k] -> *) (d1 ': (d2 ': ds) :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim2 :: TypedList Dim (d1 ': (d2 ': ds)) -> Dim (Head (Tail (d1 ': (d2 ': ds)))) Source #

Dim1 (TypedList (Dim :: k -> *) :: [k] -> *) (d ': ds :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim1 :: TypedList Dim (d ': ds) -> Dim (Head (d ': ds)) Source #

Eq (Dim n) 
Instance details

Defined in Numeric.Dim

Methods

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

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

Eq (Dim x) 
Instance details

Defined in Numeric.Dim

Methods

(==) :: Dim x -> Dim x -> Bool #

(/=) :: Dim x -> Dim x -> Bool #

Ord (Dim n) 
Instance details

Defined in Numeric.Dim

Methods

compare :: Dim n -> Dim n -> Ordering #

(<) :: Dim n -> Dim n -> Bool #

(<=) :: Dim n -> Dim n -> Bool #

(>) :: Dim n -> Dim n -> Bool #

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

max :: Dim n -> Dim n -> Dim n #

min :: Dim n -> Dim n -> Dim n #

Ord (Dim x) 
Instance details

Defined in Numeric.Dim

Methods

compare :: Dim x -> Dim x -> Ordering #

(<) :: Dim x -> Dim x -> Bool #

(<=) :: Dim x -> Dim x -> Bool #

(>) :: Dim x -> Dim x -> Bool #

(>=) :: Dim x -> Dim x -> Bool #

max :: Dim x -> Dim x -> Dim x #

min :: Dim x -> Dim x -> Dim x #

KnownDim m => Read (Dim (XN m)) 
Instance details

Defined in Numeric.Dim

Methods

readsPrec :: Int -> ReadS (Dim (XN m)) #

readList :: ReadS [Dim (XN m)] #

readPrec :: ReadPrec (Dim (XN m)) #

readListPrec :: ReadPrec [Dim (XN m)] #

Show (Dim x) 
Instance details

Defined in Numeric.Dim

Methods

showsPrec :: Int -> Dim x -> ShowS #

show :: Dim x -> String #

showList :: [Dim x] -> ShowS #

newtype Idx (n :: k) :: forall k. k -> * #

This type is used to index a single dimension; the range of indices is from 1 to n.

Note, this type has a weird Enum instance:

>>> fromEnum (Idx 7)
6

The logic behind this is that the Enum class is used to transform indices to offsets. That is, element of an array at index k :: Idx n is the element taken by an offset `k - 1 :: Int`.

Constructors

Idx 

Fields

Instances
Generic1 (Idx :: k -> *) 
Instance details

Defined in Numeric.Dimensions.Idxs

Associated Types

type Rep1 Idx :: k -> * #

Methods

from1 :: Idx a -> Rep1 Idx a #

to1 :: Rep1 Idx a -> Idx a #

KnownDim n => Bounded (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

minBound :: Idx n #

maxBound :: Idx n #

Dimensions ds => Bounded (Idxs ds) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

minBound :: Idxs ds #

maxBound :: Idxs ds #

KnownDim n => Enum (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

succ :: Idx n -> Idx n #

pred :: Idx n -> Idx n #

toEnum :: Int -> Idx n #

fromEnum :: Idx n -> Int #

enumFrom :: Idx n -> [Idx n] #

enumFromThen :: Idx n -> Idx n -> [Idx n] #

enumFromTo :: Idx n -> Idx n -> [Idx n] #

enumFromThenTo :: Idx n -> Idx n -> Idx n -> [Idx n] #

Dimensions ds => Enum (Idxs ds) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

succ :: Idxs ds -> Idxs ds #

pred :: Idxs ds -> Idxs ds #

toEnum :: Int -> Idxs ds #

fromEnum :: Idxs ds -> Int #

enumFrom :: Idxs ds -> [Idxs ds] #

enumFromThen :: Idxs ds -> Idxs ds -> [Idxs ds] #

enumFromTo :: Idxs ds -> Idxs ds -> [Idxs ds] #

enumFromThenTo :: Idxs ds -> Idxs ds -> Idxs ds -> [Idxs ds] #

Eq (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

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

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

Eq (Idxs xs) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

(==) :: Idxs xs -> Idxs xs -> Bool #

(/=) :: Idxs xs -> Idxs xs -> Bool #

KnownDim n => Integral (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

quot :: Idx n -> Idx n -> Idx n #

rem :: Idx n -> Idx n -> Idx n #

div :: Idx n -> Idx n -> Idx n #

mod :: Idx n -> Idx n -> Idx n #

quotRem :: Idx n -> Idx n -> (Idx n, Idx n) #

divMod :: Idx n -> Idx n -> (Idx n, Idx n) #

toInteger :: Idx n -> Integer #

(Typeable n, Typeable k) => Data (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

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

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

toConstr :: Idx n -> Constr #

dataTypeOf :: Idx n -> DataType #

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

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

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

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

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

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

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

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

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

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

KnownDim n => Num (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

(+) :: Idx n -> Idx n -> Idx n #

(-) :: Idx n -> Idx n -> Idx n #

(*) :: Idx n -> Idx n -> Idx n #

negate :: Idx n -> Idx n #

abs :: Idx n -> Idx n #

signum :: Idx n -> Idx n #

fromInteger :: Integer -> Idx n #

KnownDim n => Num (Idxs (n ': ([] :: [k])))

With this instance we can slightly reduce indexing expressions, e.g.

x ! (1 :* 2 :* 4) == x ! (1 :* 2 :* 4 :* U)
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

(+) :: Idxs (n ': []) -> Idxs (n ': []) -> Idxs (n ': []) #

(-) :: Idxs (n ': []) -> Idxs (n ': []) -> Idxs (n ': []) #

(*) :: Idxs (n ': []) -> Idxs (n ': []) -> Idxs (n ': []) #

negate :: Idxs (n ': []) -> Idxs (n ': []) #

abs :: Idxs (n ': []) -> Idxs (n ': []) #

signum :: Idxs (n ': []) -> Idxs (n ': []) #

fromInteger :: Integer -> Idxs (n ': []) #

Ord (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

compare :: Idx n -> Idx n -> Ordering #

(<) :: Idx n -> Idx n -> Bool #

(<=) :: Idx n -> Idx n -> Bool #

(>) :: Idx n -> Idx n -> Bool #

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

max :: Idx n -> Idx n -> Idx n #

min :: Idx n -> Idx n -> Idx n #

Ord (Idxs xs)

Compare indices by their importance in lexicorgaphic order from the last dimension to the first dimension (the last dimension is the most significant one) O(Length xs).

Literally,

compare a b = compare (reverse $ listIdxs a) (reverse $ listIdxs b)

This is the same compare rule, as for Dims. Another reason to reverse the list of indices is to have a consistent behavior when calculating index offsets:

sort == sortOn fromEnum
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

compare :: Idxs xs -> Idxs xs -> Ordering #

(<) :: Idxs xs -> Idxs xs -> Bool #

(<=) :: Idxs xs -> Idxs xs -> Bool #

(>) :: Idxs xs -> Idxs xs -> Bool #

(>=) :: Idxs xs -> Idxs xs -> Bool #

max :: Idxs xs -> Idxs xs -> Idxs xs #

min :: Idxs xs -> Idxs xs -> Idxs xs #

Read (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

KnownDim n => Real (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

toRational :: Idx n -> Rational #

Show (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

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

show :: Idx n -> String #

showList :: [Idx n] -> ShowS #

Show (Idxs xs) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

showsPrec :: Int -> Idxs xs -> ShowS #

show :: Idxs xs -> String #

showList :: [Idxs xs] -> ShowS #

Generic (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

Associated Types

type Rep (Idx n) :: * -> * #

Methods

from :: Idx n -> Rep (Idx n) x #

to :: Rep (Idx n) x -> Idx n #

Storable (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

sizeOf :: Idx n -> Int #

alignment :: Idx n -> Int #

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

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

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

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

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

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

PrimBytes (Idx x) Source # 
Instance details

Defined in Numeric.PrimBytes

RepresentableList xs => PrimBytes (Idxs xs) Source # 
Instance details

Defined in Numeric.PrimBytes

type Rep1 (Idx :: k -> *) 
Instance details

Defined in Numeric.Dimensions.Idxs

type Rep1 (Idx :: k -> *) = D1 (MetaData "Idx" "Numeric.Dimensions.Idxs" "dimensions-1.0.0.0-7nZRipxyum32WQEEFVJq6D" True) (C1 (MetaCons "Idx" PrefixI True) (S1 (MetaSel (Just "unIdx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)))
type Rep (Idx n) 
Instance details

Defined in Numeric.Dimensions.Idxs

type Rep (Idx n) = D1 (MetaData "Idx" "Numeric.Dimensions.Idxs" "dimensions-1.0.0.0-7nZRipxyum32WQEEFVJq6D" True) (C1 (MetaCons "Idx" PrefixI True) (S1 (MetaSel (Just "unIdx") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word)))

data XNat #

Either known or unknown at compile-time natural number

Constructors

XN Nat 
N Nat 
Instances
KnownDimKind XNat 
Instance details

Defined in Numeric.Dim

Methods

dimKind :: DimKind XNat #

DataFrameToList t (xns :: [XNat]) (xz :: XNat) Source # 
Instance details

Defined in Numeric.DataFrame.Shape

Methods

toList :: DataFrame t (xns +: xz) -> [DataFrame t xns] Source #

MatrixTranspose (t :: Type) (xn :: XNat) (xm :: XNat) Source # 
Instance details

Defined in Numeric.Matrix

Methods

transpose :: Matrix t xn xm -> Matrix t xm xn Source #

KnownDim n => KnownDim (N n :: XNat) 
Instance details

Defined in Numeric.Dim

Methods

dim :: Dim (N n) #

Dim3 (DataFrame l2 :: [XNat] -> *) (d1 ': (d2 ': (d3 ': ds)) :: [XNat]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim3 :: DataFrame l2 (d1 ': (d2 ': (d3 ': ds))) -> Dim (Head (Tail (Tail (d1 ': (d2 ': (d3 ': ds)))))) Source #

Dim2 (DataFrame l2 :: [XNat] -> *) (d1 ': (d2 ': ds) :: [XNat]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim2 :: DataFrame l2 (d1 ': (d2 ': ds)) -> Dim (Head (Tail (d1 ': (d2 ': ds)))) Source #

Dim1 (DataFrame l2 :: [XNat] -> *) (d ': ds :: [XNat]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim1 :: DataFrame l2 (d ': ds) -> Dim (Head (d ': ds)) Source #

Eq (Dim x) 
Instance details

Defined in Numeric.Dim

Methods

(==) :: Dim x -> Dim x -> Bool #

(/=) :: Dim x -> Dim x -> Bool #

Ord (Dim x) 
Instance details

Defined in Numeric.Dim

Methods

compare :: Dim x -> Dim x -> Ordering #

(<) :: Dim x -> Dim x -> Bool #

(<=) :: Dim x -> Dim x -> Bool #

(>) :: Dim x -> Dim x -> Bool #

(>=) :: Dim x -> Dim x -> Bool #

max :: Dim x -> Dim x -> Dim x #

min :: Dim x -> Dim x -> Dim x #

KnownDim m => Read (Dim (XN m)) 
Instance details

Defined in Numeric.Dim

Methods

readsPrec :: Int -> ReadS (Dim (XN m)) #

readList :: ReadS [Dim (XN m)] #

readPrec :: ReadPrec (Dim (XN m)) #

readListPrec :: ReadPrec [Dim (XN m)] #

(AllTypes Eq t, DataFrameInference t) => Eq (DataFrame t ds) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

(==) :: DataFrame t ds -> DataFrame t ds -> Bool #

(/=) :: DataFrame t ds -> DataFrame t ds -> Bool #

(AllTypes Show t, DataFrameInference t) => Show (DataFrame t xns) # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

showsPrec :: Int -> DataFrame t xns -> ShowS #

show :: DataFrame t xns -> String #

showList :: [DataFrame t xns] -> ShowS #

data STDataFrame s t (xs :: [XNat]) Source #

Data frame with some dimensions missing at compile time. Pattern-match against its constructor to get a Nat-indexed mutable data frame.

Instance details

Defined in Numeric.DataFrame.ST

data STDataFrame s t (xs :: [XNat]) where
data IODataFrame t (xs :: [XNat]) Source #

Data frame with some dimensions missing at compile time. Pattern-match against its constructor to get a Nat-indexed mutable data frame.

Instance details

Defined in Numeric.DataFrame.IO

data IODataFrame t (xs :: [XNat]) where
data DataFrame (ts :: l) (xns :: [XNat]) Source #

Data frame with some dimensions missing at compile time. Pattern-match against its constructor to get a Nat-indexed data frame.

Instance details

Defined in Numeric.DataFrame.Type

data DataFrame (ts :: l) (xns :: [XNat]) where

type Dims (xs :: [k]) = TypedList (Dim :: k -> *) xs #

Type-level dimensionality O(1).

type Idxs (xs :: [k]) = TypedList (Idx :: k -> *) xs #

Type-level dimensional indexing with arbitrary Word values inside. Most of the operations on it require Dimensions constraint, because the Idxs itself does not store info about dimension bounds.

Note, this type has a special Enum instance: fromEnum gives an offset of the index in a flat 1D array; this is in line with a weird Enum instance of Idx type.

data TypedList (f :: k -> Type) (xs :: [k]) :: forall k. (k -> Type) -> [k] -> * where #

Type-indexed list

Bundled Patterns

pattern Empty :: forall k (f :: k -> Type) (xs :: [k]). () => xs ~ ([] :: [k]) => TypedList f xs

Zero-length type list; synonym to U.

pattern Reverse :: forall k (f :: k -> Type) (xs :: [k]). () => forall (sx :: [k]). (xs ~ Reverse sx, sx ~ Reverse xs) => TypedList f sx -> TypedList f xs

Reverse a typed list

pattern Snoc :: forall k (f :: k -> Type) (xs :: [k]). () => forall (sy :: [k]) (y :: k). xs ~ (sy +: y) => TypedList f sy -> f y -> TypedList f xs

Constructing a type-indexed list from the other end

pattern Cons :: forall k (f :: k -> Type) (xs :: [k]). () => forall (y :: k) (ys :: [k]). xs ~ (y ': ys) => f y -> TypedList f ys -> TypedList f xs

Constructing a type-indexed list in the canonical way

pattern TypeList :: forall k (xs :: [k]). () => RepresentableList xs => TypeList xs

Pattern matching against this causes RepresentableList instance come into scope. Also it allows constructing a term-level list out of a constraint.

pattern (:*) :: forall k (f :: k -> Type) (xs :: [k]). () => forall (y :: k) (ys :: [k]). xs ~ (y ': ys) => f y -> TypedList f ys -> TypedList f xs infixr 5

Constructing a type-indexed list

pattern U :: forall k (f :: k -> Type) (xs :: [k]). () => xs ~ ([] :: [k]) => TypedList f xs

Zero-length type list

pattern AsXDims :: forall (ns :: [Nat]). () => (KnownXNatTypes (AsXDims ns), RepresentableList (AsXDims ns)) => Dims (AsXDims ns) -> Dims ns

An easy way to convert Nat-indexed dims into XNat-indexed dims.

pattern Dims :: forall k (ds :: [k]). () => Dimensions ds => Dims ds

O(1) Pattern-matching against this constructor brings a Dimensions instance into the scope. Thus, you can do arbitrary operations on your dims and use this pattern at any time to reconstruct the class instance at runtime.

pattern XDims :: forall (xns :: [XNat]). KnownXNatTypes xns => forall (ns :: [Nat]). (FixedDims xns ns, Dimensions ns) => Dims ns -> Dims xns

Pattern-matching against this constructor reveals Nat-kinded list of dims, pretending the dimensionality is known at compile time within the scope of the pattern match. This is the main recommended way to get Dims at runtime; for example, reading a list of dimensions from a file.

In order to use this pattern, one must know XNat type constructors in each dimension at compile time.

pattern KnownDims :: forall k (ds :: [k]). () => (All (KnownDim :: k -> Constraint) ds, Dimensions ds) => Dims ds

O(Length ds) Dimensions and KnownDim for each individual dimension.

Instances
Dim3 (TypedList (Dim :: k -> *) :: [k] -> *) (d1 ': (d2 ': (d3 ': ds)) :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim3 :: TypedList Dim (d1 ': (d2 ': (d3 ': ds))) -> Dim (Head (Tail (Tail (d1 ': (d2 ': (d3 ': ds)))))) Source #

Dim2 (TypedList (Dim :: k -> *) :: [k] -> *) (d1 ': (d2 ': ds) :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim2 :: TypedList Dim (d1 ': (d2 ': ds)) -> Dim (Head (Tail (d1 ': (d2 ': ds)))) Source #

Dim1 (TypedList (Dim :: k -> *) :: [k] -> *) (d ': ds :: [k]) Source # 
Instance details

Defined in Numeric.DataFrame.Type

Methods

dim1 :: TypedList Dim (d ': ds) -> Dim (Head (d ': ds)) Source #

(RepresentableList xs, All Bounded xs) => Bounded (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

minBound :: Tuple xs #

maxBound :: Tuple xs #

(RepresentableList xs, All Bounded xs) => Bounded (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Strict

Methods

minBound :: Tuple xs #

maxBound :: Tuple xs #

All Eq xs => Eq (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

(==) :: Tuple xs -> Tuple xs -> Bool #

(/=) :: Tuple xs -> Tuple xs -> Bool #

All Eq xs => Eq (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Strict

Methods

(==) :: Tuple xs -> Tuple xs -> Bool #

(/=) :: Tuple xs -> Tuple xs -> Bool #

(All Eq xs, All Ord xs) => Ord (Tuple xs)

Ord instance of the Tuple implements inverse lexicorgaphic ordering. That is, the last element in the tuple is the most significant one.

Note, this will never work on infinite-dimensional tuples!

Instance details

Defined in Numeric.Tuple.Lazy

Methods

compare :: Tuple xs -> Tuple xs -> Ordering #

(<) :: Tuple xs -> Tuple xs -> Bool #

(<=) :: Tuple xs -> Tuple xs -> Bool #

(>) :: Tuple xs -> Tuple xs -> Bool #

(>=) :: Tuple xs -> Tuple xs -> Bool #

max :: Tuple xs -> Tuple xs -> Tuple xs #

min :: Tuple xs -> Tuple xs -> Tuple xs #

(All Eq xs, All Ord xs) => Ord (Tuple xs)

Ord instance of the Tuple implements inverse lexicorgaphic ordering. That is, the last element in the tuple is the most significant one.

Note, this will never work on infinite-dimensional tuples!

Instance details

Defined in Numeric.Tuple.Strict

Methods

compare :: Tuple xs -> Tuple xs -> Ordering #

(<) :: Tuple xs -> Tuple xs -> Bool #

(<=) :: Tuple xs -> Tuple xs -> Bool #

(>) :: Tuple xs -> Tuple xs -> Bool #

(>=) :: Tuple xs -> Tuple xs -> Bool #

max :: Tuple xs -> Tuple xs -> Tuple xs #

min :: Tuple xs -> Tuple xs -> Tuple xs #

(RepresentableList xs, All Read xs) => Read (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Lazy

(RepresentableList xs, All Read xs) => Read (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Strict

All Show xs => Show (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

showsPrec :: Int -> Tuple xs -> ShowS #

show :: Tuple xs -> String #

showList :: [Tuple xs] -> ShowS #

All Show xs => Show (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Strict

Methods

showsPrec :: Int -> Tuple xs -> ShowS #

show :: Tuple xs -> String #

showList :: [Tuple xs] -> ShowS #

All Semigroup xs => Semigroup (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

(<>) :: Tuple xs -> Tuple xs -> Tuple xs #

sconcat :: NonEmpty (Tuple xs) -> Tuple xs #

stimes :: Integral b => b -> Tuple xs -> Tuple xs #

All Semigroup xs => Semigroup (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Strict

Methods

(<>) :: Tuple xs -> Tuple xs -> Tuple xs #

sconcat :: NonEmpty (Tuple xs) -> Tuple xs #

stimes :: Integral b => b -> Tuple xs -> Tuple xs #

(Semigroup (Tuple xs), RepresentableList xs, All Monoid xs) => Monoid (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

mempty :: Tuple xs #

mappend :: Tuple xs -> Tuple xs -> Tuple xs #

mconcat :: [Tuple xs] -> Tuple xs #

(Semigroup (Tuple xs), RepresentableList xs, All Monoid xs) => Monoid (Tuple xs) 
Instance details

Defined in Numeric.Tuple.Strict

Methods

mempty :: Tuple xs #

mappend :: Tuple xs -> Tuple xs -> Tuple xs #

mconcat :: [Tuple xs] -> Tuple xs #

(RepresentableList xs, All PrimBytes xs) => PrimBytes (Tuple xs) Source # 
Instance details

Defined in Numeric.PrimBytes

(RepresentableList xs, All PrimBytes xs) => PrimBytes (Tuple xs) Source # 
Instance details

Defined in Numeric.PrimBytes

Dimensions ds => Bounded (Idxs ds) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

minBound :: Idxs ds #

maxBound :: Idxs ds #

Dimensions ds => Enum (Idxs ds) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

succ :: Idxs ds -> Idxs ds #

pred :: Idxs ds -> Idxs ds #

toEnum :: Int -> Idxs ds #

fromEnum :: Idxs ds -> Int #

enumFrom :: Idxs ds -> [Idxs ds] #

enumFromThen :: Idxs ds -> Idxs ds -> [Idxs ds] #

enumFromTo :: Idxs ds -> Idxs ds -> [Idxs ds] #

enumFromThenTo :: Idxs ds -> Idxs ds -> Idxs ds -> [Idxs ds] #

Eq (Idxs xs) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

(==) :: Idxs xs -> Idxs xs -> Bool #

(/=) :: Idxs xs -> Idxs xs -> Bool #

KnownDim n => Num (Idxs (n ': ([] :: [k])))

With this instance we can slightly reduce indexing expressions, e.g.

x ! (1 :* 2 :* 4) == x ! (1 :* 2 :* 4 :* U)
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

(+) :: Idxs (n ': []) -> Idxs (n ': []) -> Idxs (n ': []) #

(-) :: Idxs (n ': []) -> Idxs (n ': []) -> Idxs (n ': []) #

(*) :: Idxs (n ': []) -> Idxs (n ': []) -> Idxs (n ': []) #

negate :: Idxs (n ': []) -> Idxs (n ': []) #

abs :: Idxs (n ': []) -> Idxs (n ': []) #

signum :: Idxs (n ': []) -> Idxs (n ': []) #

fromInteger :: Integer -> Idxs (n ': []) #

Ord (Idxs xs)

Compare indices by their importance in lexicorgaphic order from the last dimension to the first dimension (the last dimension is the most significant one) O(Length xs).

Literally,

compare a b = compare (reverse $ listIdxs a) (reverse $ listIdxs b)

This is the same compare rule, as for Dims. Another reason to reverse the list of indices is to have a consistent behavior when calculating index offsets:

sort == sortOn fromEnum
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

compare :: Idxs xs -> Idxs xs -> Ordering #

(<) :: Idxs xs -> Idxs xs -> Bool #

(<=) :: Idxs xs -> Idxs xs -> Bool #

(>) :: Idxs xs -> Idxs xs -> Bool #

(>=) :: Idxs xs -> Idxs xs -> Bool #

max :: Idxs xs -> Idxs xs -> Idxs xs #

min :: Idxs xs -> Idxs xs -> Idxs xs #

Show (Idxs xs) 
Instance details

Defined in Numeric.Dimensions.Idxs

Methods

showsPrec :: Int -> Idxs xs -> ShowS #

show :: Idxs xs -> String #

showList :: [Idxs xs] -> ShowS #

RepresentableList xs => PrimBytes (Idxs xs) Source # 
Instance details

Defined in Numeric.PrimBytes

Orphan instances

(PrimArray t (Array t ds), PrimBytes t) => PrimArray t (DataFrame t ds) Source # 
Instance details

Methods

broadcast :: t -> DataFrame t ds Source #

ix# :: Int# -> DataFrame t ds -> t Source #

gen# :: Int# -> (s -> (#s, t#)) -> s -> (#s, DataFrame t ds#) Source #

upd# :: Int# -> Int# -> t -> DataFrame t ds -> DataFrame t ds Source #

elemOffset :: DataFrame t ds -> Int# Source #

elemSize0 :: DataFrame t ds -> Int# Source #

fromElems :: Int# -> Int# -> ByteArray# -> DataFrame t ds Source #

Bounded (Array t ds) => Bounded (DataFrame t ds) Source # 
Instance details

Methods

minBound :: DataFrame t ds #

maxBound :: DataFrame t ds #

Enum (Array t ds) => Enum (DataFrame t ds) Source # 
Instance details

Methods

succ :: DataFrame t ds -> DataFrame t ds #

pred :: DataFrame t ds -> DataFrame t ds #

toEnum :: Int -> DataFrame t ds #

fromEnum :: DataFrame t ds -> Int #

enumFrom :: DataFrame t ds -> [DataFrame t ds] #

enumFromThen :: DataFrame t ds -> DataFrame t ds -> [DataFrame t ds] #

enumFromTo :: DataFrame t ds -> DataFrame t ds -> [DataFrame t ds] #

enumFromThenTo :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds -> [DataFrame t ds] #

ImplAllows Eq ts ds => Eq (DataFrame ts ds) Source # 
Instance details

Methods

(==) :: DataFrame ts ds -> DataFrame ts ds -> Bool #

(/=) :: DataFrame ts ds -> DataFrame ts ds -> Bool #

Eq (Array t ds) => Eq (DataFrame t ds) Source # 
Instance details

Methods

(==) :: DataFrame t ds -> DataFrame t ds -> Bool #

(/=) :: DataFrame t ds -> DataFrame t ds -> Bool #

(AllTypes Eq t, DataFrameInference t) => Eq (DataFrame t ds) Source # 
Instance details

Methods

(==) :: DataFrame t ds -> DataFrame t ds -> Bool #

(/=) :: DataFrame t ds -> DataFrame t ds -> Bool #

Floating (Array t ds) => Floating (DataFrame t ds) Source # 
Instance details

Methods

pi :: DataFrame t ds #

exp :: DataFrame t ds -> DataFrame t ds #

log :: DataFrame t ds -> DataFrame t ds #

sqrt :: DataFrame t ds -> DataFrame t ds #

(**) :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

logBase :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

sin :: DataFrame t ds -> DataFrame t ds #

cos :: DataFrame t ds -> DataFrame t ds #

tan :: DataFrame t ds -> DataFrame t ds #

asin :: DataFrame t ds -> DataFrame t ds #

acos :: DataFrame t ds -> DataFrame t ds #

atan :: DataFrame t ds -> DataFrame t ds #

sinh :: DataFrame t ds -> DataFrame t ds #

cosh :: DataFrame t ds -> DataFrame t ds #

tanh :: DataFrame t ds -> DataFrame t ds #

asinh :: DataFrame t ds -> DataFrame t ds #

acosh :: DataFrame t ds -> DataFrame t ds #

atanh :: DataFrame t ds -> DataFrame t ds #

log1p :: DataFrame t ds -> DataFrame t ds #

expm1 :: DataFrame t ds -> DataFrame t ds #

log1pexp :: DataFrame t ds -> DataFrame t ds #

log1mexp :: DataFrame t ds -> DataFrame t ds #

Fractional (Array t ds) => Fractional (DataFrame t ds) Source # 
Instance details

Methods

(/) :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

recip :: DataFrame t ds -> DataFrame t ds #

fromRational :: Rational -> DataFrame t ds #

Integral (Array t ds) => Integral (DataFrame t ds) Source # 
Instance details

Methods

quot :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

rem :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

div :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

mod :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

quotRem :: DataFrame t ds -> DataFrame t ds -> (DataFrame t ds, DataFrame t ds) #

divMod :: DataFrame t ds -> DataFrame t ds -> (DataFrame t ds, DataFrame t ds) #

toInteger :: DataFrame t ds -> Integer #

Num (Array t ds) => Num (DataFrame t ds) Source # 
Instance details

Methods

(+) :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

(-) :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

(*) :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

negate :: DataFrame t ds -> DataFrame t ds #

abs :: DataFrame t ds -> DataFrame t ds #

signum :: DataFrame t ds -> DataFrame t ds #

fromInteger :: Integer -> DataFrame t ds #

Ord (Array t ds) => Ord (DataFrame t ds) Source # 
Instance details

Methods

compare :: DataFrame t ds -> DataFrame t ds -> Ordering #

(<) :: DataFrame t ds -> DataFrame t ds -> Bool #

(<=) :: DataFrame t ds -> DataFrame t ds -> Bool #

(>) :: DataFrame t ds -> DataFrame t ds -> Bool #

(>=) :: DataFrame t ds -> DataFrame t ds -> Bool #

max :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

min :: DataFrame t ds -> DataFrame t ds -> DataFrame t ds #

(Read (Array t ds), Dimensions ds) => Read (DataFrame t ds) Source # 
Instance details

Real (Array t ds) => Real (DataFrame t ds) Source # 
Instance details

Methods

toRational :: DataFrame t ds -> Rational #

RealFloat (Array t ds) => RealFloat (DataFrame t ds) Source # 
Instance details

RealFrac (Array t ds) => RealFrac (DataFrame t ds) Source # 
Instance details

Methods

properFraction :: Integral b => DataFrame t ds -> (b, DataFrame t ds) #

truncate :: Integral b => DataFrame t ds -> b #

round :: Integral b => DataFrame t ds -> b #

ceiling :: Integral b => DataFrame t ds -> b #

floor :: Integral b => DataFrame t ds -> b #

(Dimensions ds, ImplAllows Show ts ds) => Show (DataFrame ts ds) Source # 
Instance details

Methods

showsPrec :: Int -> DataFrame ts ds -> ShowS #

show :: DataFrame ts ds -> String #

showList :: [DataFrame ts ds] -> ShowS #

(Show (Array t ds), Dimensions ds) => Show (DataFrame t ds) Source # 
Instance details

Methods

showsPrec :: Int -> DataFrame t ds -> ShowS #

show :: DataFrame t ds -> String #

showList :: [DataFrame t ds] -> ShowS #

(AllTypes Show t, DataFrameInference t) => Show (DataFrame t xns) Source # 
Instance details

Methods

showsPrec :: Int -> DataFrame t xns -> ShowS #

show :: DataFrame t xns -> String #

showList :: [DataFrame t xns] -> ShowS #

PrimBytes (DataFrame t ds) => Storable (DataFrame t ds) Source # 
Instance details

Methods

sizeOf :: DataFrame t ds -> Int #

alignment :: DataFrame t ds -> Int #

peekElemOff :: Ptr (DataFrame t ds) -> Int -> IO (DataFrame t ds) #

pokeElemOff :: Ptr (DataFrame t ds) -> Int -> DataFrame t ds -> IO () #

peekByteOff :: Ptr b -> Int -> IO (DataFrame t ds) #

pokeByteOff :: Ptr b -> Int -> DataFrame t ds -> IO () #

peek :: Ptr (DataFrame t ds) -> IO (DataFrame t ds) #

poke :: Ptr (DataFrame t ds) -> DataFrame t ds -> IO () #

PrimBytes (Array t ds) => PrimBytes (DataFrame t ds) Source # 
Instance details