dimensions-2.0.0.0: Safe type-level dimensionality for multidimensional data.

Copyright(c) Artem Chirkin
LicenseBSD3
Safe HaskellNone
LanguageHaskell2010

Numeric.Tuple.Lazy

Description

 
Synopsis

Documentation

newtype Id a Source #

This is an almost complete copy of Identity by (c) Andy Gill 2001.

Constructors

Id 

Fields

Instances
Monad Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

(>>=) :: Id a -> (a -> Id b) -> Id b #

(>>) :: Id a -> Id b -> Id b #

return :: a -> Id a #

fail :: String -> Id a #

Functor Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

fmap :: (a -> b) -> Id a -> Id b #

(<$) :: a -> Id b -> Id a #

MonadFix Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

mfix :: (a -> Id a) -> Id a #

Applicative Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

pure :: a -> Id a #

(<*>) :: Id (a -> b) -> Id a -> Id b #

liftA2 :: (a -> b -> c) -> Id a -> Id b -> Id c #

(*>) :: Id a -> Id b -> Id b #

(<*) :: Id a -> Id b -> Id a #

Foldable Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

fold :: Monoid m => Id m -> m #

foldMap :: Monoid m => (a -> m) -> Id a -> m #

foldr :: (a -> b -> b) -> b -> Id a -> b #

foldr' :: (a -> b -> b) -> b -> Id a -> b #

foldl :: (b -> a -> b) -> b -> Id a -> b #

foldl' :: (b -> a -> b) -> b -> Id a -> b #

foldr1 :: (a -> a -> a) -> Id a -> a #

foldl1 :: (a -> a -> a) -> Id a -> a #

toList :: Id a -> [a] #

null :: Id a -> Bool #

length :: Id a -> Int #

elem :: Eq a => a -> Id a -> Bool #

maximum :: Ord a => Id a -> a #

minimum :: Ord a => Id a -> a #

sum :: Num a => Id a -> a #

product :: Num a => Id a -> a #

Traversable Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

traverse :: Applicative f => (a -> f b) -> Id a -> f (Id b) #

sequenceA :: Applicative f => Id (f a) -> f (Id a) #

mapM :: Monad m => (a -> m b) -> Id a -> m (Id b) #

sequence :: Monad m => Id (m a) -> m (Id a) #

Eq1 Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

liftEq :: (a -> b -> Bool) -> Id a -> Id b -> Bool #

Ord1 Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

liftCompare :: (a -> b -> Ordering) -> Id a -> Id b -> Ordering #

Read1 Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Id a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [Id a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (Id a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [Id a] #

Show1 Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Id a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [Id a] -> ShowS #

MonadZip Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

mzip :: Id a -> Id b -> Id (a, b) #

mzipWith :: (a -> b -> c) -> Id a -> Id b -> Id c #

munzip :: Id (a, b) -> (Id a, Id b) #

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

Defined in Numeric.Tuple.Lazy

Methods

minBound :: Tuple xs #

maxBound :: Tuple xs #

Bounded a => Bounded (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

minBound :: Id a #

maxBound :: Id a #

Enum a => Enum (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

succ :: Id a -> Id a #

pred :: Id a -> Id a #

toEnum :: Int -> Id a #

fromEnum :: Id a -> Int #

enumFrom :: Id a -> [Id a] #

enumFromThen :: Id a -> Id a -> [Id a] #

enumFromTo :: Id a -> Id a -> [Id a] #

enumFromThenTo :: Id a -> Id a -> Id a -> [Id a] #

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

Defined in Numeric.Tuple.Lazy

Methods

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

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

Eq a => Eq (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

(==) :: Id a -> Id a -> Bool #

(/=) :: Id a -> Id a -> Bool #

Floating a => Floating (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

pi :: Id a #

exp :: Id a -> Id a #

log :: Id a -> Id a #

sqrt :: Id a -> Id a #

(**) :: Id a -> Id a -> Id a #

logBase :: Id a -> Id a -> Id a #

sin :: Id a -> Id a #

cos :: Id a -> Id a #

tan :: Id a -> Id a #

asin :: Id a -> Id a #

acos :: Id a -> Id a #

atan :: Id a -> Id a #

sinh :: Id a -> Id a #

cosh :: Id a -> Id a #

tanh :: Id a -> Id a #

asinh :: Id a -> Id a #

acosh :: Id a -> Id a #

atanh :: Id a -> Id a #

log1p :: Id a -> Id a #

expm1 :: Id a -> Id a #

log1pexp :: Id a -> Id a #

log1mexp :: Id a -> Id a #

Fractional a => Fractional (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

(/) :: Id a -> Id a -> Id a #

recip :: Id a -> Id a #

fromRational :: Rational -> Id a #

Integral a => Integral (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

quot :: Id a -> Id a -> Id a #

rem :: Id a -> Id a -> Id a #

div :: Id a -> Id a -> Id a #

mod :: Id a -> Id a -> Id a #

quotRem :: Id a -> Id a -> (Id a, Id a) #

divMod :: Id a -> Id a -> (Id a, Id a) #

toInteger :: Id a -> Integer #

Data a => Data (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Id a -> c (Id a) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Id a) #

toConstr :: Id a -> Constr #

dataTypeOf :: Id a -> DataType #

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

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

gmapT :: (forall b. Data b => b -> b) -> Id a -> Id a #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Id a -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Id a -> r #

gmapQ :: (forall d. Data d => d -> u) -> Id a -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Id a -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Id a -> m (Id a) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Id a -> m (Id a) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Id a -> m (Id a) #

Num a => Num (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

(+) :: Id a -> Id a -> Id a #

(-) :: Id a -> Id a -> Id a #

(*) :: Id a -> Id a -> Id a #

negate :: Id a -> Id a #

abs :: Id a -> Id a #

signum :: Id a -> Id a #

fromInteger :: Integer -> Id a #

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

Lexicorgaphic ordering; same as normal Haskell lists.

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 #

Ord a => Ord (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

compare :: Id a -> Id a -> Ordering #

(<) :: Id a -> Id a -> Bool #

(<=) :: Id a -> Id a -> Bool #

(>) :: Id a -> Id a -> Bool #

(>=) :: Id a -> Id a -> Bool #

max :: Id a -> Id a -> Id a #

min :: Id a -> Id a -> Id a #

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

Defined in Numeric.Tuple.Lazy

Read a => Read (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Real a => Real (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

toRational :: Id a -> Rational #

RealFloat a => RealFloat (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

floatRadix :: Id a -> Integer #

floatDigits :: Id a -> Int #

floatRange :: Id a -> (Int, Int) #

decodeFloat :: Id a -> (Integer, Int) #

encodeFloat :: Integer -> Int -> Id a #

exponent :: Id a -> Int #

significand :: Id a -> Id a #

scaleFloat :: Int -> Id a -> Id a #

isNaN :: Id a -> Bool #

isInfinite :: Id a -> Bool #

isDenormalized :: Id a -> Bool #

isNegativeZero :: Id a -> Bool #

isIEEE :: Id a -> Bool #

atan2 :: Id a -> Id a -> Id a #

RealFrac a => RealFrac (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

properFraction :: Integral b => Id a -> (b, Id a) #

truncate :: Integral b => Id a -> b #

round :: Integral b => Id a -> b #

ceiling :: Integral b => Id a -> b #

floor :: Integral b => Id a -> b #

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

Defined in Numeric.Tuple.Lazy

Methods

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

show :: Tuple xs -> String #

showList :: [Tuple xs] -> ShowS #

Show a => Show (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

showsPrec :: Int -> Id a -> ShowS #

show :: Id a -> String #

showList :: [Id a] -> ShowS #

Ix a => Ix (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

range :: (Id a, Id a) -> [Id a] #

index :: (Id a, Id a) -> Id a -> Int #

unsafeIndex :: (Id a, Id a) -> Id a -> Int

inRange :: (Id a, Id a) -> Id a -> Bool #

rangeSize :: (Id a, Id a) -> Int #

unsafeRangeSize :: (Id a, Id a) -> Int

IsString a => IsString (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

fromString :: String -> Id a #

Generic (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Associated Types

type Rep (Id a) :: Type -> Type #

Methods

from :: Id a -> Rep (Id a) x #

to :: Rep (Id a) x -> Id a #

All Semigroup xs => Semigroup (Tuple xs) Source # 
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 #

Semigroup a => Semigroup (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

(<>) :: Id a -> Id a -> Id a #

sconcat :: NonEmpty (Id a) -> Id a #

stimes :: Integral b => b -> Id a -> Id a #

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

Defined in Numeric.Tuple.Lazy

Methods

mempty :: Tuple xs #

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

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

Monoid a => Monoid (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

mempty :: Id a #

mappend :: Id a -> Id a -> Id a #

mconcat :: [Id a] -> Id a #

Storable a => Storable (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

sizeOf :: Id a -> Int #

alignment :: Id a -> Int #

peekElemOff :: Ptr (Id a) -> Int -> IO (Id a) #

pokeElemOff :: Ptr (Id a) -> Int -> Id a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (Id a) #

pokeByteOff :: Ptr b -> Int -> Id a -> IO () #

peek :: Ptr (Id a) -> IO (Id a) #

poke :: Ptr (Id a) -> Id a -> IO () #

Bits a => Bits (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

(.&.) :: Id a -> Id a -> Id a #

(.|.) :: Id a -> Id a -> Id a #

xor :: Id a -> Id a -> Id a #

complement :: Id a -> Id a #

shift :: Id a -> Int -> Id a #

rotate :: Id a -> Int -> Id a #

zeroBits :: Id a #

bit :: Int -> Id a #

setBit :: Id a -> Int -> Id a #

clearBit :: Id a -> Int -> Id a #

complementBit :: Id a -> Int -> Id a #

testBit :: Id a -> Int -> Bool #

bitSizeMaybe :: Id a -> Maybe Int #

bitSize :: Id a -> Int #

isSigned :: Id a -> Bool #

shiftL :: Id a -> Int -> Id a #

unsafeShiftL :: Id a -> Int -> Id a #

shiftR :: Id a -> Int -> Id a #

unsafeShiftR :: Id a -> Int -> Id a #

rotateL :: Id a -> Int -> Id a #

rotateR :: Id a -> Int -> Id a #

popCount :: Id a -> Int #

FiniteBits a => FiniteBits (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Generic1 Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Associated Types

type Rep1 Id :: k -> Type #

Methods

from1 :: Id a -> Rep1 Id a #

to1 :: Rep1 Id a -> Id a #

type Rep (Id a) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

type Rep (Id a) = D1 (MetaData "Id" "Numeric.Tuple.Lazy" "dimensions-2.0.0.0-E3TodFh6CxsCRM2bfCokxE" True) (C1 (MetaCons "Id" PrefixI True) (S1 (MetaSel (Just "runId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Rep1 Id Source # 
Instance details

Defined in Numeric.Tuple.Lazy

type Rep1 Id = D1 (MetaData "Id" "Numeric.Tuple.Lazy" "dimensions-2.0.0.0-E3TodFh6CxsCRM2bfCokxE" True) (C1 (MetaCons "Id" PrefixI True) (S1 (MetaSel (Just "runId") NoSourceUnpackedness NoSourceStrictness DecidedLazy) Par1))

type Tuple (xs :: [Type]) = TypedList Id xs Source #

A tuple indexed by a list of types

data TypedList (f :: k -> Type) (xs :: [k]) where Source #

Type-indexed list

Bundled Patterns

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

Zero-length type list

pattern (:*) :: forall (k :: Type) (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 (:$) :: forall (xs :: [Type]). () => forall (y :: Type) (ys :: [Type]). xs ~ (y ': ys) => y -> Tuple ys -> Tuple xs infixr 5

Constructing a type-indexed list

pattern (:!) :: forall (xs :: [Type]). () => forall (y :: Type) (ys :: [Type]). xs ~ (y ': ys) => y -> Tuple ys -> Tuple xs infixr 5

Constructing a type-indexed list

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

Zero-length type list; synonym to U.

pattern TypeList :: forall (k :: Type) (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 Cons :: forall (k :: Type) (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 Snoc :: forall (k :: Type) (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 Reverse :: forall (k :: Type) (f :: k -> Type) (xs :: [k]). () => forall (sx :: [k]). (xs ~ Reverse sx, sx ~ Reverse xs) => TypedList f sx -> TypedList f xs

Reverse a typed list

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

Defined in Numeric.Tuple.Strict

Methods

minBound :: Tuple xs #

maxBound :: Tuple xs #

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

Defined in Numeric.Tuple.Lazy

Methods

minBound :: Tuple xs #

maxBound :: Tuple xs #

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

Defined in Numeric.Tuple.Strict

Methods

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

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

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

Defined in Numeric.Tuple.Lazy

Methods

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

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

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

Lexicorgaphic ordering; same as normal Haskell lists.

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 #

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

Lexicorgaphic ordering; same as normal Haskell lists.

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 Read xs, RepresentableList xs) => Read (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Strict

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

Defined in Numeric.Tuple.Lazy

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

Defined in Numeric.Tuple.Strict

Methods

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

show :: Tuple xs -> String #

showList :: [Tuple xs] -> ShowS #

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

Defined in Numeric.Tuple.Lazy

Methods

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

show :: Tuple xs -> String #

showList :: [Tuple xs] -> ShowS #

All Semigroup xs => Semigroup (Tuple xs) Source # 
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 #

All Semigroup xs => Semigroup (Tuple xs) Source # 
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 #

(RepresentableList xs, All Semigroup xs, All Monoid xs) => Monoid (Tuple xs) Source # 
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 Semigroup xs, All Monoid xs) => Monoid (Tuple xs) Source # 
Instance details

Defined in Numeric.Tuple.Lazy

Methods

mempty :: Tuple xs #

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

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

BoundedDims ds => Bounded (Idxs ds) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

minBound :: Idxs ds #

maxBound :: Idxs ds #

Dimensions ds => Enum (Idxs ds) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

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 (Dims ds) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

Methods

(==) :: Dims ds -> Dims ds -> Bool #

(/=) :: Dims ds -> Dims ds -> Bool #

Eq (Dims ds) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

Methods

(==) :: Dims ds -> Dims ds -> Bool #

(/=) :: Dims ds -> Dims ds -> Bool #

Eq (Idxs xs) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

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

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

BoundedDim n => Num (Idxs (n ': ([] :: [k]))) Source #

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.Idx

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 (Dims ds) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

Methods

compare :: Dims ds -> Dims ds -> Ordering #

(<) :: Dims ds -> Dims ds -> Bool #

(<=) :: Dims ds -> Dims ds -> Bool #

(>) :: Dims ds -> Dims ds -> Bool #

(>=) :: Dims ds -> Dims ds -> Bool #

max :: Dims ds -> Dims ds -> Dims ds #

min :: Dims ds -> Dims ds -> Dims ds #

Ord (Dims ds) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

Methods

compare :: Dims ds -> Dims ds -> Ordering #

(<) :: Dims ds -> Dims ds -> Bool #

(<=) :: Dims ds -> Dims ds -> Bool #

(>) :: Dims ds -> Dims ds -> Bool #

(>=) :: Dims ds -> Dims ds -> Bool #

max :: Dims ds -> Dims ds -> Dims ds #

min :: Dims ds -> Dims ds -> Dims ds #

Ord (Idxs xs) Source #

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

Literally,

compare a b = compare (listIdxs a) (listIdxs b)

This is the same compare rule, as for Dims. This is also consistent with offsets:

sort == sortOn fromEnum
Instance details

Defined in Numeric.Dimensions.Idx

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 #

BoundedDims xs => Read (Dims xs) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

BoundedDims xs => Read (Idxs xs) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Show (Dims xs) Source # 
Instance details

Defined in Numeric.Dimensions.Dim

Methods

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

show :: Dims xs -> String #

showList :: [Dims xs] -> ShowS #

Show (Idxs xs) Source # 
Instance details

Defined in Numeric.Dimensions.Idx

Methods

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

show :: Idxs xs -> String #

showList :: [Idxs xs] -> ShowS #

(Typeable k, Typeable f, Typeable xs, All Data (Map f xs)) => Data (TypedList f xs) Source #

Term-level structure of a TypedList f xs is fully determined by its type Typeable xs. Thus, gunfold does not use its last argument (Constr) at all, relying on the structure of the type parameter.

Instance details

Defined in Numeric.TypedList

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TypedList f xs -> c (TypedList f xs) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TypedList f xs) #

toConstr :: TypedList f xs -> Constr #

dataTypeOf :: TypedList f xs -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (TypedList f xs)) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TypedList f xs)) #

gmapT :: (forall b. Data b => b -> b) -> TypedList f xs -> TypedList f xs #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TypedList f xs -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TypedList f xs -> r #

gmapQ :: (forall d. Data d => d -> u) -> TypedList f xs -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TypedList f xs -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TypedList f xs -> m (TypedList f xs) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TypedList f xs -> m (TypedList f xs) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TypedList f xs -> m (TypedList f xs) #

Generic (TypedList f xs) Source # 
Instance details

Defined in Numeric.TypedList

Associated Types

type Rep (TypedList f xs) :: Type -> Type #

Methods

from :: TypedList f xs -> Rep (TypedList f xs) x #

to :: Rep (TypedList f xs) x -> TypedList f xs #

type Rep (TypedList f xs) Source # 
Instance details

Defined in Numeric.TypedList

type Rep (TypedList f xs)

(*$) :: x -> Tuple xs -> Tuple (x :+ xs) infixr 5 Source #

Grow a tuple on the left O(1).

($*) :: Tuple xs -> x -> Tuple (xs +: x) infixl 5 Source #

Grow a tuple on the right. Note, it traverses an element list inside O(n).

(*!) :: x -> Tuple xs -> Tuple (x :+ xs) infixr 5 Source #

Grow a tuple on the left while evaluating arguments to WHNF O(1).

(!*) :: Tuple xs -> x -> Tuple (xs +: x) infixl 5 Source #

Grow a tuple on the right while evaluating arguments to WHNF. Note, it traverses an element list inside O(n).