safe-tensor-0.2.1.0: Dependently typed tensor algebra
Copyright(c) Nils Alex 2020
LicenseMIT
Maintainernils.alex@fau.de
Safe HaskellNone
LanguageHaskell2010

Math.Tensor.Safe

Description

Dependently typed implementation of the Einstein tensor calculus, primarily used in mathematical physics. For usage examples, see https://github.com/nilsalex/safe-tensor/#readme.

Synopsis

Tensor calculus

Given a field \(K\) and a \(K\)-vector space \(V\) of dimension \(n\), a tensor \(T\) of rank \((r,s)\) is a multilinear map from \(r\) copies of the dual vector space \(V^\ast\) and \(s\) copies of \(V\) to \(K\),

\[ T \colon \underbrace{V^\ast \times \dots \times V^\ast}_{r\text{ times}} \times \underbrace{V \times \dots \times V}_{s\text{ times}} \rightarrow K. \]

The components \(T^{a_1\dots a_r}_{\hphantom{a_1\dots a_r}b_1\dots b_s} \in K\) with respect to a basis \((e_i)_{i=1\dots n}\) of \(V\) and a corresponding dual basis \((\epsilon^i)_{i=1\dots n}\) of \(V^\ast\) are the \(n^{r+s}\) numbers

\[ T^{a_1\dots a_r}_{\hphantom{a_1\dots a_r}b_1\dots b_s} = T(\epsilon^{a_1},\dots,\epsilon^{a_r},e_{b_1},\dots,e_{b_s}). \]

The upper indices \(a_i\) are called contravariant and the lower indices \(b_i\) are called covariant, reflecting their behaviour under a change of basis. From the components and the basis, the tensor can be reconstructed as

\[ T = T^{a_1\dots a_r}_{\hphantom{a_1\dots a_3}b_1\dots b_s} \cdot e_{a_1} \otimes \dots \otimes e_{a_r} \otimes \epsilon^{b_1} \otimes \dots \otimes \epsilon^{b_s} \]

using the Einstein summation convention and the tensor product.

The representation of tensors using their components with respect to a fixed but arbitrary basis forms the foundation of this tensor calculus. An example is the sum of a \((2,0)\) tensor \(T\) and the transposition of a \((2,0)\) tensor \(S\), which using the calculus can be written as

\[ \lbrack T + \operatorname{transpose}(S)\rbrack^{a b} = T^{a b} + S^{b a}. \]

The generalized rank of the tensor \(T^{a b}\) in the above example is the set of contravariant indices \(\{a, b\}\). The indices must be distinct. The generalized rank of a tensor with both contravariant and covariant indices (e.g. \(T^{ac}_{\hphantom{ac}rbl}\)) is the set of contravariant and the set of covariant indices (e.g. \((\{a,c\}, \{b,l,r\})\)). Note that both sets need not be distinct, as they label completely different entities (basis vectors vs. dual basis vectors). Overlapping indices can be removed by performing a contraction, see also contract.

Tensors with generalized rank can be understood as a graded algebra where only tensors of the same generalized rank can be added together and the tensor product of two tensors yields a tensor with new generalized rank. Importantly, this product is only possible if both the contravariant indices and the covariant indices of the factors do not overlap. As an example, the generalized rank of the tensor product \(T^{ap}_{\hphantom{ap}fc} S^{eg}_{\hphantom{eg}p}\) would be \((\{a,e,g,p\},\{c,f,p\})\).

We take this abstraction one step further and consider tensors that are multilinear maps over potentially different vector spaces and duals thereof. The generalized rank now consists of the contra- and covariant index sets for each distinct vector space. Upon multiplication of tensors, only the indices for each vector space must be distinct and contraction only removes overlapping indices among the same vector space.

Practical examples of configurations with multiple vector spaces are situations where both the tangent space to spacetime, \(V = T_pM\), and symmetric tensors \(S^2(V) \subset V\otimes V\), which form a proper subset of \(V\otimes V\), are considered simultaneously. See also Math.Tensor.Basic.Sym2.

Generalized rank

The tensor calculus described above is now implemented in Haskell. Using Template Haskell provided by the singletons library, this code is lifted to the type level and singletons are generated.

A vector space is parameterised by a label a and a dimension b.

data VSpace a b Source #

Constructors

VSpace 

Fields

Instances

Instances details
NFData a => NFData1 (VSpace a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

liftRnf :: (a0 -> ()) -> VSpace a a0 -> () #

Generic1 (VSpace a :: Type -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Rep1 (VSpace a) :: k -> Type #

Methods

from1 :: forall (a0 :: k). VSpace a a0 -> Rep1 (VSpace a) a0 #

to1 :: forall (a0 :: k). Rep1 (VSpace a) a0 -> VSpace a a0 #

(Eq a, Eq b) => Eq (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(==) :: VSpace a b -> VSpace a b -> Bool #

(/=) :: VSpace a b -> VSpace a b -> Bool #

(Ord a, Ord b) => Ord (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

compare :: VSpace a b -> VSpace a b -> Ordering #

(<) :: VSpace a b -> VSpace a b -> Bool #

(<=) :: VSpace a b -> VSpace a b -> Bool #

(>) :: VSpace a b -> VSpace a b -> Bool #

(>=) :: VSpace a b -> VSpace a b -> Bool #

max :: VSpace a b -> VSpace a b -> VSpace a b #

min :: VSpace a b -> VSpace a b -> VSpace a b #

(Show a, Show b) => Show (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

showsPrec :: Int -> VSpace a b -> ShowS #

show :: VSpace a b -> String #

showList :: [VSpace a b] -> ShowS #

Generic (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Rep (VSpace a b) :: Type -> Type #

Methods

from :: VSpace a b -> Rep (VSpace a b) x #

to :: Rep (VSpace a b) x -> VSpace a b #

(NFData a, NFData b) => NFData (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

rnf :: VSpace a b -> () #

PShow (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

(SShow a, SShow b) => SShow (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sShowsPrec :: forall (t1 :: Nat) (t2 :: VSpace a b) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: VSpace a b). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [VSpace a b]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

POrd (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

(SOrd a, SOrd b) => SOrd (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sCompare :: forall (t1 :: VSpace a b) (t2 :: VSpace a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: forall (t1 :: VSpace a b) (t2 :: VSpace a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: forall (t1 :: VSpace a b) (t2 :: VSpace a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: forall (t1 :: VSpace a b) (t2 :: VSpace a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: forall (t1 :: VSpace a b) (t2 :: VSpace a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: forall (t1 :: VSpace a b) (t2 :: VSpace a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

sMin :: forall (t1 :: VSpace a b) (t2 :: VSpace a b). Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) #

(SEq a, SEq b) => SEq (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(%==) :: forall (a0 :: VSpace a b) (b0 :: VSpace a b). Sing a0 -> Sing b0 -> Sing (a0 == b0) #

(%/=) :: forall (a0 :: VSpace a b) (b0 :: VSpace a b). Sing a0 -> Sing b0 -> Sing (a0 /= b0) #

PEq (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

(SDecide a, SDecide b) => SDecide (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(%~) :: forall (a0 :: VSpace a b) (b0 :: VSpace a b). Sing a0 -> Sing b0 -> Decision (a0 :~: b0) #

(SingKind a, SingKind b) => SingKind (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Demote (VSpace a b) = (r :: Type) #

Methods

fromSing :: forall (a0 :: VSpace a b). Sing a0 -> Demote (VSpace a b) #

toSing :: Demote (VSpace a b) -> SomeSing (VSpace a b) #

SuppressUnusedWarnings DeltaRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings EpsilonRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings EpsilonInvRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI DeltaRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI EpsilonRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI EpsilonInvRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (DeltaRankSym1 a6989586621679574034 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym1 a6989586621679573955 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym1 a6989586621679573932 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym1 a6989586621679573916 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym1 a6989586621679573890 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (EpsilonRankSym1 a6989586621679574013 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (EpsilonInvRankSym1 a6989586621679573993 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym1 a6989586621679573855 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym1 a6989586621679573829 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym1 a6989586621679573803 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym1 a6989586621679573777 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (DeltaRankSym1 d :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym1 d) #

SingI d => SingI (InjSym2ConRankSym1 d :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (InjSym2CovRankSym1 d :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (SurjSym2ConRankSym1 d :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (SurjSym2CovRankSym1 d :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (EpsilonRankSym1 d :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonRankSym1 d) #

SingI d => SingI (EpsilonInvRankSym1 d :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (InjAreaConRankSym1 d :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (InjAreaCovRankSym1 d :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (SurjAreaConRankSym1 d :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (SurjAreaCovRankSym1 d :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

(SDecide a, SDecide b) => TestCoercion (SVSpace :: VSpace a b -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testCoercion :: forall (a0 :: k) (b0 :: k). SVSpace a0 -> SVSpace b0 -> Maybe (Coercion a0 b0) #

(SDecide a, SDecide b) => TestEquality (SVSpace :: VSpace a b -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testEquality :: forall (a0 :: k) (b0 :: k). SVSpace a0 -> SVSpace b0 -> Maybe (a0 :~: b0) #

SuppressUnusedWarnings (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679117751Sym0 :: TyFun Nat (VSpace a b ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (DeltaRankSym2 a6989586621679574034 a6989586621679574035 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym2 a6989586621679573955 a6989586621679573956 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym2 a6989586621679573932 a6989586621679573933 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym2 a6989586621679573916 a6989586621679573917 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym2 a6989586621679573890 a6989586621679573891 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym2 a6989586621679573855 a6989586621679573856 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym2 a6989586621679573829 a6989586621679573830 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym2 a6989586621679573803 a6989586621679573804 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym2 a6989586621679573777 a6989586621679573778 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym0 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (VDimSym0 :: TyFun (VSpace a b) b -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (VIdSym0 :: TyFun (VSpace a b) a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679117768Sym0 :: TyFun (VSpace a b) (VSpace a b ~> Ordering) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (VSpaceSym0 :: TyFun a (b ~> VSpace a b) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573965RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573942RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (EpsilonRankSym2 a6989586621679574013 a6989586621679574014 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (EpsilonInvRankSym2 a6989586621679573993 a6989586621679573994 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SOrd s => SingI (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing MergeRSym0 #

SOrd s => SingI (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing TailRSym0 #

SOrd s => SingI (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing HeadRSym0 #

(SOrd a, SOrd b) => SingI (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing SaneSym0 #

SingI (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SingI d1, SingI d2) => SingI (DeltaRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (InjSym2ConRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2ConRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (InjSym2CovRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2CovRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (SurjSym2ConRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2ConRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (SurjSym2CovRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2CovRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (InjAreaConRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (InjAreaCovRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (SurjAreaConRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (SurjAreaCovRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym2 d1 d2) #

(SOrd s, SOrd n) => SingI (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (CanTransposeCovSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (VIdSym0 :: TyFun (VSpace a b) a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing VIdSym0 #

SingI (VDimSym0 :: TyFun (VSpace a b) b -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing VDimSym0 #

SOrd s => SingI (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (VSpaceSym0 :: TyFun a (b ~> VSpace a b) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing VSpaceSym0 #

(SingI d1, SingI d2) => SingI (EpsilonRankSym2 d1 d2 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (EpsilonInvRankSym2 d1 d2 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonInvRankSym2 d1 d2) #

SuppressUnusedWarnings (MergeRSym1 a6989586621679113791 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RemoveUntilSym1 a6989586621679113432 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573965RSym1 vid6989586621679573960 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573942RSym1 vid6989586621679573937 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (DeltaRankSym3 a6989586621679574034 a6989586621679574035 a6989586621679574036 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym3 a6989586621679573955 a6989586621679573956 a6989586621679573957 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym3 a6989586621679573932 a6989586621679573933 a6989586621679573934 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym3 a6989586621679573916 a6989586621679573917 a6989586621679573918 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym3 a6989586621679573890 a6989586621679573891 a6989586621679573892 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym3 a6989586621679573855 a6989586621679573856 a6989586621679573857 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym3 a6989586621679573829 a6989586621679573830 a6989586621679573831 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym3 a6989586621679573803 a6989586621679573804 a6989586621679573805 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym3 a6989586621679573777 a6989586621679573778 a6989586621679573779 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679117751Sym1 a6989586621679117759 :: TyFun (VSpace a b) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679117768Sym1 a6989586621679117773 :: TyFun (VSpace a b) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym1 a6989586621679113455 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113436GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym1 xv6989586621679113795 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym1 a6989586621679113407 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (VSpaceSym1 a6989586621679112978 :: TyFun b (VSpace a b) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeConSym1 a6989586621679113537 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym1 a6989586621679113482 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym1 vid6989586621679573783 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym1 vid6989586621679573809 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym1 vid6989586621679573835 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym1 vid6989586621679573861 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (RelabelRSym1 a6989586621679113156 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SingI d) => SingI (RemoveUntilSym1 d :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RemoveUntilSym1 d) #

(SOrd s, SOrd n, SingI d) => SingI (MergeRSym1 d :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (MergeRSym1 d) #

(SingI d1, SingI d2, SingI d3) => SingI (DeltaRankSym3 d1 d2 d3 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (InjSym2ConRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2ConRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (InjSym2CovRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2CovRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (SurjSym2ConRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2ConRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (SurjSym2CovRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2CovRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (InjAreaConRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (InjAreaCovRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (SurjAreaConRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (SurjAreaCovRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym3 d1 d2 d3) #

(SOrd s, SOrd n, SingI d) => SingI (CanTransposeCovSym1 d :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d) => SingI (CanTransposeConSym1 d :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d) => SingI (CanTransposeSym1 d :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym1 d) #

(SOrd s, SOrd n, SingI d) => SingI (TranspositionsSym1 d :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d) => SingI (CanTransposeMultSym1 d :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI d => SingI (VSpaceSym1 d :: TyFun b (VSpace a b) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (VSpaceSym1 d) #

(SOrd s, SOrd n, SingI d) => SingI (RelabelRSym1 d :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelRSym1 d) #

SuppressUnusedWarnings (Lambda_6989586621679113805Sym2 xv6989586621679113795 xl6989586621679113796 :: TyFun [(VSpace s n, IList s)] (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelRSym2 a6989586621679113156 a6989586621679113157 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym2 a6989586621679113361 a6989586621679113362 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym2 a6989586621679113407 a6989586621679113408 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjSym2ConRankSym4 a6989586621679573955 a6989586621679573956 a6989586621679573957 a6989586621679573958 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym4 a6989586621679573932 a6989586621679573933 a6989586621679573934 a6989586621679573935 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym4 a6989586621679573916 a6989586621679573917 a6989586621679573918 a6989586621679573919 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym4 a6989586621679573890 a6989586621679573891 a6989586621679573892 a6989586621679573893 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym4 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym4 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym4 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym4 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (CanTransposeSym2 a6989586621679113455 a6989586621679113456 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeConSym2 a6989586621679113537 a6989586621679113538 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym2 a6989586621679113482 a6989586621679113483 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym2 vid6989586621679573783 a6989586621679573784 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym2 vid6989586621679573809 a6989586621679573810 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym2 vid6989586621679573835 a6989586621679573836 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym2 vid6989586621679573861 a6989586621679573862 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573965RSym2 vid6989586621679573960 vdim6989586621679573961 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573942RSym2 vid6989586621679573937 vdim6989586621679573938 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

(SingI n1, SingI n2) => SingI ('VSpace n1 n2 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('VSpace n1 n2) #

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (RelabelRSym2 d1 d2 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelRSym2 d1 d2) #

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (TranspositionsSym2 d1 d2 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TranspositionsSym2 d1 d2) #

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (CanTransposeMultSym2 d1 d2 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeMultSym2 d1 d2) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (InjSym2ConRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2ConRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (InjSym2CovRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2CovRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (SurjSym2ConRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2ConRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (SurjSym2CovRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2CovRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (InjAreaConRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (InjAreaCovRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (SurjAreaConRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (SurjAreaCovRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym4 d1 d2 d3 d4) #

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (CanTransposeCovSym2 d1 d2 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeCovSym2 d1 d2) #

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (CanTransposeConSym2 d1 d2 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeConSym2 d1 d2) #

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (CanTransposeSym2 d1 d2 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym2 d1 d2) #

SuppressUnusedWarnings (CanTransposeConSym3 a6989586621679113537 a6989586621679113538 a6989586621679113539 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym3 a6989586621679113482 a6989586621679113483 a6989586621679113484 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym3 a6989586621679113455 a6989586621679113456 a6989586621679113457 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjAreaConRankSym5 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 a6989586621679573859 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym5 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 a6989586621679573833 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym5 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 a6989586621679573807 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym5 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 a6989586621679573781 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym3 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym3 vid6989586621679573783 a6989586621679573784 b6989586621679573785 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym3 vid6989586621679573809 a6989586621679573810 b6989586621679573811 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym3 vid6989586621679573835 a6989586621679573836 b6989586621679573837 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym3 vid6989586621679573861 a6989586621679573862 b6989586621679573863 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573965RSym3 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573942RSym3 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

(SOrd s, SOrd n, SingI d1, SingI d2, SingI d3) => SingI (CanTransposeSym3 d1 d2 d3 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym3 d1 d2 d3) #

(SOrd s, SOrd n, SingI d1, SingI d2, SingI d3) => SingI (CanTransposeCovSym3 d1 d2 d3 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeCovSym3 d1 d2 d3) #

(SOrd s, SOrd n, SingI d1, SingI d2, SingI d3) => SingI (CanTransposeConSym3 d1 d2 d3 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeConSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3, SingI d4, SingI d5) => SingI (InjAreaConRankSym5 d1 d2 d3 d4 d5 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym5 d1 d2 d3 d4 d5) #

(SingI d1, SingI d2, SingI d3, SingI d4, SingI d5) => SingI (InjAreaCovRankSym5 d1 d2 d3 d4 d5 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym5 d1 d2 d3 d4 d5) #

(SingI d1, SingI d2, SingI d3, SingI d4, SingI d5) => SingI (SurjAreaConRankSym5 d1 d2 d3 d4 d5 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym5 d1 d2 d3 d4 d5) #

(SingI d1, SingI d2, SingI d3, SingI d4, SingI d5) => SingI (SurjAreaCovRankSym5 d1 d2 d3 d4 d5 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym5 d1 d2 d3 d4 d5) #

SuppressUnusedWarnings (Let6989586621679113436GoSym3 i6989586621679113434 r6989586621679113435 a6989586621679113437 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym4 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym4 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym4 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym4 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym4 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573965RSym4 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 b6989586621679573963 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573942RSym4 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 b6989586621679573940 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym5 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym5 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 d6989586621679573787 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym5 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 d6989586621679573813 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym5 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 d6989586621679573839 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym5 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 d6989586621679573865 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym6 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 ys6989586621679113800 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (DeltaRankSym3 a6989586621679574034 a6989586621679574035 a6989586621679574036 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679574037 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym3 a6989586621679574034 a6989586621679574035 a6989586621679574036 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679574037 :: Symbol) = DeltaRankSym4 a6989586621679574034 a6989586621679574035 a6989586621679574036 a6989586621679574037
type Apply (InjSym2ConRankSym4 a6989586621679573955 a6989586621679573956 a6989586621679573957 a6989586621679573958 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573959 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym4 a6989586621679573955 a6989586621679573956 a6989586621679573957 a6989586621679573958 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573959 :: Symbol) = InjSym2ConRankSym5 a6989586621679573955 a6989586621679573956 a6989586621679573957 a6989586621679573958 a6989586621679573959
type Apply (InjSym2CovRankSym4 a6989586621679573932 a6989586621679573933 a6989586621679573934 a6989586621679573935 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573936 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym4 a6989586621679573932 a6989586621679573933 a6989586621679573934 a6989586621679573935 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573936 :: Symbol) = InjSym2CovRankSym5 a6989586621679573932 a6989586621679573933 a6989586621679573934 a6989586621679573935 a6989586621679573936
type Apply (SurjSym2ConRankSym4 a6989586621679573916 a6989586621679573917 a6989586621679573918 a6989586621679573919 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573920 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym4 a6989586621679573916 a6989586621679573917 a6989586621679573918 a6989586621679573919 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573920 :: Symbol) = SurjSym2ConRankSym5 a6989586621679573916 a6989586621679573917 a6989586621679573918 a6989586621679573919 a6989586621679573920
type Apply (SurjSym2CovRankSym4 a6989586621679573890 a6989586621679573891 a6989586621679573892 a6989586621679573893 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573894 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym4 a6989586621679573890 a6989586621679573891 a6989586621679573892 a6989586621679573893 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573894 :: Symbol) = SurjSym2CovRankSym5 a6989586621679573890 a6989586621679573891 a6989586621679573892 a6989586621679573893 a6989586621679573894
type Apply (InjAreaConRankSym5 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 a6989586621679573859 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573860 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym5 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 a6989586621679573859 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573860 :: Symbol) = InjAreaConRankSym6 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 a6989586621679573859 a6989586621679573860
type Apply (InjAreaCovRankSym5 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 a6989586621679573833 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573834 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym5 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 a6989586621679573833 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573834 :: Symbol) = InjAreaCovRankSym6 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 a6989586621679573833 a6989586621679573834
type Apply (SurjAreaConRankSym5 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 a6989586621679573807 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573808 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym5 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 a6989586621679573807 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573808 :: Symbol) = SurjAreaConRankSym6 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 a6989586621679573807 a6989586621679573808
type Apply (SurjAreaCovRankSym5 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 a6989586621679573781 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573782 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym5 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 a6989586621679573781 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573782 :: Symbol) = SurjAreaCovRankSym6 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 a6989586621679573781 a6989586621679573782
type Apply (Let6989586621679573965RSym4 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 b6989586621679573963 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573964 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573965RSym4 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 b6989586621679573963 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573964 :: a) = Let6989586621679573965RSym5 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 b6989586621679573963 i6989586621679573964
type Apply (Let6989586621679573942RSym4 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 b6989586621679573940 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573941 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573942RSym4 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 b6989586621679573940 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573941 :: a) = Let6989586621679573942RSym5 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 b6989586621679573940 i6989586621679573941
type Apply (Let6989586621679573789RSym5 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 d6989586621679573787 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573788 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym5 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 d6989586621679573787 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573788 :: a) = Let6989586621679573789RSym6 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 d6989586621679573787 i6989586621679573788
type Apply (Let6989586621679573815RSym5 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 d6989586621679573813 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573814 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym5 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 d6989586621679573813 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573814 :: a) = Let6989586621679573815RSym6 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 d6989586621679573813 i6989586621679573814
type Apply (Let6989586621679573841RSym5 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 d6989586621679573839 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573840 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym5 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 d6989586621679573839 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573840 :: a) = Let6989586621679573841RSym6 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 d6989586621679573839 i6989586621679573840
type Apply (Let6989586621679573867RSym5 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 d6989586621679573865 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573866 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym5 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 d6989586621679573865 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573866 :: a) = Let6989586621679573867RSym6 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 d6989586621679573865 i6989586621679573866
type Apply DeltaRankSym0 (a6989586621679574034 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply DeltaRankSym0 (a6989586621679574034 :: Symbol) = DeltaRankSym1 a6989586621679574034
type Apply InjSym2ConRankSym0 (a6989586621679573955 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2ConRankSym0 (a6989586621679573955 :: Symbol) = InjSym2ConRankSym1 a6989586621679573955
type Apply InjSym2CovRankSym0 (a6989586621679573932 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2CovRankSym0 (a6989586621679573932 :: Symbol) = InjSym2CovRankSym1 a6989586621679573932
type Apply SurjSym2ConRankSym0 (a6989586621679573916 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2ConRankSym0 (a6989586621679573916 :: Symbol) = SurjSym2ConRankSym1 a6989586621679573916
type Apply SurjSym2CovRankSym0 (a6989586621679573890 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2CovRankSym0 (a6989586621679573890 :: Symbol) = SurjSym2CovRankSym1 a6989586621679573890
type Apply EpsilonRankSym0 (a6989586621679574013 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonRankSym0 (a6989586621679574013 :: Symbol) = EpsilonRankSym1 a6989586621679574013
type Apply EpsilonInvRankSym0 (a6989586621679573993 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonInvRankSym0 (a6989586621679573993 :: Symbol) = EpsilonInvRankSym1 a6989586621679573993
type Apply InjAreaConRankSym0 (a6989586621679573855 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaConRankSym0 (a6989586621679573855 :: Symbol) = InjAreaConRankSym1 a6989586621679573855
type Apply InjAreaCovRankSym0 (a6989586621679573829 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaCovRankSym0 (a6989586621679573829 :: Symbol) = InjAreaCovRankSym1 a6989586621679573829
type Apply SurjAreaConRankSym0 (a6989586621679573803 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjAreaConRankSym0 (a6989586621679573803 :: Symbol) = SurjAreaConRankSym1 a6989586621679573803
type Apply SurjAreaCovRankSym0 (a6989586621679573777 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjAreaCovRankSym0 (a6989586621679573777 :: Symbol) = SurjAreaCovRankSym1 a6989586621679573777
type Apply (DeltaRankSym1 a6989586621679574034 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679574035 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym1 a6989586621679574034 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679574035 :: Nat) = DeltaRankSym2 a6989586621679574034 a6989586621679574035
type Apply (InjSym2ConRankSym1 a6989586621679573955 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573956 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym1 a6989586621679573955 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573956 :: Nat) = InjSym2ConRankSym2 a6989586621679573955 a6989586621679573956
type Apply (InjSym2CovRankSym1 a6989586621679573932 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573933 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym1 a6989586621679573932 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573933 :: Nat) = InjSym2CovRankSym2 a6989586621679573932 a6989586621679573933
type Apply (SurjSym2ConRankSym1 a6989586621679573916 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573917 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym1 a6989586621679573916 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573917 :: Nat) = SurjSym2ConRankSym2 a6989586621679573916 a6989586621679573917
type Apply (SurjSym2CovRankSym1 a6989586621679573890 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573891 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym1 a6989586621679573890 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573891 :: Nat) = SurjSym2CovRankSym2 a6989586621679573890 a6989586621679573891
type Apply (EpsilonRankSym1 a6989586621679574013 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574014 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym1 a6989586621679574013 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574014 :: Nat) = EpsilonRankSym2 a6989586621679574013 a6989586621679574014
type Apply (EpsilonInvRankSym1 a6989586621679573993 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573994 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym1 a6989586621679573993 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573994 :: Nat) = EpsilonInvRankSym2 a6989586621679573993 a6989586621679573994
type Apply (InjAreaConRankSym1 a6989586621679573855 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573856 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym1 a6989586621679573855 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573856 :: Symbol) = InjAreaConRankSym2 a6989586621679573855 a6989586621679573856
type Apply (InjAreaCovRankSym1 a6989586621679573829 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573830 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym1 a6989586621679573829 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573830 :: Symbol) = InjAreaCovRankSym2 a6989586621679573829 a6989586621679573830
type Apply (SurjAreaConRankSym1 a6989586621679573803 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573804 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym1 a6989586621679573803 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573804 :: Symbol) = SurjAreaConRankSym2 a6989586621679573803 a6989586621679573804
type Apply (SurjAreaCovRankSym1 a6989586621679573777 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573778 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym1 a6989586621679573777 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573778 :: Symbol) = SurjAreaCovRankSym2 a6989586621679573777 a6989586621679573778
type Apply (ShowsPrec_6989586621679117751Sym0 :: TyFun Nat (VSpace a b ~> (Symbol ~> Symbol)) -> Type) (a6989586621679117759 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679117751Sym0 :: TyFun Nat (VSpace a b ~> (Symbol ~> Symbol)) -> Type) (a6989586621679117759 :: Nat) = ShowsPrec_6989586621679117751Sym1 a6989586621679117759 :: TyFun (VSpace a b) (Symbol ~> Symbol) -> Type
type Apply (DeltaRankSym2 a6989586621679574034 a6989586621679574035 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574036 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym2 a6989586621679574034 a6989586621679574035 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574036 :: Symbol) = DeltaRankSym3 a6989586621679574034 a6989586621679574035 a6989586621679574036
type Apply (InjSym2ConRankSym2 a6989586621679573955 a6989586621679573956 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573957 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym2 a6989586621679573955 a6989586621679573956 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573957 :: Symbol) = InjSym2ConRankSym3 a6989586621679573955 a6989586621679573956 a6989586621679573957
type Apply (InjSym2CovRankSym2 a6989586621679573932 a6989586621679573933 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573934 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym2 a6989586621679573932 a6989586621679573933 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573934 :: Symbol) = InjSym2CovRankSym3 a6989586621679573932 a6989586621679573933 a6989586621679573934
type Apply (SurjSym2ConRankSym2 a6989586621679573916 a6989586621679573917 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573918 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym2 a6989586621679573916 a6989586621679573917 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573918 :: Symbol) = SurjSym2ConRankSym3 a6989586621679573916 a6989586621679573917 a6989586621679573918
type Apply (SurjSym2CovRankSym2 a6989586621679573890 a6989586621679573891 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573892 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym2 a6989586621679573890 a6989586621679573891 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573892 :: Symbol) = SurjSym2CovRankSym3 a6989586621679573890 a6989586621679573891 a6989586621679573892
type Apply (InjAreaConRankSym2 a6989586621679573855 a6989586621679573856 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573857 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym2 a6989586621679573855 a6989586621679573856 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573857 :: Symbol) = InjAreaConRankSym3 a6989586621679573855 a6989586621679573856 a6989586621679573857
type Apply (InjAreaCovRankSym2 a6989586621679573829 a6989586621679573830 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573831 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym2 a6989586621679573829 a6989586621679573830 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573831 :: Symbol) = InjAreaCovRankSym3 a6989586621679573829 a6989586621679573830 a6989586621679573831
type Apply (SurjAreaConRankSym2 a6989586621679573803 a6989586621679573804 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573805 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym2 a6989586621679573803 a6989586621679573804 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573805 :: Symbol) = SurjAreaConRankSym3 a6989586621679573803 a6989586621679573804 a6989586621679573805
type Apply (SurjAreaCovRankSym2 a6989586621679573777 a6989586621679573778 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573779 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym2 a6989586621679573777 a6989586621679573778 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573779 :: Symbol) = SurjAreaCovRankSym3 a6989586621679573777 a6989586621679573778 a6989586621679573779
type Apply (VSpaceSym0 :: TyFun a (b ~> VSpace a b) -> Type) (a6989586621679112978 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (VSpaceSym0 :: TyFun a (b ~> VSpace a b) -> Type) (a6989586621679112978 :: a) = VSpaceSym1 a6989586621679112978 :: TyFun b (VSpace a b) -> Type
type Apply (Let6989586621679573789RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573783 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573783 :: k1) = Let6989586621679573789RSym1 vid6989586621679573783 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573815RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573809 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573809 :: k1) = Let6989586621679573815RSym1 vid6989586621679573809 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573841RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573835 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573835 :: k1) = Let6989586621679573841RSym1 vid6989586621679573835 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573867RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573861 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573861 :: k1) = Let6989586621679573867RSym1 vid6989586621679573861 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573965RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573960 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573965RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573960 :: k1) = Let6989586621679573965RSym1 vid6989586621679573960 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573942RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573937 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573942RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573937 :: k1) = Let6989586621679573942RSym1 vid6989586621679573937 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573965RSym1 vid6989586621679573960 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679573961 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573965RSym1 vid6989586621679573960 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679573961 :: Nat) = Let6989586621679573965RSym2 vid6989586621679573960 vdim6989586621679573961 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (Let6989586621679573942RSym1 vid6989586621679573937 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679573938 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573942RSym1 vid6989586621679573937 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679573938 :: Nat) = Let6989586621679573942RSym2 vid6989586621679573937 vdim6989586621679573938 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (InjSym2ConRankSym3 a6989586621679573955 a6989586621679573956 a6989586621679573957 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573958 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym3 a6989586621679573955 a6989586621679573956 a6989586621679573957 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573958 :: Symbol) = InjSym2ConRankSym4 a6989586621679573955 a6989586621679573956 a6989586621679573957 a6989586621679573958
type Apply (InjSym2CovRankSym3 a6989586621679573932 a6989586621679573933 a6989586621679573934 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573935 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym3 a6989586621679573932 a6989586621679573933 a6989586621679573934 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573935 :: Symbol) = InjSym2CovRankSym4 a6989586621679573932 a6989586621679573933 a6989586621679573934 a6989586621679573935
type Apply (SurjSym2ConRankSym3 a6989586621679573916 a6989586621679573917 a6989586621679573918 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573919 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym3 a6989586621679573916 a6989586621679573917 a6989586621679573918 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573919 :: Symbol) = SurjSym2ConRankSym4 a6989586621679573916 a6989586621679573917 a6989586621679573918 a6989586621679573919
type Apply (SurjSym2CovRankSym3 a6989586621679573890 a6989586621679573891 a6989586621679573892 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573893 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym3 a6989586621679573890 a6989586621679573891 a6989586621679573892 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573893 :: Symbol) = SurjSym2CovRankSym4 a6989586621679573890 a6989586621679573891 a6989586621679573892 a6989586621679573893
type Apply (InjAreaConRankSym3 a6989586621679573855 a6989586621679573856 a6989586621679573857 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573858 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym3 a6989586621679573855 a6989586621679573856 a6989586621679573857 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573858 :: Symbol) = InjAreaConRankSym4 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858
type Apply (InjAreaCovRankSym3 a6989586621679573829 a6989586621679573830 a6989586621679573831 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573832 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym3 a6989586621679573829 a6989586621679573830 a6989586621679573831 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573832 :: Symbol) = InjAreaCovRankSym4 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832
type Apply (SurjAreaConRankSym3 a6989586621679573803 a6989586621679573804 a6989586621679573805 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573806 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym3 a6989586621679573803 a6989586621679573804 a6989586621679573805 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573806 :: Symbol) = SurjAreaConRankSym4 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806
type Apply (SurjAreaCovRankSym3 a6989586621679573777 a6989586621679573778 a6989586621679573779 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573780 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym3 a6989586621679573777 a6989586621679573778 a6989586621679573779 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573780 :: Symbol) = SurjAreaCovRankSym4 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780
type Apply (VSpaceSym1 a6989586621679112978 :: TyFun b (VSpace a b) -> Type) (a6989586621679112979 :: b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (VSpaceSym1 a6989586621679112978 :: TyFun b (VSpace a b) -> Type) (a6989586621679112979 :: b) = VSpaceSym2 a6989586621679112978 a6989586621679112979
type Apply (CanTransposeConSym1 a6989586621679113537 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113538 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym1 a6989586621679113537 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113538 :: s) = CanTransposeConSym2 a6989586621679113537 a6989586621679113538
type Apply (CanTransposeCovSym1 a6989586621679113482 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113483 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym1 a6989586621679113482 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113483 :: s) = CanTransposeCovSym2 a6989586621679113482 a6989586621679113483
type Apply (Let6989586621679573789RSym1 vid6989586621679573783 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573784 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym1 vid6989586621679573783 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573784 :: a) = Let6989586621679573789RSym2 vid6989586621679573783 a6989586621679573784
type Apply (Let6989586621679573815RSym1 vid6989586621679573809 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573810 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym1 vid6989586621679573809 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573810 :: a) = Let6989586621679573815RSym2 vid6989586621679573809 a6989586621679573810
type Apply (Let6989586621679573841RSym1 vid6989586621679573835 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573836 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym1 vid6989586621679573835 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573836 :: a) = Let6989586621679573841RSym2 vid6989586621679573835 a6989586621679573836
type Apply (Let6989586621679573867RSym1 vid6989586621679573861 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573862 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym1 vid6989586621679573861 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573862 :: a) = Let6989586621679573867RSym2 vid6989586621679573861 a6989586621679573862
type Apply (InjAreaConRankSym4 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573859 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym4 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573859 :: Symbol) = InjAreaConRankSym5 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 a6989586621679573859
type Apply (InjAreaCovRankSym4 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573833 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym4 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573833 :: Symbol) = InjAreaCovRankSym5 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 a6989586621679573833
type Apply (SurjAreaConRankSym4 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573807 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym4 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573807 :: Symbol) = SurjAreaConRankSym5 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 a6989586621679573807
type Apply (SurjAreaCovRankSym4 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573781 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym4 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573781 :: Symbol) = SurjAreaCovRankSym5 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 a6989586621679573781
type Apply (CanTransposeConSym2 a6989586621679113537 a6989586621679113538 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113539 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym2 a6989586621679113537 a6989586621679113538 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113539 :: s) = CanTransposeConSym3 a6989586621679113537 a6989586621679113538 a6989586621679113539
type Apply (CanTransposeCovSym2 a6989586621679113482 a6989586621679113483 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113484 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym2 a6989586621679113482 a6989586621679113483 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113484 :: s) = CanTransposeCovSym3 a6989586621679113482 a6989586621679113483 a6989586621679113484
type Apply (Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679113435 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679113435 :: k) = Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type
type Apply (Let6989586621679573789RSym2 vid6989586621679573783 a6989586621679573784 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573785 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym2 vid6989586621679573783 a6989586621679573784 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573785 :: a) = Let6989586621679573789RSym3 vid6989586621679573783 a6989586621679573784 b6989586621679573785
type Apply (Let6989586621679573815RSym2 vid6989586621679573809 a6989586621679573810 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573811 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym2 vid6989586621679573809 a6989586621679573810 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573811 :: a) = Let6989586621679573815RSym3 vid6989586621679573809 a6989586621679573810 b6989586621679573811
type Apply (Let6989586621679573841RSym2 vid6989586621679573835 a6989586621679573836 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573837 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym2 vid6989586621679573835 a6989586621679573836 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573837 :: a) = Let6989586621679573841RSym3 vid6989586621679573835 a6989586621679573836 b6989586621679573837
type Apply (Let6989586621679573867RSym2 vid6989586621679573861 a6989586621679573862 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573863 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym2 vid6989586621679573861 a6989586621679573862 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573863 :: a) = Let6989586621679573867RSym3 vid6989586621679573861 a6989586621679573862 b6989586621679573863
type Apply (Let6989586621679573965RSym2 vid6989586621679573960 vdim6989586621679573961 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679573962 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573965RSym2 vid6989586621679573960 vdim6989586621679573961 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679573962 :: a) = Let6989586621679573965RSym3 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962
type Apply (Let6989586621679573942RSym2 vid6989586621679573937 vdim6989586621679573938 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679573939 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573942RSym2 vid6989586621679573937 vdim6989586621679573938 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679573939 :: a) = Let6989586621679573942RSym3 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939
type Apply (Let6989586621679573789RSym3 vid6989586621679573783 a6989586621679573784 b6989586621679573785 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573786 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym3 vid6989586621679573783 a6989586621679573784 b6989586621679573785 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573786 :: a) = Let6989586621679573789RSym4 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786
type Apply (Let6989586621679573815RSym3 vid6989586621679573809 a6989586621679573810 b6989586621679573811 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573812 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym3 vid6989586621679573809 a6989586621679573810 b6989586621679573811 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573812 :: a) = Let6989586621679573815RSym4 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812
type Apply (Let6989586621679573841RSym3 vid6989586621679573835 a6989586621679573836 b6989586621679573837 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573838 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym3 vid6989586621679573835 a6989586621679573836 b6989586621679573837 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573838 :: a) = Let6989586621679573841RSym4 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838
type Apply (Let6989586621679573867RSym3 vid6989586621679573861 a6989586621679573862 b6989586621679573863 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573864 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym3 vid6989586621679573861 a6989586621679573862 b6989586621679573863 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573864 :: a) = Let6989586621679573867RSym4 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864
type Apply (Let6989586621679573965RSym3 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679573963 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573965RSym3 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679573963 :: a) = Let6989586621679573965RSym4 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 b6989586621679573963
type Apply (Let6989586621679573942RSym3 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679573940 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573942RSym3 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679573940 :: a) = Let6989586621679573942RSym4 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 b6989586621679573940
type Apply (Let6989586621679573789RSym4 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573787 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym4 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573787 :: a) = Let6989586621679573789RSym5 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 d6989586621679573787
type Apply (Let6989586621679573815RSym4 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573813 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym4 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573813 :: a) = Let6989586621679573815RSym5 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 d6989586621679573813
type Apply (Let6989586621679573841RSym4 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573839 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym4 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573839 :: a) = Let6989586621679573841RSym5 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 d6989586621679573839
type Apply (Let6989586621679573867RSym4 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573865 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym4 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573865 :: a) = Let6989586621679573867RSym5 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 d6989586621679573865
type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679113897 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679113897 :: [(VSpace s n, IList s)]) = LengthRSym1 a6989586621679113897
type Apply (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) (a6989586621679113888 :: [(VSpace a b, IList a)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) (a6989586621679113888 :: [(VSpace a b, IList a)]) = SaneSym1 a6989586621679113888
type Apply (CanTransposeMultSym2 a6989586621679113407 a6989586621679113408 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113409 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym2 a6989586621679113407 a6989586621679113408 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113409 :: [(VSpace s n, IList s)]) = CanTransposeMultSym3 a6989586621679113407 a6989586621679113408 a6989586621679113409
type Apply (CanTransposeConSym3 a6989586621679113537 a6989586621679113538 a6989586621679113539 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113540 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym3 a6989586621679113537 a6989586621679113538 a6989586621679113539 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113540 :: [(VSpace s n, IList s)]) = CanTransposeConSym4 a6989586621679113537 a6989586621679113538 a6989586621679113539 a6989586621679113540
type Apply (CanTransposeCovSym3 a6989586621679113482 a6989586621679113483 a6989586621679113484 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113485 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym3 a6989586621679113482 a6989586621679113483 a6989586621679113484 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113485 :: [(VSpace s n, IList s)]) = CanTransposeCovSym4 a6989586621679113482 a6989586621679113483 a6989586621679113484 a6989586621679113485
type Apply (CanTransposeSym3 a6989586621679113455 a6989586621679113456 a6989586621679113457 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113458 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym3 a6989586621679113455 a6989586621679113456 a6989586621679113457 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113458 :: [(VSpace s n, IList s)]) = CanTransposeSym4 a6989586621679113455 a6989586621679113456 a6989586621679113457 a6989586621679113458
type Rep1 (VSpace a :: Type -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep1 (VSpace a :: Type -> Type) = D1 ('MetaData "VSpace" "Math.Tensor.Safe.TH" "safe-tensor-0.2.1.0-inplace" 'False) (C1 ('MetaCons "VSpace" 'PrefixI 'True) (S1 ('MetaSel ('Just "vId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "vDim") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Apply (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113695 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113695 :: [(VSpace s n, IList s)]) = ContractRSym1 a6989586621679113695
type Apply (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113816 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113816 :: [(VSpace s n, IList s)]) = TailRSym1 a6989586621679113816
type Apply (EpsilonRankSym2 a6989586621679574013 a6989586621679574014 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574015 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym2 a6989586621679574013 a6989586621679574014 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574015 :: NonEmpty Symbol) = EpsilonRankSym3 a6989586621679574013 a6989586621679574014 a6989586621679574015
type Apply (EpsilonInvRankSym2 a6989586621679573993 a6989586621679573994 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573995 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym2 a6989586621679573993 a6989586621679573994 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573995 :: NonEmpty Symbol) = EpsilonInvRankSym3 a6989586621679573993 a6989586621679573994 a6989586621679573995
type Apply (MergeRSym1 a6989586621679113791 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113792 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym1 a6989586621679113791 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113792 :: [(VSpace s n, IList s)]) = MergeRSym2 a6989586621679113791 a6989586621679113792
type Apply (RemoveUntilSym1 a6989586621679113432 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113433 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym1 a6989586621679113432 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113433 :: [(VSpace s n, IList s)]) = RemoveUntilSym2 a6989586621679113432 a6989586621679113433
type Apply (RelabelRSym2 a6989586621679113156 a6989586621679113157 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113158 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym2 a6989586621679113156 a6989586621679113157 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113158 :: [(VSpace s n, IList s)]) = RelabelRSym3 a6989586621679113156 a6989586621679113157 a6989586621679113158
type Apply (TranspositionsSym2 a6989586621679113361 a6989586621679113362 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679113363 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679113361 a6989586621679113362 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679113363 :: [(VSpace s n, IList s)]) = TranspositionsSym3 a6989586621679113361 a6989586621679113362 a6989586621679113363
type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679113412 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679113412 :: [(VSpace s n, IList s)]) = Let6989586621679113413Scrutinee_6989586621679107344Sym3 vs6989586621679113410 tl6989586621679113411 r6989586621679113412
type Apply (Let6989586621679113436GoSym3 i6989586621679113434 r6989586621679113435 a6989586621679113437 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113438 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113436GoSym3 i6989586621679113434 r6989586621679113435 a6989586621679113437 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113438 :: [(VSpace s n, IList s)]) = Let6989586621679113436GoSym4 i6989586621679113434 r6989586621679113435 a6989586621679113437 a6989586621679113438
type Apply (Lambda_6989586621679113805Sym6 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 ys6989586621679113800 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679113807 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym6 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 ys6989586621679113800 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679113807 :: IList s) = Lambda_6989586621679113805Sym7 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 ys6989586621679113800 xl'6989586621679113807
type Apply (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113791 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113791 :: [(VSpace s n, IList s)]) = MergeRSym1 a6989586621679113791
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679113871 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679113871 :: [(VSpace s n, IList s)]) = HeadRSym1 a6989586621679113871
type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113432 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113432 :: Ix s) = RemoveUntilSym1 a6989586621679113432 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (CanTransposeSym1 a6989586621679113455 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113456 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679113455 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113456 :: Ix s) = CanTransposeSym2 a6989586621679113455 a6989586621679113456
type Apply (Let6989586621679113436GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679113434 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113436GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679113434 :: Ix s) = Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type
type Apply (Lambda_6989586621679113805Sym1 xv6989586621679113795 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))))) -> Type) (xl6989586621679113796 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym1 xv6989586621679113795 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))))) -> Type) (xl6989586621679113796 :: IList s) = Lambda_6989586621679113805Sym2 xv6989586621679113795 xl6989586621679113796
type Apply (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679113362 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679113362 :: TransRule s) = TranspositionsSym2 a6989586621679113361 a6989586621679113362
type Apply (CanTransposeMultSym1 a6989586621679113407 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113408 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679113407 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113408 :: TransRule s) = CanTransposeMultSym2 a6989586621679113407 a6989586621679113408
type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679113411 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679113411 :: TransRule s) = Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411
type Apply (RelabelRSym1 a6989586621679113156 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113157 :: NonEmpty (s, s)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym1 a6989586621679113156 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113157 :: NonEmpty (s, s)) = RelabelRSym2 a6989586621679113156 a6989586621679113157
type Apply (Lambda_6989586621679113805Sym2 xv6989586621679113795 xl6989586621679113796 :: TyFun [(VSpace s n, IList s)] (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))) -> Type) (xs6989586621679113797 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym2 xv6989586621679113795 xl6989586621679113796 :: TyFun [(VSpace s n, IList s)] (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))) -> Type) (xs6989586621679113797 :: [(VSpace s n, IList s)]) = Lambda_6989586621679113805Sym3 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797
type Apply (CanTransposeSym2 a6989586621679113455 a6989586621679113456 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113457 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679113455 a6989586621679113456 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113457 :: Ix s) = CanTransposeSym3 a6989586621679113455 a6989586621679113456 a6989586621679113457
type Apply (Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113437 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113437 :: Ix s) = Let6989586621679113436GoSym3 i6989586621679113434 r6989586621679113435 a6989586621679113437 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (Lambda_6989586621679113805Sym4 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679113799 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym4 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679113799 :: IList s) = Lambda_6989586621679113805Sym5 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799
type Apply (Lambda_6989586621679113805Sym5 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679113800 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym5 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679113800 :: [(VSpace s n, IList s)]) = Lambda_6989586621679113805Sym6 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 ys6989586621679113800
type Rep (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep (VSpace a b) = D1 ('MetaData "VSpace" "Math.Tensor.Safe.TH" "safe-tensor-0.2.1.0-inplace" 'False) (C1 ('MetaCons "VSpace" 'PrefixI 'True) (S1 ('MetaSel ('Just "vId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "vDim") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 b)))
type Sing Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing = SVSpace :: VSpace a b -> Type
type Demote (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Demote (VSpace a b) = VSpace (Demote a) (Demote b)
type Show_ (arg :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: VSpace a b) = Apply (Show__6989586621680635830Sym0 :: TyFun (VSpace a b) Symbol -> Type) arg
type ShowList (arg :: [VSpace a b]) arg1 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type ShowList (arg :: [VSpace a b]) arg1 = Apply (Apply (ShowList_6989586621680635838Sym0 :: TyFun [VSpace a b] (Symbol ~> Symbol) -> Type) arg) arg1
type Min (arg :: VSpace a b) (arg1 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Min (arg :: VSpace a b) (arg1 :: VSpace a b) = Apply (Apply (Min_6989586621679837319Sym0 :: TyFun (VSpace a b) (VSpace a b ~> VSpace a b) -> Type) arg) arg1
type Max (arg :: VSpace a b) (arg1 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Max (arg :: VSpace a b) (arg1 :: VSpace a b) = Apply (Apply (Max_6989586621679837303Sym0 :: TyFun (VSpace a b) (VSpace a b ~> VSpace a b) -> Type) arg) arg1
type (arg :: VSpace a b) >= (arg1 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: VSpace a b) >= (arg1 :: VSpace a b) = Apply (Apply (TFHelper_6989586621679837287Sym0 :: TyFun (VSpace a b) (VSpace a b ~> Bool) -> Type) arg) arg1
type (arg :: VSpace a b) > (arg1 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: VSpace a b) > (arg1 :: VSpace a b) = Apply (Apply (TFHelper_6989586621679837271Sym0 :: TyFun (VSpace a b) (VSpace a b ~> Bool) -> Type) arg) arg1
type (arg :: VSpace a b) <= (arg1 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: VSpace a b) <= (arg1 :: VSpace a b) = Apply (Apply (TFHelper_6989586621679837255Sym0 :: TyFun (VSpace a b) (VSpace a b ~> Bool) -> Type) arg) arg1
type (arg :: VSpace a b) < (arg1 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: VSpace a b) < (arg1 :: VSpace a b) = Apply (Apply (TFHelper_6989586621679837239Sym0 :: TyFun (VSpace a b) (VSpace a b ~> Bool) -> Type) arg) arg1
type Compare (a2 :: VSpace a1 b) (a3 :: VSpace a1 b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Compare (a2 :: VSpace a1 b) (a3 :: VSpace a1 b) = Apply (Apply (Compare_6989586621679117768Sym0 :: TyFun (VSpace a1 b) (VSpace a1 b ~> Ordering) -> Type) a2) a3
type (x :: VSpace a b) /= (y :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (x :: VSpace a b) /= (y :: VSpace a b) = Not (x == y)
type (a2 :: VSpace a1 b1) == (b2 :: VSpace a1 b1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (a2 :: VSpace a1 b1) == (b2 :: VSpace a1 b1) = Equals_6989586621679117889 a2 b2
type ShowsPrec a2 (a3 :: VSpace a1 b) a4 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type ShowsPrec a2 (a3 :: VSpace a1 b) a4 = Apply (Apply (Apply (ShowsPrec_6989586621679117751Sym0 :: TyFun Nat (VSpace a1 b ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (VDimSym0 :: TyFun (VSpace a b) b -> Type) (a6989586621679113973 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (VDimSym0 :: TyFun (VSpace a b) b -> Type) (a6989586621679113973 :: VSpace a b) = VDimSym1 a6989586621679113973
type Apply (VIdSym0 :: TyFun (VSpace a b) a -> Type) (a6989586621679113977 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (VIdSym0 :: TyFun (VSpace a b) a -> Type) (a6989586621679113977 :: VSpace a b) = VIdSym1 a6989586621679113977
type Apply (Compare_6989586621679117768Sym1 a6989586621679117773 :: TyFun (VSpace a b) Ordering -> Type) (a6989586621679117774 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679117768Sym1 a6989586621679117773 :: TyFun (VSpace a b) Ordering -> Type) (a6989586621679117774 :: VSpace a b) = Compare_6989586621679117768Sym2 a6989586621679117773 a6989586621679117774
type Apply (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113537 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113537 :: VSpace s n) = CanTransposeConSym1 a6989586621679113537
type Apply (CanTransposeCovSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113482 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113482 :: VSpace s n) = CanTransposeCovSym1 a6989586621679113482
type Apply (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113455 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113455 :: VSpace s n) = CanTransposeSym1 a6989586621679113455
type Apply (Lambda_6989586621679113805Sym0 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))))) -> Type) (xv6989586621679113795 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym0 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))))) -> Type) (xv6989586621679113795 :: VSpace s n) = Lambda_6989586621679113805Sym1 xv6989586621679113795
type Apply (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) (a6989586621679113156 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) (a6989586621679113156 :: VSpace s n) = RelabelRSym1 a6989586621679113156
type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679113361 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679113361 :: VSpace s n) = TranspositionsSym1 a6989586621679113361
type Apply (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113407 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113407 :: VSpace s n) = CanTransposeMultSym1 a6989586621679113407
type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679113410 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679113410 :: VSpace s n) = Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410
type Apply (Compare_6989586621679117768Sym0 :: TyFun (VSpace a b) (VSpace a b ~> Ordering) -> Type) (a6989586621679117773 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679117768Sym0 :: TyFun (VSpace a b) (VSpace a b ~> Ordering) -> Type) (a6989586621679117773 :: VSpace a b) = Compare_6989586621679117768Sym1 a6989586621679117773
type Apply (ShowsPrec_6989586621679117751Sym1 a6989586621679117759 :: TyFun (VSpace a b) (Symbol ~> Symbol) -> Type) (a6989586621679117760 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679117751Sym1 a6989586621679117759 :: TyFun (VSpace a b) (Symbol ~> Symbol) -> Type) (a6989586621679117760 :: VSpace a b) = ShowsPrec_6989586621679117751Sym2 a6989586621679117759 a6989586621679117760
type Apply (Lambda_6989586621679113805Sym3 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679113798 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym3 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679113798 :: VSpace s n) = Lambda_6989586621679113805Sym4 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798

Each vector space must have a list of indices. This can be a contravariant index list, a covariant index list, or both. For sane generalized ranks, the individual lists must be ascending. As already noted, both lists in the mixed case need not be disjoint.

data IList a Source #

Constructors

ConCov (NonEmpty a) (NonEmpty a) 
Cov (NonEmpty a) 
Con (NonEmpty a) 

Instances

Instances details
NFData1 IList Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

liftRnf :: (a -> ()) -> IList a -> () #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

compare :: IList a -> IList a -> Ordering #

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

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

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

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

max :: IList a -> IList a -> IList a #

min :: IList a -> IList a -> IList a #

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

Defined in Math.Tensor.Safe.TH

Methods

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

show :: IList a -> String #

showList :: [IList a] -> ShowS #

Generic (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

NFData a => NFData (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

rnf :: IList a -> () #

PShow (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

SShow (NonEmpty a) => SShow (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sShowsPrec :: forall (t1 :: Nat) (t2 :: IList a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: IList a). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [IList a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

POrd (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

SOrd (NonEmpty a) => SOrd (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sCompare :: forall (t1 :: IList a) (t2 :: IList a). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: forall (t1 :: IList a) (t2 :: IList a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: forall (t1 :: IList a) (t2 :: IList a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: forall (t1 :: IList a) (t2 :: IList a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: forall (t1 :: IList a) (t2 :: IList a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: forall (t1 :: IList a) (t2 :: IList a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

sMin :: forall (t1 :: IList a) (t2 :: IList a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) #

SEq (NonEmpty a) => SEq (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(%==) :: forall (a0 :: IList a) (b :: IList a). Sing a0 -> Sing b -> Sing (a0 == b) #

(%/=) :: forall (a0 :: IList a) (b :: IList a). Sing a0 -> Sing b -> Sing (a0 /= b) #

PEq (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

SDecide (NonEmpty a) => SDecide (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(%~) :: forall (a0 :: IList a) (b :: IList a). Sing a0 -> Sing b -> Decision (a0 :~: b) #

SingKind a => SingKind (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Demote (IList a) = (r :: Type) #

Methods

fromSing :: forall (a0 :: IList a). Sing a0 -> Demote (IList a) #

toSing :: Demote (IList a) -> SomeSing (IList a) #

Generic1 IList Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Rep1 IList :: k -> Type #

Methods

from1 :: forall (a :: k). IList a -> Rep1 IList a #

to1 :: forall (a :: k). Rep1 IList a -> IList a #

SDecide (NonEmpty a) => TestCoercion (SIList :: IList a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testCoercion :: forall (a0 :: k) (b :: k). SIList a0 -> SIList b -> Maybe (Coercion a0 b) #

SDecide (NonEmpty a) => TestEquality (SIList :: IList a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testEquality :: forall (a0 :: k) (b :: k). SIList a0 -> SIList b -> Maybe (a0 :~: b) #

SingI n => SingI ('Cov n :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('Cov n) #

SingI n => SingI ('Con n :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('Con n) #

(SingI n1, SingI n2) => SingI ('ConCov n1 n2 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('ConCov n1 n2) #

SuppressUnusedWarnings DeltaRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings EpsilonRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings EpsilonInvRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI DeltaRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI EpsilonRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI EpsilonInvRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (DeltaRankSym1 a6989586621679574034 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym1 a6989586621679573955 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym1 a6989586621679573932 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym1 a6989586621679573916 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym1 a6989586621679573890 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679117817Sym0 :: TyFun Nat (IList a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (EpsilonRankSym1 a6989586621679574013 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (EpsilonInvRankSym1 a6989586621679573993 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym1 a6989586621679573855 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym1 a6989586621679573829 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym1 a6989586621679573803 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym1 a6989586621679573777 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (ContractISym0 :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (MergeILSym0 :: TyFun (IList a) (IList a ~> Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (LengthILSym0 :: TyFun (IList a) N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (IsAscendingISym0 :: TyFun (IList a) Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679117844Sym0 :: TyFun (IList a) (IList a ~> Ordering) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (PrepICovSym0 :: TyFun a (IList a ~> IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (PrepIConSym0 :: TyFun a (IList a ~> IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113655Scrutinee_6989586621679107274Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113644Scrutinee_6989586621679107284Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelIL'Sym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList (a, a))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelILSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113143Scrutinee_6989586621679107406Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113082Scrutinee_6989586621679107422Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ConCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CovSym0 :: TyFun (NonEmpty a) (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ConSym0 :: TyFun (NonEmpty a) (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI d => SingI (DeltaRankSym1 d :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym1 d) #

SingI d => SingI (InjSym2ConRankSym1 d :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (InjSym2CovRankSym1 d :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (SurjSym2ConRankSym1 d :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (SurjSym2CovRankSym1 d :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (EpsilonRankSym1 d :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonRankSym1 d) #

SingI d => SingI (EpsilonInvRankSym1 d :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (InjAreaConRankSym1 d :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (InjAreaCovRankSym1 d :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (SurjAreaConRankSym1 d :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI d => SingI (SurjAreaCovRankSym1 d :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI (PrepICovSym0 :: TyFun a (IList a ~> IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (PrepIConSym0 :: TyFun a (IList a ~> IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (ContractISym0 :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (MergeILSym0 :: TyFun (IList a) (IList a ~> Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (LengthILSym0 :: TyFun (IList a) N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (IsAscendingISym0 :: TyFun (IList a) Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (RelabelIL'Sym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList (a, a))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (RelabelILSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (ConSym0 :: TyFun (NonEmpty a) (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ConSym0 #

SingI (CovSym0 :: TyFun (NonEmpty a) (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing CovSym0 #

SingI (ConCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ConCovSym0 #

SuppressUnusedWarnings (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113655Scrutinee_6989586621679107274Sym1 y'6989586621679113653 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113644Scrutinee_6989586621679107284Sym1 x'6989586621679113642 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (DeltaRankSym2 a6989586621679574034 a6989586621679574035 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym2 a6989586621679573955 a6989586621679573956 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym2 a6989586621679573932 a6989586621679573933 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym2 a6989586621679573916 a6989586621679573917 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym2 a6989586621679573890 a6989586621679573891 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym2 a6989586621679573855 a6989586621679573856 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym2 a6989586621679573829 a6989586621679573830 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym2 a6989586621679573803 a6989586621679573804 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym2 a6989586621679573777 a6989586621679573778 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym0 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (PrepICovSym1 a6989586621679113668 :: TyFun (IList a) (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (PrepIConSym1 a6989586621679113682 :: TyFun (IList a) (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (MergeILSym1 a6989586621679113738 :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelIL'Sym1 a6989586621679113094 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelILSym1 a6989586621679113139 :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113143Scrutinee_6989586621679107406Sym1 rl6989586621679113141 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelTranspositionsSym1 a6989586621679113078 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113082Scrutinee_6989586621679107422Sym1 rl6989586621679113080 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679117817Sym1 a6989586621679117829 :: TyFun (IList a) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679117844Sym1 a6989586621679117849 :: TyFun (IList a) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573965RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573942RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (EpsilonRankSym2 a6989586621679574013 a6989586621679574014 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (EpsilonInvRankSym2 a6989586621679573993 a6989586621679573994 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679113121Sym0 :: TyFun (NonEmpty (a, a)) (TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ConCovSym1 a6989586621679112985 :: TyFun (NonEmpty a) (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd s => SingI (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing MergeRSym0 #

SOrd s => SingI (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing TailRSym0 #

SOrd s => SingI (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing HeadRSym0 #

(SOrd a, SOrd b) => SingI (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing SaneSym0 #

SingI (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SingI d1, SingI d2) => SingI (DeltaRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (InjSym2ConRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2ConRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (InjSym2CovRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2CovRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (SurjSym2ConRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2ConRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (SurjSym2CovRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2CovRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (InjAreaConRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (InjAreaCovRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (SurjAreaConRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (SurjAreaCovRankSym2 d1 d2 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym2 d1 d2) #

(SOrd s, SOrd n) => SingI (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (CanTransposeCovSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd s => SingI (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd a, SingI d) => SingI (RelabelTranspositionsSym1 d :: TyFun (IList a) (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd a, SingI d) => SingI (RelabelIL'Sym1 d :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelIL'Sym1 d) #

(SOrd a, SingI d) => SingI (RelabelILSym1 d :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelILSym1 d) #

SingI d => SingI (PrepICovSym1 d :: TyFun (IList a) (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (PrepICovSym1 d) #

SingI d => SingI (PrepIConSym1 d :: TyFun (IList a) (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (PrepIConSym1 d) #

(SOrd a, SingI d) => SingI (MergeILSym1 d :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (MergeILSym1 d) #

(SingI d1, SingI d2) => SingI (EpsilonRankSym2 d1 d2 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonRankSym2 d1 d2) #

(SingI d1, SingI d2) => SingI (EpsilonInvRankSym2 d1 d2 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonInvRankSym2 d1 d2) #

SingI d => SingI (ConCovSym1 d :: TyFun (NonEmpty a) (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (ConCovSym1 d) #

SuppressUnusedWarnings (MergeRSym1 a6989586621679113791 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RemoveUntilSym1 a6989586621679113432 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573965RSym1 vid6989586621679573960 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573942RSym1 vid6989586621679573937 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (DeltaRankSym3 a6989586621679574034 a6989586621679574035 a6989586621679574036 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym3 a6989586621679573955 a6989586621679573956 a6989586621679573957 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym3 a6989586621679573932 a6989586621679573933 a6989586621679573934 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym3 a6989586621679573916 a6989586621679573917 a6989586621679573918 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym3 a6989586621679573890 a6989586621679573891 a6989586621679573892 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym3 a6989586621679573855 a6989586621679573856 a6989586621679573857 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym3 a6989586621679573829 a6989586621679573830 a6989586621679573831 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym3 a6989586621679573803 a6989586621679573804 a6989586621679573805 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym3 a6989586621679573777 a6989586621679573778 a6989586621679573779 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (CanTransposeSym1 a6989586621679113455 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113436GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym1 xv6989586621679113795 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113112Scrutinee_6989586621679107418Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113101Scrutinee_6989586621679107420Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym1 a6989586621679113407 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113755Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113769Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113780Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113820L'Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeConSym1 a6989586621679113537 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym1 a6989586621679113482 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113699Scrutinee_6989586621679107266Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113655Scrutinee_6989586621679107274Sym2 y'6989586621679113653 ys'6989586621679113654 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113644Scrutinee_6989586621679107284Sym2 x'6989586621679113642 xs'6989586621679113643 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113744Sym0 :: TyFun k2 (TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113121Sym1 rl6989586621679113118 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113109Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113098Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym1 vid6989586621679573783 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym1 vid6989586621679573809 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym1 vid6989586621679573835 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym1 vid6989586621679573861 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (RelabelRSym1 a6989586621679113156 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113762Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SingI d) => SingI (RemoveUntilSym1 d :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RemoveUntilSym1 d) #

(SOrd s, SOrd n, SingI d) => SingI (MergeRSym1 d :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (MergeRSym1 d) #

(SingI d1, SingI d2, SingI d3) => SingI (DeltaRankSym3 d1 d2 d3 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (InjSym2ConRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2ConRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (InjSym2CovRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2CovRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (SurjSym2ConRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2ConRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (SurjSym2CovRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2CovRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (InjAreaConRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (InjAreaCovRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (SurjAreaConRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3) => SingI (SurjAreaCovRankSym3 d1 d2 d3 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym3 d1 d2 d3) #

(SOrd s, SOrd n, SingI d) => SingI (CanTransposeCovSym1 d :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d) => SingI (CanTransposeConSym1 d :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d) => SingI (CanTransposeSym1 d :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym1 d) #

(SOrd s, SOrd n, SingI d) => SingI (TranspositionsSym1 d :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d) => SingI (CanTransposeMultSym1 d :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d) => SingI (RelabelRSym1 d :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelRSym1 d) #

SuppressUnusedWarnings (Lambda_6989586621679113805Sym2 xv6989586621679113795 xl6989586621679113796 :: TyFun [(VSpace s n, IList s)] (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelRSym2 a6989586621679113156 a6989586621679113157 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym2 a6989586621679113361 a6989586621679113362 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym2 a6989586621679113407 a6989586621679113408 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113655Scrutinee_6989586621679107274Sym3 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113644Scrutinee_6989586621679107284Sym3 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjSym2ConRankSym4 a6989586621679573955 a6989586621679573956 a6989586621679573957 a6989586621679573958 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym4 a6989586621679573932 a6989586621679573933 a6989586621679573934 a6989586621679573935 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym4 a6989586621679573916 a6989586621679573917 a6989586621679573918 a6989586621679573919 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym4 a6989586621679573890 a6989586621679573891 a6989586621679573892 a6989586621679573893 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym4 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym4 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym4 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym4 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (CanTransposeSym2 a6989586621679113455 a6989586621679113456 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113820L'Sym1 v6989586621679113817 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113699Scrutinee_6989586621679107266Sym1 v6989586621679113696 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113762Sym1 xs6989586621679113759 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113769Sym1 xs6989586621679113766 :: TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeConSym2 a6989586621679113537 a6989586621679113538 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym2 a6989586621679113482 a6989586621679113483 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113109Sym1 rl6989586621679113107 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113098Sym1 rl6989586621679113096 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym2 vid6989586621679573783 a6989586621679573784 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym2 vid6989586621679573809 a6989586621679573810 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym2 vid6989586621679573835 a6989586621679573836 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym2 vid6989586621679573861 a6989586621679573862 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573965RSym2 vid6989586621679573960 vdim6989586621679573961 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573942RSym2 vid6989586621679573937 vdim6989586621679573938 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679113127L'Sym0 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113755Sym1 xs6989586621679113752 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113780Sym1 ys6989586621679113777 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113744Sym1 xs6989586621679113740 :: TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113124Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113121Sym2 rl6989586621679113118 is6989586621679113119 :: TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (RelabelRSym2 d1 d2 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelRSym2 d1 d2) #

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (TranspositionsSym2 d1 d2 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TranspositionsSym2 d1 d2) #

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (CanTransposeMultSym2 d1 d2 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeMultSym2 d1 d2) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (InjSym2ConRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2ConRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (InjSym2CovRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2CovRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (SurjSym2ConRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2ConRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (SurjSym2CovRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2CovRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (InjAreaConRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (InjAreaCovRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (SurjAreaConRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym4 d1 d2 d3 d4) #

(SingI d1, SingI d2, SingI d3, SingI d4) => SingI (SurjAreaCovRankSym4 d1 d2 d3 d4 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym4 d1 d2 d3 d4) #

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (CanTransposeCovSym2 d1 d2 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeCovSym2 d1 d2) #

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (CanTransposeConSym2 d1 d2 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeConSym2 d1 d2) #

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (CanTransposeSym2 d1 d2 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym2 d1 d2) #

SuppressUnusedWarnings (CanTransposeConSym3 a6989586621679113537 a6989586621679113538 a6989586621679113539 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym3 a6989586621679113482 a6989586621679113483 a6989586621679113484 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym3 a6989586621679113455 a6989586621679113456 a6989586621679113457 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjAreaConRankSym5 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 a6989586621679573859 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym5 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 a6989586621679573833 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym5 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 a6989586621679573807 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym5 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 a6989586621679573781 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym3 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113109Sym2 rl6989586621679113107 is6989586621679113108 :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113098Sym2 rl6989586621679113096 is6989586621679113097 :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113755Sym2 xs6989586621679113752 ys6989586621679113753 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113762Sym2 xs6989586621679113759 ys6989586621679113760 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113780Sym2 ys6989586621679113777 xs6989586621679113778 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113820L'Sym2 v6989586621679113817 l6989586621679113818 :: TyFun k2 (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113699Scrutinee_6989586621679107266Sym2 v6989586621679113696 is6989586621679113697 :: TyFun k2 (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113655Scrutinee_6989586621679107274Sym4 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 xs6989586621679113618 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113644Scrutinee_6989586621679107284Sym4 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 xs6989586621679113618 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113744Sym2 xs6989586621679113740 ys6989586621679113741 :: TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113124Sym1 is'6989586621679113123 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym3 vid6989586621679573783 a6989586621679573784 b6989586621679573785 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym3 vid6989586621679573809 a6989586621679573810 b6989586621679573811 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym3 vid6989586621679573835 a6989586621679573836 b6989586621679573837 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym3 vid6989586621679573861 a6989586621679573862 b6989586621679573863 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573965RSym3 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573942RSym3 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679113121Sym3 rl6989586621679113118 is6989586621679113119 js6989586621679113120 :: TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113127L'Sym1 js'6989586621679113126 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113747Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113769Sym2 xs6989586621679113766 xs'6989586621679113767 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d1, SingI d2, SingI d3) => SingI (CanTransposeSym3 d1 d2 d3 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym3 d1 d2 d3) #

(SOrd s, SOrd n, SingI d1, SingI d2, SingI d3) => SingI (CanTransposeCovSym3 d1 d2 d3 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeCovSym3 d1 d2 d3) #

(SOrd s, SOrd n, SingI d1, SingI d2, SingI d3) => SingI (CanTransposeConSym3 d1 d2 d3 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeConSym3 d1 d2 d3) #

(SingI d1, SingI d2, SingI d3, SingI d4, SingI d5) => SingI (InjAreaConRankSym5 d1 d2 d3 d4 d5 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym5 d1 d2 d3 d4 d5) #

(SingI d1, SingI d2, SingI d3, SingI d4, SingI d5) => SingI (InjAreaCovRankSym5 d1 d2 d3 d4 d5 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym5 d1 d2 d3 d4 d5) #

(SingI d1, SingI d2, SingI d3, SingI d4, SingI d5) => SingI (SurjAreaConRankSym5 d1 d2 d3 d4 d5 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym5 d1 d2 d3 d4 d5) #

(SingI d1, SingI d2, SingI d3, SingI d4, SingI d5) => SingI (SurjAreaCovRankSym5 d1 d2 d3 d4 d5 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym5 d1 d2 d3 d4 d5) #

SuppressUnusedWarnings (Let6989586621679113436GoSym3 i6989586621679113434 r6989586621679113435 a6989586621679113437 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113655Scrutinee_6989586621679107274Sym5 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 xs6989586621679113618 y6989586621679113619 :: TyFun [a] (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113644Scrutinee_6989586621679107284Sym5 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 xs6989586621679113618 y6989586621679113619 :: TyFun [a] (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym4 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113127L'Sym2 js'6989586621679113126 is'6989586621679113123 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113747Sym1 xs''6989586621679113746 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113124Sym2 is'6989586621679113123 rl6989586621679113118 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym4 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym4 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym4 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym4 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573965RSym4 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 b6989586621679573963 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573942RSym4 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 b6989586621679573940 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679113755Sym3 xs6989586621679113752 ys6989586621679113753 xs'6989586621679113754 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113762Sym3 xs6989586621679113759 ys6989586621679113760 ys'6989586621679113761 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113769Sym3 xs6989586621679113766 xs'6989586621679113767 ys6989586621679113768 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113780Sym3 ys6989586621679113777 xs6989586621679113778 ys'6989586621679113779 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113744Sym3 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym5 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113127L'Sym3 js'6989586621679113126 is'6989586621679113123 rl6989586621679113118 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113747Sym2 xs''6989586621679113746 xs6989586621679113740 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113124Sym3 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679573789RSym5 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 d6989586621679573787 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573815RSym5 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 d6989586621679573813 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573841RSym5 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 d6989586621679573839 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679573867RSym5 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 d6989586621679573865 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679113744Sym4 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 ys'6989586621679113743 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113805Sym6 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 ys6989586621679113800 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113127L'Sym4 js'6989586621679113126 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 :: TyFun k3 (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113747Sym3 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113124Sym4 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 js6989586621679113120 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113747Sym4 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113747Sym5 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 ys'6989586621679113743 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (DeltaRankSym3 a6989586621679574034 a6989586621679574035 a6989586621679574036 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679574037 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym3 a6989586621679574034 a6989586621679574035 a6989586621679574036 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679574037 :: Symbol) = DeltaRankSym4 a6989586621679574034 a6989586621679574035 a6989586621679574036 a6989586621679574037
type Apply (InjSym2ConRankSym4 a6989586621679573955 a6989586621679573956 a6989586621679573957 a6989586621679573958 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573959 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym4 a6989586621679573955 a6989586621679573956 a6989586621679573957 a6989586621679573958 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573959 :: Symbol) = InjSym2ConRankSym5 a6989586621679573955 a6989586621679573956 a6989586621679573957 a6989586621679573958 a6989586621679573959
type Apply (InjSym2CovRankSym4 a6989586621679573932 a6989586621679573933 a6989586621679573934 a6989586621679573935 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573936 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym4 a6989586621679573932 a6989586621679573933 a6989586621679573934 a6989586621679573935 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573936 :: Symbol) = InjSym2CovRankSym5 a6989586621679573932 a6989586621679573933 a6989586621679573934 a6989586621679573935 a6989586621679573936
type Apply (SurjSym2ConRankSym4 a6989586621679573916 a6989586621679573917 a6989586621679573918 a6989586621679573919 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573920 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym4 a6989586621679573916 a6989586621679573917 a6989586621679573918 a6989586621679573919 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573920 :: Symbol) = SurjSym2ConRankSym5 a6989586621679573916 a6989586621679573917 a6989586621679573918 a6989586621679573919 a6989586621679573920
type Apply (SurjSym2CovRankSym4 a6989586621679573890 a6989586621679573891 a6989586621679573892 a6989586621679573893 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573894 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym4 a6989586621679573890 a6989586621679573891 a6989586621679573892 a6989586621679573893 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573894 :: Symbol) = SurjSym2CovRankSym5 a6989586621679573890 a6989586621679573891 a6989586621679573892 a6989586621679573893 a6989586621679573894
type Apply (InjAreaConRankSym5 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 a6989586621679573859 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573860 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym5 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 a6989586621679573859 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573860 :: Symbol) = InjAreaConRankSym6 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 a6989586621679573859 a6989586621679573860
type Apply (InjAreaCovRankSym5 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 a6989586621679573833 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573834 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym5 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 a6989586621679573833 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573834 :: Symbol) = InjAreaCovRankSym6 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 a6989586621679573833 a6989586621679573834
type Apply (SurjAreaConRankSym5 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 a6989586621679573807 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573808 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym5 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 a6989586621679573807 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573808 :: Symbol) = SurjAreaConRankSym6 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 a6989586621679573807 a6989586621679573808
type Apply (SurjAreaCovRankSym5 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 a6989586621679573781 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573782 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym5 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 a6989586621679573781 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573782 :: Symbol) = SurjAreaCovRankSym6 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 a6989586621679573781 a6989586621679573782
type Apply (Let6989586621679113820L'Sym2 v6989586621679113817 l6989586621679113818 :: TyFun k2 (Maybe (IList a)) -> Type) (ls6989586621679113819 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113820L'Sym2 v6989586621679113817 l6989586621679113818 :: TyFun k2 (Maybe (IList a)) -> Type) (ls6989586621679113819 :: k2) = Let6989586621679113820L'Sym3 v6989586621679113817 l6989586621679113818 ls6989586621679113819
type Apply (Let6989586621679113699Scrutinee_6989586621679107266Sym2 v6989586621679113696 is6989586621679113697 :: TyFun k2 (Maybe (IList a)) -> Type) (xs6989586621679113698 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113699Scrutinee_6989586621679107266Sym2 v6989586621679113696 is6989586621679113697 :: TyFun k2 (Maybe (IList a)) -> Type) (xs6989586621679113698 :: k2) = Let6989586621679113699Scrutinee_6989586621679107266Sym3 v6989586621679113696 is6989586621679113697 xs6989586621679113698
type Apply (Let6989586621679573965RSym4 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 b6989586621679573963 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573964 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573965RSym4 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 b6989586621679573963 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573964 :: a) = Let6989586621679573965RSym5 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 b6989586621679573963 i6989586621679573964
type Apply (Let6989586621679573942RSym4 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 b6989586621679573940 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573941 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573942RSym4 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 b6989586621679573940 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573941 :: a) = Let6989586621679573942RSym5 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 b6989586621679573940 i6989586621679573941
type Apply (Let6989586621679573789RSym5 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 d6989586621679573787 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573788 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym5 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 d6989586621679573787 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573788 :: a) = Let6989586621679573789RSym6 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 d6989586621679573787 i6989586621679573788
type Apply (Let6989586621679573815RSym5 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 d6989586621679573813 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573814 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym5 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 d6989586621679573813 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573814 :: a) = Let6989586621679573815RSym6 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 d6989586621679573813 i6989586621679573814
type Apply (Let6989586621679573841RSym5 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 d6989586621679573839 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573840 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym5 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 d6989586621679573839 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573840 :: a) = Let6989586621679573841RSym6 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 d6989586621679573839 i6989586621679573840
type Apply (Let6989586621679573867RSym5 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 d6989586621679573865 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573866 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym5 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 d6989586621679573865 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679573866 :: a) = Let6989586621679573867RSym6 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 d6989586621679573865 i6989586621679573866
type Apply (Let6989586621679113127L'Sym4 js'6989586621679113126 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 :: TyFun k3 (IList a) -> Type) (js6989586621679113120 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113127L'Sym4 js'6989586621679113126 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 :: TyFun k3 (IList a) -> Type) (js6989586621679113120 :: k3) = Let6989586621679113127L'Sym5 js'6989586621679113126 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 js6989586621679113120
type Apply DeltaRankSym0 (a6989586621679574034 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply DeltaRankSym0 (a6989586621679574034 :: Symbol) = DeltaRankSym1 a6989586621679574034
type Apply InjSym2ConRankSym0 (a6989586621679573955 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2ConRankSym0 (a6989586621679573955 :: Symbol) = InjSym2ConRankSym1 a6989586621679573955
type Apply InjSym2CovRankSym0 (a6989586621679573932 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2CovRankSym0 (a6989586621679573932 :: Symbol) = InjSym2CovRankSym1 a6989586621679573932
type Apply SurjSym2ConRankSym0 (a6989586621679573916 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2ConRankSym0 (a6989586621679573916 :: Symbol) = SurjSym2ConRankSym1 a6989586621679573916
type Apply SurjSym2CovRankSym0 (a6989586621679573890 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2CovRankSym0 (a6989586621679573890 :: Symbol) = SurjSym2CovRankSym1 a6989586621679573890
type Apply EpsilonRankSym0 (a6989586621679574013 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonRankSym0 (a6989586621679574013 :: Symbol) = EpsilonRankSym1 a6989586621679574013
type Apply EpsilonInvRankSym0 (a6989586621679573993 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonInvRankSym0 (a6989586621679573993 :: Symbol) = EpsilonInvRankSym1 a6989586621679573993
type Apply InjAreaConRankSym0 (a6989586621679573855 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaConRankSym0 (a6989586621679573855 :: Symbol) = InjAreaConRankSym1 a6989586621679573855
type Apply InjAreaCovRankSym0 (a6989586621679573829 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaCovRankSym0 (a6989586621679573829 :: Symbol) = InjAreaCovRankSym1 a6989586621679573829
type Apply SurjAreaConRankSym0 (a6989586621679573803 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjAreaConRankSym0 (a6989586621679573803 :: Symbol) = SurjAreaConRankSym1 a6989586621679573803
type Apply SurjAreaCovRankSym0 (a6989586621679573777 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjAreaCovRankSym0 (a6989586621679573777 :: Symbol) = SurjAreaCovRankSym1 a6989586621679573777
type Apply (DeltaRankSym1 a6989586621679574034 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679574035 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym1 a6989586621679574034 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679574035 :: Nat) = DeltaRankSym2 a6989586621679574034 a6989586621679574035
type Apply (InjSym2ConRankSym1 a6989586621679573955 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573956 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym1 a6989586621679573955 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573956 :: Nat) = InjSym2ConRankSym2 a6989586621679573955 a6989586621679573956
type Apply (InjSym2CovRankSym1 a6989586621679573932 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573933 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym1 a6989586621679573932 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573933 :: Nat) = InjSym2CovRankSym2 a6989586621679573932 a6989586621679573933
type Apply (SurjSym2ConRankSym1 a6989586621679573916 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573917 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym1 a6989586621679573916 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573917 :: Nat) = SurjSym2ConRankSym2 a6989586621679573916 a6989586621679573917
type Apply (SurjSym2CovRankSym1 a6989586621679573890 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573891 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym1 a6989586621679573890 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573891 :: Nat) = SurjSym2CovRankSym2 a6989586621679573890 a6989586621679573891
type Apply (ShowsPrec_6989586621679117817Sym0 :: TyFun Nat (IList a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679117829 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679117817Sym0 :: TyFun Nat (IList a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679117829 :: Nat) = ShowsPrec_6989586621679117817Sym1 a6989586621679117829 :: TyFun (IList a) (Symbol ~> Symbol) -> Type
type Apply (EpsilonRankSym1 a6989586621679574013 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574014 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym1 a6989586621679574013 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574014 :: Nat) = EpsilonRankSym2 a6989586621679574013 a6989586621679574014
type Apply (EpsilonInvRankSym1 a6989586621679573993 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573994 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym1 a6989586621679573993 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573994 :: Nat) = EpsilonInvRankSym2 a6989586621679573993 a6989586621679573994
type Apply (InjAreaConRankSym1 a6989586621679573855 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573856 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym1 a6989586621679573855 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573856 :: Symbol) = InjAreaConRankSym2 a6989586621679573855 a6989586621679573856
type Apply (InjAreaCovRankSym1 a6989586621679573829 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573830 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym1 a6989586621679573829 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573830 :: Symbol) = InjAreaCovRankSym2 a6989586621679573829 a6989586621679573830
type Apply (SurjAreaConRankSym1 a6989586621679573803 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573804 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym1 a6989586621679573803 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573804 :: Symbol) = SurjAreaConRankSym2 a6989586621679573803 a6989586621679573804
type Apply (SurjAreaCovRankSym1 a6989586621679573777 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573778 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym1 a6989586621679573777 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679573778 :: Symbol) = SurjAreaCovRankSym2 a6989586621679573777 a6989586621679573778
type Apply (PrepICovSym0 :: TyFun a (IList a ~> IList a) -> Type) (a6989586621679113668 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepICovSym0 :: TyFun a (IList a ~> IList a) -> Type) (a6989586621679113668 :: a) = PrepICovSym1 a6989586621679113668
type Apply (PrepIConSym0 :: TyFun a (IList a ~> IList a) -> Type) (a6989586621679113682 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepIConSym0 :: TyFun a (IList a ~> IList a) -> Type) (a6989586621679113682 :: a) = PrepIConSym1 a6989586621679113682
type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (y'6989586621679113653 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (y'6989586621679113653 :: a) = Let6989586621679113655Scrutinee_6989586621679107274Sym1 y'6989586621679113653
type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x'6989586621679113642 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x'6989586621679113642 :: a) = Let6989586621679113644Scrutinee_6989586621679107284Sym1 x'6989586621679113642
type Apply (DeltaRankSym2 a6989586621679574034 a6989586621679574035 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574036 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym2 a6989586621679574034 a6989586621679574035 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574036 :: Symbol) = DeltaRankSym3 a6989586621679574034 a6989586621679574035 a6989586621679574036
type Apply (InjSym2ConRankSym2 a6989586621679573955 a6989586621679573956 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573957 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym2 a6989586621679573955 a6989586621679573956 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573957 :: Symbol) = InjSym2ConRankSym3 a6989586621679573955 a6989586621679573956 a6989586621679573957
type Apply (InjSym2CovRankSym2 a6989586621679573932 a6989586621679573933 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573934 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym2 a6989586621679573932 a6989586621679573933 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573934 :: Symbol) = InjSym2CovRankSym3 a6989586621679573932 a6989586621679573933 a6989586621679573934
type Apply (SurjSym2ConRankSym2 a6989586621679573916 a6989586621679573917 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573918 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym2 a6989586621679573916 a6989586621679573917 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573918 :: Symbol) = SurjSym2ConRankSym3 a6989586621679573916 a6989586621679573917 a6989586621679573918
type Apply (SurjSym2CovRankSym2 a6989586621679573890 a6989586621679573891 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573892 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym2 a6989586621679573890 a6989586621679573891 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573892 :: Symbol) = SurjSym2CovRankSym3 a6989586621679573890 a6989586621679573891 a6989586621679573892
type Apply (InjAreaConRankSym2 a6989586621679573855 a6989586621679573856 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573857 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym2 a6989586621679573855 a6989586621679573856 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573857 :: Symbol) = InjAreaConRankSym3 a6989586621679573855 a6989586621679573856 a6989586621679573857
type Apply (InjAreaCovRankSym2 a6989586621679573829 a6989586621679573830 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573831 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym2 a6989586621679573829 a6989586621679573830 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573831 :: Symbol) = InjAreaCovRankSym3 a6989586621679573829 a6989586621679573830 a6989586621679573831
type Apply (SurjAreaConRankSym2 a6989586621679573803 a6989586621679573804 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573805 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym2 a6989586621679573803 a6989586621679573804 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573805 :: Symbol) = SurjAreaConRankSym3 a6989586621679573803 a6989586621679573804 a6989586621679573805
type Apply (SurjAreaCovRankSym2 a6989586621679573777 a6989586621679573778 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573779 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym2 a6989586621679573777 a6989586621679573778 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679573779 :: Symbol) = SurjAreaCovRankSym3 a6989586621679573777 a6989586621679573778 a6989586621679573779
type Apply (Let6989586621679573789RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573783 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573783 :: k1) = Let6989586621679573789RSym1 vid6989586621679573783 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573815RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573809 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573809 :: k1) = Let6989586621679573815RSym1 vid6989586621679573809 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573841RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573835 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573835 :: k1) = Let6989586621679573841RSym1 vid6989586621679573835 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573867RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573861 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573861 :: k1) = Let6989586621679573867RSym1 vid6989586621679573861 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573965RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573960 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573965RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573960 :: k1) = Let6989586621679573965RSym1 vid6989586621679573960 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573942RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573937 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573942RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679573937 :: k1) = Let6989586621679573942RSym1 vid6989586621679573937 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679573965RSym1 vid6989586621679573960 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679573961 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573965RSym1 vid6989586621679573960 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679573961 :: Nat) = Let6989586621679573965RSym2 vid6989586621679573960 vdim6989586621679573961 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (Let6989586621679573942RSym1 vid6989586621679573937 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679573938 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573942RSym1 vid6989586621679573937 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679573938 :: Nat) = Let6989586621679573942RSym2 vid6989586621679573937 vdim6989586621679573938 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (InjSym2ConRankSym3 a6989586621679573955 a6989586621679573956 a6989586621679573957 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573958 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym3 a6989586621679573955 a6989586621679573956 a6989586621679573957 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573958 :: Symbol) = InjSym2ConRankSym4 a6989586621679573955 a6989586621679573956 a6989586621679573957 a6989586621679573958
type Apply (InjSym2CovRankSym3 a6989586621679573932 a6989586621679573933 a6989586621679573934 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573935 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym3 a6989586621679573932 a6989586621679573933 a6989586621679573934 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573935 :: Symbol) = InjSym2CovRankSym4 a6989586621679573932 a6989586621679573933 a6989586621679573934 a6989586621679573935
type Apply (SurjSym2ConRankSym3 a6989586621679573916 a6989586621679573917 a6989586621679573918 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573919 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym3 a6989586621679573916 a6989586621679573917 a6989586621679573918 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573919 :: Symbol) = SurjSym2ConRankSym4 a6989586621679573916 a6989586621679573917 a6989586621679573918 a6989586621679573919
type Apply (SurjSym2CovRankSym3 a6989586621679573890 a6989586621679573891 a6989586621679573892 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573893 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym3 a6989586621679573890 a6989586621679573891 a6989586621679573892 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573893 :: Symbol) = SurjSym2CovRankSym4 a6989586621679573890 a6989586621679573891 a6989586621679573892 a6989586621679573893
type Apply (InjAreaConRankSym3 a6989586621679573855 a6989586621679573856 a6989586621679573857 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573858 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym3 a6989586621679573855 a6989586621679573856 a6989586621679573857 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573858 :: Symbol) = InjAreaConRankSym4 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858
type Apply (InjAreaCovRankSym3 a6989586621679573829 a6989586621679573830 a6989586621679573831 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573832 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym3 a6989586621679573829 a6989586621679573830 a6989586621679573831 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573832 :: Symbol) = InjAreaCovRankSym4 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832
type Apply (SurjAreaConRankSym3 a6989586621679573803 a6989586621679573804 a6989586621679573805 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573806 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym3 a6989586621679573803 a6989586621679573804 a6989586621679573805 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573806 :: Symbol) = SurjAreaConRankSym4 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806
type Apply (SurjAreaCovRankSym3 a6989586621679573777 a6989586621679573778 a6989586621679573779 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573780 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym3 a6989586621679573777 a6989586621679573778 a6989586621679573779 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679573780 :: Symbol) = SurjAreaCovRankSym4 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780
type Apply (Lambda_6989586621679113755Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679113752 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113755Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679113752 :: k1) = Lambda_6989586621679113755Sym1 xs6989586621679113752 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113769Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679113766 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113769Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679113766 :: k1) = Lambda_6989586621679113769Sym1 xs6989586621679113766 :: TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113780Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679113777 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113780Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679113777 :: k1) = Lambda_6989586621679113780Sym1 ys6989586621679113777 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Let6989586621679113820L'Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679113817 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113820L'Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679113817 :: k1) = Let6989586621679113820L'Sym1 v6989586621679113817 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type
type Apply (CanTransposeConSym1 a6989586621679113537 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113538 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym1 a6989586621679113537 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113538 :: s) = CanTransposeConSym2 a6989586621679113537 a6989586621679113538
type Apply (CanTransposeCovSym1 a6989586621679113482 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113483 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym1 a6989586621679113482 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113483 :: s) = CanTransposeCovSym2 a6989586621679113482 a6989586621679113483
type Apply (Let6989586621679113699Scrutinee_6989586621679107266Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679113696 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113699Scrutinee_6989586621679107266Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679113696 :: k1) = Let6989586621679113699Scrutinee_6989586621679107266Sym1 v6989586621679113696 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type
type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym2 y'6989586621679113653 ys'6989586621679113654 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679113617 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym2 y'6989586621679113653 ys'6989586621679113654 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679113617 :: a) = Let6989586621679113655Scrutinee_6989586621679107274Sym3 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617
type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym2 x'6989586621679113642 xs'6989586621679113643 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679113617 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym2 x'6989586621679113642 xs'6989586621679113643 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679113617 :: a) = Let6989586621679113644Scrutinee_6989586621679107284Sym3 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617
type Apply (Lambda_6989586621679113744Sym0 :: TyFun k2 (TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679113740 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113744Sym0 :: TyFun k2 (TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679113740 :: k2) = Lambda_6989586621679113744Sym1 xs6989586621679113740 :: TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113121Sym1 rl6989586621679113118 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) (is6989586621679113119 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113121Sym1 rl6989586621679113118 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) (is6989586621679113119 :: k1) = Lambda_6989586621679113121Sym2 rl6989586621679113118 is6989586621679113119
type Apply (Lambda_6989586621679113109Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679113107 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113109Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679113107 :: k1) = Lambda_6989586621679113109Sym1 rl6989586621679113107 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679113098Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679113096 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113098Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679113096 :: k1) = Lambda_6989586621679113098Sym1 rl6989586621679113096 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type
type Apply (Let6989586621679573789RSym1 vid6989586621679573783 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573784 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym1 vid6989586621679573783 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573784 :: a) = Let6989586621679573789RSym2 vid6989586621679573783 a6989586621679573784
type Apply (Let6989586621679573815RSym1 vid6989586621679573809 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573810 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym1 vid6989586621679573809 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573810 :: a) = Let6989586621679573815RSym2 vid6989586621679573809 a6989586621679573810
type Apply (Let6989586621679573841RSym1 vid6989586621679573835 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573836 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym1 vid6989586621679573835 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573836 :: a) = Let6989586621679573841RSym2 vid6989586621679573835 a6989586621679573836
type Apply (Let6989586621679573867RSym1 vid6989586621679573861 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573862 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym1 vid6989586621679573861 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679573862 :: a) = Let6989586621679573867RSym2 vid6989586621679573861 a6989586621679573862
type Apply (InjAreaConRankSym4 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573859 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym4 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573859 :: Symbol) = InjAreaConRankSym5 a6989586621679573855 a6989586621679573856 a6989586621679573857 a6989586621679573858 a6989586621679573859
type Apply (InjAreaCovRankSym4 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573833 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym4 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573833 :: Symbol) = InjAreaCovRankSym5 a6989586621679573829 a6989586621679573830 a6989586621679573831 a6989586621679573832 a6989586621679573833
type Apply (SurjAreaConRankSym4 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573807 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym4 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573807 :: Symbol) = SurjAreaConRankSym5 a6989586621679573803 a6989586621679573804 a6989586621679573805 a6989586621679573806 a6989586621679573807
type Apply (SurjAreaCovRankSym4 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573781 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym4 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573781 :: Symbol) = SurjAreaCovRankSym5 a6989586621679573777 a6989586621679573778 a6989586621679573779 a6989586621679573780 a6989586621679573781
type Apply (Lambda_6989586621679113762Sym1 xs6989586621679113759 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679113760 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113762Sym1 xs6989586621679113759 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679113760 :: k1) = Lambda_6989586621679113762Sym2 xs6989586621679113759 ys6989586621679113760 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679113769Sym1 xs6989586621679113766 :: TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679113767 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113769Sym1 xs6989586621679113766 :: TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679113767 :: k2) = Lambda_6989586621679113769Sym2 xs6989586621679113766 xs'6989586621679113767 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (CanTransposeConSym2 a6989586621679113537 a6989586621679113538 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113539 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym2 a6989586621679113537 a6989586621679113538 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113539 :: s) = CanTransposeConSym3 a6989586621679113537 a6989586621679113538 a6989586621679113539
type Apply (CanTransposeCovSym2 a6989586621679113482 a6989586621679113483 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113484 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym2 a6989586621679113482 a6989586621679113483 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113484 :: s) = CanTransposeCovSym3 a6989586621679113482 a6989586621679113483 a6989586621679113484
type Apply (Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679113435 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679113435 :: k) = Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type
type Apply (Lambda_6989586621679113109Sym1 rl6989586621679113107 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679113108 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113109Sym1 rl6989586621679113107 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679113108 :: k2) = Lambda_6989586621679113109Sym2 rl6989586621679113107 is6989586621679113108 :: TyFun (IList a) (Maybe (IList a)) -> Type
type Apply (Lambda_6989586621679113098Sym1 rl6989586621679113096 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679113097 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113098Sym1 rl6989586621679113096 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679113097 :: k2) = Lambda_6989586621679113098Sym2 rl6989586621679113096 is6989586621679113097 :: TyFun (IList a) (Maybe (IList a)) -> Type
type Apply (Let6989586621679573789RSym2 vid6989586621679573783 a6989586621679573784 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573785 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym2 vid6989586621679573783 a6989586621679573784 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573785 :: a) = Let6989586621679573789RSym3 vid6989586621679573783 a6989586621679573784 b6989586621679573785
type Apply (Let6989586621679573815RSym2 vid6989586621679573809 a6989586621679573810 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573811 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym2 vid6989586621679573809 a6989586621679573810 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573811 :: a) = Let6989586621679573815RSym3 vid6989586621679573809 a6989586621679573810 b6989586621679573811
type Apply (Let6989586621679573841RSym2 vid6989586621679573835 a6989586621679573836 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573837 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym2 vid6989586621679573835 a6989586621679573836 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573837 :: a) = Let6989586621679573841RSym3 vid6989586621679573835 a6989586621679573836 b6989586621679573837
type Apply (Let6989586621679573867RSym2 vid6989586621679573861 a6989586621679573862 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573863 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym2 vid6989586621679573861 a6989586621679573862 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679573863 :: a) = Let6989586621679573867RSym3 vid6989586621679573861 a6989586621679573862 b6989586621679573863
type Apply (Let6989586621679573965RSym2 vid6989586621679573960 vdim6989586621679573961 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679573962 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573965RSym2 vid6989586621679573960 vdim6989586621679573961 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679573962 :: a) = Let6989586621679573965RSym3 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962
type Apply (Let6989586621679573942RSym2 vid6989586621679573937 vdim6989586621679573938 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679573939 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573942RSym2 vid6989586621679573937 vdim6989586621679573938 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679573939 :: a) = Let6989586621679573942RSym3 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939
type Apply (Lambda_6989586621679113755Sym2 xs6989586621679113752 ys6989586621679113753 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (xs'6989586621679113754 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113755Sym2 xs6989586621679113752 ys6989586621679113753 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (xs'6989586621679113754 :: k2) = Lambda_6989586621679113755Sym3 xs6989586621679113752 ys6989586621679113753 xs'6989586621679113754
type Apply (Lambda_6989586621679113762Sym2 xs6989586621679113759 ys6989586621679113760 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679113761 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113762Sym2 xs6989586621679113759 ys6989586621679113760 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679113761 :: k2) = Lambda_6989586621679113762Sym3 xs6989586621679113759 ys6989586621679113760 ys'6989586621679113761
type Apply (Lambda_6989586621679113780Sym2 ys6989586621679113777 xs6989586621679113778 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679113779 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113780Sym2 ys6989586621679113777 xs6989586621679113778 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679113779 :: k2) = Lambda_6989586621679113780Sym3 ys6989586621679113777 xs6989586621679113778 ys'6989586621679113779
type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym4 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 xs6989586621679113618 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679113619 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym4 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 xs6989586621679113618 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679113619 :: a) = Let6989586621679113655Scrutinee_6989586621679107274Sym5 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 xs6989586621679113618 y6989586621679113619
type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym4 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 xs6989586621679113618 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679113619 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym4 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 xs6989586621679113618 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679113619 :: a) = Let6989586621679113644Scrutinee_6989586621679107284Sym5 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 xs6989586621679113618 y6989586621679113619
type Apply (Lambda_6989586621679113744Sym2 xs6989586621679113740 ys6989586621679113741 :: TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679113742 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113744Sym2 xs6989586621679113740 ys6989586621679113741 :: TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679113742 :: k3) = Lambda_6989586621679113744Sym3 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742
type Apply (Lambda_6989586621679113124Sym1 is'6989586621679113123 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (rl6989586621679113118 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113124Sym1 is'6989586621679113123 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (rl6989586621679113118 :: k1) = Lambda_6989586621679113124Sym2 is'6989586621679113123 rl6989586621679113118 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Let6989586621679573789RSym3 vid6989586621679573783 a6989586621679573784 b6989586621679573785 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573786 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym3 vid6989586621679573783 a6989586621679573784 b6989586621679573785 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573786 :: a) = Let6989586621679573789RSym4 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786
type Apply (Let6989586621679573815RSym3 vid6989586621679573809 a6989586621679573810 b6989586621679573811 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573812 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym3 vid6989586621679573809 a6989586621679573810 b6989586621679573811 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573812 :: a) = Let6989586621679573815RSym4 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812
type Apply (Let6989586621679573841RSym3 vid6989586621679573835 a6989586621679573836 b6989586621679573837 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573838 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym3 vid6989586621679573835 a6989586621679573836 b6989586621679573837 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573838 :: a) = Let6989586621679573841RSym4 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838
type Apply (Let6989586621679573867RSym3 vid6989586621679573861 a6989586621679573862 b6989586621679573863 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573864 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym3 vid6989586621679573861 a6989586621679573862 b6989586621679573863 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679573864 :: a) = Let6989586621679573867RSym4 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864
type Apply (Let6989586621679573965RSym3 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679573963 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573965RSym3 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679573963 :: a) = Let6989586621679573965RSym4 vid6989586621679573960 vdim6989586621679573961 a6989586621679573962 b6989586621679573963
type Apply (Let6989586621679573942RSym3 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679573940 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573942RSym3 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679573940 :: a) = Let6989586621679573942RSym4 vid6989586621679573937 vdim6989586621679573938 a6989586621679573939 b6989586621679573940
type Apply (Let6989586621679113127L'Sym2 js'6989586621679113126 is'6989586621679113123 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) (rl6989586621679113118 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113127L'Sym2 js'6989586621679113126 is'6989586621679113123 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) (rl6989586621679113118 :: k1) = Let6989586621679113127L'Sym3 js'6989586621679113126 is'6989586621679113123 rl6989586621679113118 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type
type Apply (Lambda_6989586621679113747Sym1 xs''6989586621679113746 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679113740 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113747Sym1 xs''6989586621679113746 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679113740 :: k1) = Lambda_6989586621679113747Sym2 xs''6989586621679113746 xs6989586621679113740 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113124Sym2 is'6989586621679113123 rl6989586621679113118 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (is6989586621679113119 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113124Sym2 is'6989586621679113123 rl6989586621679113118 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (is6989586621679113119 :: k2) = Lambda_6989586621679113124Sym3 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Let6989586621679573789RSym4 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573787 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573789RSym4 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573787 :: a) = Let6989586621679573789RSym5 vid6989586621679573783 a6989586621679573784 b6989586621679573785 c6989586621679573786 d6989586621679573787
type Apply (Let6989586621679573815RSym4 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573813 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573815RSym4 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573813 :: a) = Let6989586621679573815RSym5 vid6989586621679573809 a6989586621679573810 b6989586621679573811 c6989586621679573812 d6989586621679573813
type Apply (Let6989586621679573841RSym4 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573839 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573841RSym4 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573839 :: a) = Let6989586621679573841RSym5 vid6989586621679573835 a6989586621679573836 b6989586621679573837 c6989586621679573838 d6989586621679573839
type Apply (Let6989586621679573867RSym4 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573865 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679573867RSym4 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679573865 :: a) = Let6989586621679573867RSym5 vid6989586621679573861 a6989586621679573862 b6989586621679573863 c6989586621679573864 d6989586621679573865
type Apply (Let6989586621679113127L'Sym3 js'6989586621679113126 is'6989586621679113123 rl6989586621679113118 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) (is6989586621679113119 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113127L'Sym3 js'6989586621679113126 is'6989586621679113123 rl6989586621679113118 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) (is6989586621679113119 :: k2) = Let6989586621679113127L'Sym4 js'6989586621679113126 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 :: TyFun k3 (IList a) -> Type
type Apply (Lambda_6989586621679113747Sym2 xs''6989586621679113746 xs6989586621679113740 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679113741 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113747Sym2 xs''6989586621679113746 xs6989586621679113740 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679113741 :: k2) = Lambda_6989586621679113747Sym3 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113124Sym3 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (js6989586621679113120 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113124Sym3 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (js6989586621679113120 :: k3) = Lambda_6989586621679113124Sym4 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 js6989586621679113120
type Apply (Lambda_6989586621679113747Sym3 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679113742 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113747Sym3 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679113742 :: k3) = Lambda_6989586621679113747Sym4 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679113747Sym4 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679113743 :: k4) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113747Sym4 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679113743 :: k4) = Lambda_6989586621679113747Sym5 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 ys'6989586621679113743
type Rep (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing = SIList :: IList a -> Type
type Demote (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Demote (IList a) = IList (Demote a)
type Rep1 IList Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: IList a) = Apply (Show__6989586621680635830Sym0 :: TyFun (IList a) Symbol -> Type) arg
type ShowList (arg :: [IList a]) arg1 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type ShowList (arg :: [IList a]) arg1 = Apply (Apply (ShowList_6989586621680635838Sym0 :: TyFun [IList a] (Symbol ~> Symbol) -> Type) arg) arg1
type Min (arg :: IList a) (arg1 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Min (arg :: IList a) (arg1 :: IList a) = Apply (Apply (Min_6989586621679837319Sym0 :: TyFun (IList a) (IList a ~> IList a) -> Type) arg) arg1
type Max (arg :: IList a) (arg1 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Max (arg :: IList a) (arg1 :: IList a) = Apply (Apply (Max_6989586621679837303Sym0 :: TyFun (IList a) (IList a ~> IList a) -> Type) arg) arg1
type (arg :: IList a) >= (arg1 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: IList a) >= (arg1 :: IList a) = Apply (Apply (TFHelper_6989586621679837287Sym0 :: TyFun (IList a) (IList a ~> Bool) -> Type) arg) arg1
type (arg :: IList a) > (arg1 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: IList a) > (arg1 :: IList a) = Apply (Apply (TFHelper_6989586621679837271Sym0 :: TyFun (IList a) (IList a ~> Bool) -> Type) arg) arg1
type (arg :: IList a) <= (arg1 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: IList a) <= (arg1 :: IList a) = Apply (Apply (TFHelper_6989586621679837255Sym0 :: TyFun (IList a) (IList a ~> Bool) -> Type) arg) arg1
type (arg :: IList a) < (arg1 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: IList a) < (arg1 :: IList a) = Apply (Apply (TFHelper_6989586621679837239Sym0 :: TyFun (IList a) (IList a ~> Bool) -> Type) arg) arg1
type Compare (a2 :: IList a1) (a3 :: IList a1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Compare (a2 :: IList a1) (a3 :: IList a1) = Apply (Apply (Compare_6989586621679117844Sym0 :: TyFun (IList a1) (IList a1 ~> Ordering) -> Type) a2) a3
type (x :: IList a) /= (y :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (x :: IList a) /= (y :: IList a) = Not (x == y)
type (a2 :: IList a1) == (b :: IList a1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (a2 :: IList a1) == (b :: IList a1) = Equals_6989586621679117905 a2 b
type ShowsPrec a2 (a3 :: IList a1) a4 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type ShowsPrec a2 (a3 :: IList a1) a4 = Apply (Apply (Apply (ShowsPrec_6989586621679117817Sym0 :: TyFun Nat (IList a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679113902 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679113902 :: IList a) = LengthILSym1 a6989586621679113902
type Apply (IsAscendingISym0 :: TyFun (IList a) Bool -> Type) (a6989586621679113923 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IsAscendingISym0 :: TyFun (IList a) Bool -> Type) (a6989586621679113923 :: IList a) = IsAscendingISym1 a6989586621679113923
type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679113897 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679113897 :: [(VSpace s n, IList s)]) = LengthRSym1 a6989586621679113897
type Apply (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) (a6989586621679113888 :: [(VSpace a b, IList a)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) (a6989586621679113888 :: [(VSpace a b, IList a)]) = SaneSym1 a6989586621679113888
type Apply (Compare_6989586621679117844Sym1 a6989586621679117849 :: TyFun (IList a) Ordering -> Type) (a6989586621679117850 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679117844Sym1 a6989586621679117849 :: TyFun (IList a) Ordering -> Type) (a6989586621679117850 :: IList a) = Compare_6989586621679117844Sym2 a6989586621679117849 a6989586621679117850
type Apply (CanTransposeMultSym2 a6989586621679113407 a6989586621679113408 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113409 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym2 a6989586621679113407 a6989586621679113408 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113409 :: [(VSpace s n, IList s)]) = CanTransposeMultSym3 a6989586621679113407 a6989586621679113408 a6989586621679113409
type Apply (CanTransposeConSym3 a6989586621679113537 a6989586621679113538 a6989586621679113539 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113540 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym3 a6989586621679113537 a6989586621679113538 a6989586621679113539 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113540 :: [(VSpace s n, IList s)]) = CanTransposeConSym4 a6989586621679113537 a6989586621679113538 a6989586621679113539 a6989586621679113540
type Apply (CanTransposeCovSym3 a6989586621679113482 a6989586621679113483 a6989586621679113484 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113485 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym3 a6989586621679113482 a6989586621679113483 a6989586621679113484 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113485 :: [(VSpace s n, IList s)]) = CanTransposeCovSym4 a6989586621679113482 a6989586621679113483 a6989586621679113484 a6989586621679113485
type Apply (CanTransposeSym3 a6989586621679113455 a6989586621679113456 a6989586621679113457 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113458 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym3 a6989586621679113455 a6989586621679113456 a6989586621679113457 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679113458 :: [(VSpace s n, IList s)]) = CanTransposeSym4 a6989586621679113455 a6989586621679113456 a6989586621679113457 a6989586621679113458
type Apply (ContractISym0 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679113616 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ContractISym0 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679113616 :: IList a) = ContractISym1 a6989586621679113616
type Apply (CovSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679112988 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CovSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679112988 :: NonEmpty a) = CovSym1 a6989586621679112988
type Apply (ConSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679112990 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ConSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679112990 :: NonEmpty a) = ConSym1 a6989586621679112990
type Apply (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113695 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113695 :: [(VSpace s n, IList s)]) = ContractRSym1 a6989586621679113695
type Apply (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113816 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113816 :: [(VSpace s n, IList s)]) = TailRSym1 a6989586621679113816
type Apply (PrepICovSym1 a6989586621679113668 :: TyFun (IList a) (IList a) -> Type) (a6989586621679113669 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepICovSym1 a6989586621679113668 :: TyFun (IList a) (IList a) -> Type) (a6989586621679113669 :: IList a) = PrepICovSym2 a6989586621679113668 a6989586621679113669
type Apply (PrepIConSym1 a6989586621679113682 :: TyFun (IList a) (IList a) -> Type) (a6989586621679113683 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepIConSym1 a6989586621679113682 :: TyFun (IList a) (IList a) -> Type) (a6989586621679113683 :: IList a) = PrepIConSym2 a6989586621679113682 a6989586621679113683
type Apply (MergeILSym1 a6989586621679113738 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679113739 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeILSym1 a6989586621679113738 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679113739 :: IList a) = MergeILSym2 a6989586621679113738 a6989586621679113739
type Apply (RelabelIL'Sym1 a6989586621679113094 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (a6989586621679113095 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelIL'Sym1 a6989586621679113094 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (a6989586621679113095 :: IList a) = RelabelIL'Sym2 a6989586621679113094 a6989586621679113095
type Apply (RelabelILSym1 a6989586621679113139 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679113140 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelILSym1 a6989586621679113139 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679113140 :: IList a) = RelabelILSym2 a6989586621679113139 a6989586621679113140
type Apply (Let6989586621679113143Scrutinee_6989586621679107406Sym1 rl6989586621679113141 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679113142 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113143Scrutinee_6989586621679107406Sym1 rl6989586621679113141 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679113142 :: IList a) = Let6989586621679113143Scrutinee_6989586621679107406Sym2 rl6989586621679113141 is6989586621679113142
type Apply (RelabelTranspositionsSym1 a6989586621679113078 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679113079 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym1 a6989586621679113078 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679113079 :: IList a) = RelabelTranspositionsSym2 a6989586621679113078 a6989586621679113079
type Apply (Let6989586621679113082Scrutinee_6989586621679107422Sym1 rl6989586621679113080 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679113081 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113082Scrutinee_6989586621679107422Sym1 rl6989586621679113080 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679113081 :: IList a) = Let6989586621679113082Scrutinee_6989586621679107422Sym2 rl6989586621679113080 is6989586621679113081
type Apply (EpsilonRankSym2 a6989586621679574013 a6989586621679574014 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574015 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym2 a6989586621679574013 a6989586621679574014 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679574015 :: NonEmpty Symbol) = EpsilonRankSym3 a6989586621679574013 a6989586621679574014 a6989586621679574015
type Apply (EpsilonInvRankSym2 a6989586621679573993 a6989586621679573994 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573995 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym2 a6989586621679573993 a6989586621679573994 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679573995 :: NonEmpty Symbol) = EpsilonInvRankSym3 a6989586621679573993 a6989586621679573994 a6989586621679573995
type Apply (ConCovSym1 a6989586621679112985 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679112986 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ConCovSym1 a6989586621679112985 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679112986 :: NonEmpty a) = ConCovSym2 a6989586621679112985 a6989586621679112986
type Apply (MergeRSym1 a6989586621679113791 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113792 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym1 a6989586621679113791 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113792 :: [(VSpace s n, IList s)]) = MergeRSym2 a6989586621679113791 a6989586621679113792
type Apply (RemoveUntilSym1 a6989586621679113432 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113433 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym1 a6989586621679113432 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113433 :: [(VSpace s n, IList s)]) = RemoveUntilSym2 a6989586621679113432 a6989586621679113433
type Apply (RelabelRSym2 a6989586621679113156 a6989586621679113157 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113158 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym2 a6989586621679113156 a6989586621679113157 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113158 :: [(VSpace s n, IList s)]) = RelabelRSym3 a6989586621679113156 a6989586621679113157 a6989586621679113158
type Apply (TranspositionsSym2 a6989586621679113361 a6989586621679113362 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679113363 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679113361 a6989586621679113362 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679113363 :: [(VSpace s n, IList s)]) = TranspositionsSym3 a6989586621679113361 a6989586621679113362 a6989586621679113363
type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679113412 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679113412 :: [(VSpace s n, IList s)]) = Let6989586621679113413Scrutinee_6989586621679107344Sym3 vs6989586621679113410 tl6989586621679113411 r6989586621679113412
type Apply (Lambda_6989586621679113109Sym2 rl6989586621679113107 is6989586621679113108 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679113111 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113109Sym2 rl6989586621679113107 is6989586621679113108 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679113111 :: IList a) = Lambda_6989586621679113109Sym3 rl6989586621679113107 is6989586621679113108 is'6989586621679113111
type Apply (Lambda_6989586621679113098Sym2 rl6989586621679113096 is6989586621679113097 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679113100 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113098Sym2 rl6989586621679113096 is6989586621679113097 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679113100 :: IList a) = Lambda_6989586621679113098Sym3 rl6989586621679113096 is6989586621679113097 is'6989586621679113100
type Apply (Lambda_6989586621679113121Sym3 rl6989586621679113118 is6989586621679113119 js6989586621679113120 :: TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) (is'6989586621679113123 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113121Sym3 rl6989586621679113118 is6989586621679113119 js6989586621679113120 :: TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) (is'6989586621679113123 :: NonEmpty (a, a)) = Lambda_6989586621679113121Sym4 rl6989586621679113118 is6989586621679113119 js6989586621679113120 is'6989586621679113123
type Apply (Let6989586621679113436GoSym3 i6989586621679113434 r6989586621679113435 a6989586621679113437 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113438 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113436GoSym3 i6989586621679113434 r6989586621679113435 a6989586621679113437 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679113438 :: [(VSpace s n, IList s)]) = Let6989586621679113436GoSym4 i6989586621679113434 r6989586621679113435 a6989586621679113437 a6989586621679113438
type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym5 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 xs6989586621679113618 y6989586621679113619 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679113620 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym5 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 xs6989586621679113618 y6989586621679113619 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679113620 :: [a]) = Let6989586621679113655Scrutinee_6989586621679107274Sym6 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 xs6989586621679113618 y6989586621679113619 ys6989586621679113620
type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym5 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 xs6989586621679113618 y6989586621679113619 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679113620 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym5 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 xs6989586621679113618 y6989586621679113619 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679113620 :: [a]) = Let6989586621679113644Scrutinee_6989586621679107284Sym6 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 xs6989586621679113618 y6989586621679113619 ys6989586621679113620
type Apply (Lambda_6989586621679113755Sym3 xs6989586621679113752 ys6989586621679113753 xs'6989586621679113754 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679113757 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113755Sym3 xs6989586621679113752 ys6989586621679113753 xs'6989586621679113754 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679113757 :: NonEmpty a) = Lambda_6989586621679113755Sym4 xs6989586621679113752 ys6989586621679113753 xs'6989586621679113754 xs''6989586621679113757
type Apply (Lambda_6989586621679113762Sym3 xs6989586621679113759 ys6989586621679113760 ys'6989586621679113761 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679113764 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113762Sym3 xs6989586621679113759 ys6989586621679113760 ys'6989586621679113761 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679113764 :: NonEmpty a) = Lambda_6989586621679113762Sym4 xs6989586621679113759 ys6989586621679113760 ys'6989586621679113761 ys''6989586621679113764
type Apply (Lambda_6989586621679113769Sym3 xs6989586621679113766 xs'6989586621679113767 ys6989586621679113768 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679113771 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113769Sym3 xs6989586621679113766 xs'6989586621679113767 ys6989586621679113768 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679113771 :: NonEmpty a) = Lambda_6989586621679113769Sym4 xs6989586621679113766 xs'6989586621679113767 ys6989586621679113768 xs''6989586621679113771
type Apply (Lambda_6989586621679113780Sym3 ys6989586621679113777 xs6989586621679113778 ys'6989586621679113779 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679113782 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113780Sym3 ys6989586621679113777 xs6989586621679113778 ys'6989586621679113779 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679113782 :: NonEmpty a) = Lambda_6989586621679113780Sym4 ys6989586621679113777 xs6989586621679113778 ys'6989586621679113779 ys''6989586621679113782
type Apply (Lambda_6989586621679113744Sym4 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 ys'6989586621679113743 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679113746 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113744Sym4 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 ys'6989586621679113743 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679113746 :: NonEmpty a) = Lambda_6989586621679113744Sym5 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 ys'6989586621679113743 xs''6989586621679113746
type Apply (Lambda_6989586621679113805Sym6 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 ys6989586621679113800 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679113807 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym6 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 ys6989586621679113800 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679113807 :: IList s) = Lambda_6989586621679113805Sym7 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 ys6989586621679113800 xl'6989586621679113807
type Apply (Lambda_6989586621679113124Sym4 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 js6989586621679113120 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (js'6989586621679113126 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113124Sym4 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 js6989586621679113120 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (js'6989586621679113126 :: NonEmpty a) = Lambda_6989586621679113124Sym5 is'6989586621679113123 rl6989586621679113118 is6989586621679113119 js6989586621679113120 js'6989586621679113126
type Apply (Lambda_6989586621679113747Sym5 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 ys'6989586621679113743 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679113749 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113747Sym5 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 ys'6989586621679113743 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679113749 :: NonEmpty a) = Lambda_6989586621679113747Sym6 xs''6989586621679113746 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 ys'6989586621679113743 ys''6989586621679113749
type Apply (MergeILSym0 :: TyFun (IList a) (IList a ~> Maybe (IList a)) -> Type) (a6989586621679113738 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeILSym0 :: TyFun (IList a) (IList a ~> Maybe (IList a)) -> Type) (a6989586621679113738 :: IList a) = MergeILSym1 a6989586621679113738
type Apply (Compare_6989586621679117844Sym0 :: TyFun (IList a) (IList a ~> Ordering) -> Type) (a6989586621679117849 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679117844Sym0 :: TyFun (IList a) (IList a ~> Ordering) -> Type) (a6989586621679117849 :: IList a) = Compare_6989586621679117844Sym1 a6989586621679117849
type Apply (RelabelIL'Sym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList (a, a))) -> Type) (a6989586621679113094 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelIL'Sym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList (a, a))) -> Type) (a6989586621679113094 :: NonEmpty (a, a)) = RelabelIL'Sym1 a6989586621679113094
type Apply (RelabelILSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList a)) -> Type) (a6989586621679113139 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelILSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList a)) -> Type) (a6989586621679113139 :: NonEmpty (a, a)) = RelabelILSym1 a6989586621679113139
type Apply (Let6989586621679113143Scrutinee_6989586621679107406Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679113141 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113143Scrutinee_6989586621679107406Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679113141 :: NonEmpty (a, a)) = Let6989586621679113143Scrutinee_6989586621679107406Sym1 rl6989586621679113141
type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) (a6989586621679113078 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) (a6989586621679113078 :: NonEmpty (a, a)) = RelabelTranspositionsSym1 a6989586621679113078
type Apply (Let6989586621679113082Scrutinee_6989586621679107422Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679113080 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113082Scrutinee_6989586621679107422Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679113080 :: NonEmpty (a, a)) = Let6989586621679113082Scrutinee_6989586621679107422Sym1 rl6989586621679113080
type Apply (ConCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> IList a) -> Type) (a6989586621679112985 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ConCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> IList a) -> Type) (a6989586621679112985 :: NonEmpty a) = ConCovSym1 a6989586621679112985
type Apply (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113791 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113791 :: [(VSpace s n, IList s)]) = MergeRSym1 a6989586621679113791
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679113871 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679113871 :: [(VSpace s n, IList s)]) = HeadRSym1 a6989586621679113871
type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym1 y'6989586621679113653 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (ys'6989586621679113654 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym1 y'6989586621679113653 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (ys'6989586621679113654 :: [a]) = Let6989586621679113655Scrutinee_6989586621679107274Sym2 y'6989586621679113653 ys'6989586621679113654
type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym1 x'6989586621679113642 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs'6989586621679113643 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym1 x'6989586621679113642 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs'6989586621679113643 :: [a]) = Let6989586621679113644Scrutinee_6989586621679107284Sym2 x'6989586621679113642 xs'6989586621679113643
type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113432 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113432 :: Ix s) = RemoveUntilSym1 a6989586621679113432 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (ShowsPrec_6989586621679117817Sym1 a6989586621679117829 :: TyFun (IList a) (Symbol ~> Symbol) -> Type) (a6989586621679117830 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679117817Sym1 a6989586621679117829 :: TyFun (IList a) (Symbol ~> Symbol) -> Type) (a6989586621679117830 :: IList a) = ShowsPrec_6989586621679117817Sym2 a6989586621679117829 a6989586621679117830
type Apply (Lambda_6989586621679113121Sym0 :: TyFun (NonEmpty (a, a)) (TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) -> Type) (rl6989586621679113118 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113121Sym0 :: TyFun (NonEmpty (a, a)) (TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) -> Type) (rl6989586621679113118 :: NonEmpty (a, a)) = Lambda_6989586621679113121Sym1 rl6989586621679113118 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type
type Apply (CanTransposeSym1 a6989586621679113455 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113456 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679113455 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113456 :: Ix s) = CanTransposeSym2 a6989586621679113455 a6989586621679113456
type Apply (Let6989586621679113436GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679113434 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113436GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679113434 :: Ix s) = Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type
type Apply (Lambda_6989586621679113805Sym1 xv6989586621679113795 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))))) -> Type) (xl6989586621679113796 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym1 xv6989586621679113795 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))))) -> Type) (xl6989586621679113796 :: IList s) = Lambda_6989586621679113805Sym2 xv6989586621679113795 xl6989586621679113796
type Apply (Let6989586621679113112Scrutinee_6989586621679107418Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679113111 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113112Scrutinee_6989586621679107418Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679113111 :: IList a) = Let6989586621679113112Scrutinee_6989586621679107418Sym1 is'6989586621679113111 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type
type Apply (Let6989586621679113101Scrutinee_6989586621679107420Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679113100 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113101Scrutinee_6989586621679107420Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679113100 :: IList a) = Let6989586621679113101Scrutinee_6989586621679107420Sym1 is'6989586621679113100 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type
type Apply (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679113362 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679113362 :: TransRule s) = TranspositionsSym2 a6989586621679113361 a6989586621679113362
type Apply (CanTransposeMultSym1 a6989586621679113407 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113408 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679113407 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113408 :: TransRule s) = CanTransposeMultSym2 a6989586621679113407 a6989586621679113408
type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679113411 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679113411 :: TransRule s) = Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411
type Apply (RelabelRSym1 a6989586621679113156 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113157 :: NonEmpty (s, s)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym1 a6989586621679113156 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679113157 :: NonEmpty (s, s)) = RelabelRSym2 a6989586621679113156 a6989586621679113157
type Apply (Lambda_6989586621679113762Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679113759 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113762Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679113759 :: NonEmpty a) = Lambda_6989586621679113762Sym1 xs6989586621679113759 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113805Sym2 xv6989586621679113795 xl6989586621679113796 :: TyFun [(VSpace s n, IList s)] (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))) -> Type) (xs6989586621679113797 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym2 xv6989586621679113795 xl6989586621679113796 :: TyFun [(VSpace s n, IList s)] (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))) -> Type) (xs6989586621679113797 :: [(VSpace s n, IList s)]) = Lambda_6989586621679113805Sym3 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797
type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym3 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679113618 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113655Scrutinee_6989586621679107274Sym3 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679113618 :: [a]) = Let6989586621679113655Scrutinee_6989586621679107274Sym4 y'6989586621679113653 ys'6989586621679113654 x6989586621679113617 xs6989586621679113618
type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym3 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679113618 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113644Scrutinee_6989586621679107284Sym3 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679113618 :: [a]) = Let6989586621679113644Scrutinee_6989586621679107284Sym4 x'6989586621679113642 xs'6989586621679113643 x6989586621679113617 xs6989586621679113618
type Apply (CanTransposeSym2 a6989586621679113455 a6989586621679113456 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113457 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679113455 a6989586621679113456 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113457 :: Ix s) = CanTransposeSym3 a6989586621679113455 a6989586621679113456 a6989586621679113457
type Apply (Let6989586621679113820L'Sym1 v6989586621679113817 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (l6989586621679113818 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113820L'Sym1 v6989586621679113817 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (l6989586621679113818 :: IList a) = Let6989586621679113820L'Sym2 v6989586621679113817 l6989586621679113818 :: TyFun k2 (Maybe (IList a)) -> Type
type Apply (Let6989586621679113699Scrutinee_6989586621679107266Sym1 v6989586621679113696 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (is6989586621679113697 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113699Scrutinee_6989586621679107266Sym1 v6989586621679113696 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (is6989586621679113697 :: IList a) = Let6989586621679113699Scrutinee_6989586621679107266Sym2 v6989586621679113696 is6989586621679113697 :: TyFun k2 (Maybe (IList a)) -> Type
type Apply (Let6989586621679113127L'Sym0 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) -> Type) (js'6989586621679113126 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113127L'Sym0 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) -> Type) (js'6989586621679113126 :: NonEmpty a) = Let6989586621679113127L'Sym1 js'6989586621679113126 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113755Sym1 xs6989586621679113752 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679113753 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113755Sym1 xs6989586621679113752 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679113753 :: NonEmpty a) = Lambda_6989586621679113755Sym2 xs6989586621679113752 ys6989586621679113753 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679113780Sym1 ys6989586621679113777 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679113778 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113780Sym1 ys6989586621679113777 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679113778 :: NonEmpty a) = Lambda_6989586621679113780Sym2 ys6989586621679113777 xs6989586621679113778 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679113744Sym1 xs6989586621679113740 :: TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679113741 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113744Sym1 xs6989586621679113740 :: TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679113741 :: NonEmpty a) = Lambda_6989586621679113744Sym2 xs6989586621679113740 ys6989586621679113741 :: TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113124Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (is'6989586621679113123 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113124Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (is'6989586621679113123 :: NonEmpty a) = Lambda_6989586621679113124Sym1 is'6989586621679113123 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113121Sym2 rl6989586621679113118 is6989586621679113119 :: TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) (js6989586621679113120 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113121Sym2 rl6989586621679113118 is6989586621679113119 :: TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) (js6989586621679113120 :: NonEmpty a) = Lambda_6989586621679113121Sym3 rl6989586621679113118 is6989586621679113119 js6989586621679113120
type Apply (Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113437 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113437 :: Ix s) = Let6989586621679113436GoSym3 i6989586621679113434 r6989586621679113435 a6989586621679113437 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (Let6989586621679113127L'Sym1 js'6989586621679113126 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) (is'6989586621679113123 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113127L'Sym1 js'6989586621679113126 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) (is'6989586621679113123 :: NonEmpty a) = Let6989586621679113127L'Sym2 js'6989586621679113126 is'6989586621679113123 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113747Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (xs''6989586621679113746 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113747Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (xs''6989586621679113746 :: NonEmpty a) = Lambda_6989586621679113747Sym1 xs''6989586621679113746 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113769Sym2 xs6989586621679113766 xs'6989586621679113767 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys6989586621679113768 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113769Sym2 xs6989586621679113766 xs'6989586621679113767 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys6989586621679113768 :: NonEmpty a) = Lambda_6989586621679113769Sym3 xs6989586621679113766 xs'6989586621679113767 ys6989586621679113768
type Apply (Lambda_6989586621679113805Sym4 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679113799 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym4 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679113799 :: IList s) = Lambda_6989586621679113805Sym5 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799
type Apply (Lambda_6989586621679113744Sym3 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679113743 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113744Sym3 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679113743 :: NonEmpty a) = Lambda_6989586621679113744Sym4 xs6989586621679113740 ys6989586621679113741 xs'6989586621679113742 ys'6989586621679113743
type Apply (Lambda_6989586621679113805Sym5 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679113800 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym5 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679113800 :: [(VSpace s n, IList s)]) = Lambda_6989586621679113805Sym6 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798 yl6989586621679113799 ys6989586621679113800
type Apply (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113537 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113537 :: VSpace s n) = CanTransposeConSym1 a6989586621679113537
type Apply (CanTransposeCovSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113482 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113482 :: VSpace s n) = CanTransposeCovSym1 a6989586621679113482
type Apply (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113455 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113455 :: VSpace s n) = CanTransposeSym1 a6989586621679113455
type Apply (Lambda_6989586621679113805Sym0 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))))) -> Type) (xv6989586621679113795 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym0 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))))) -> Type) (xv6989586621679113795 :: VSpace s n) = Lambda_6989586621679113805Sym1 xv6989586621679113795
type Apply (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) (a6989586621679113156 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) (a6989586621679113156 :: VSpace s n) = RelabelRSym1 a6989586621679113156
type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679113361 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679113361 :: VSpace s n) = TranspositionsSym1 a6989586621679113361
type Apply (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113407 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113407 :: VSpace s n) = CanTransposeMultSym1 a6989586621679113407
type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679113410 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679113410 :: VSpace s n) = Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410
type Apply (Lambda_6989586621679113805Sym3 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679113798 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113805Sym3 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679113798 :: VSpace s n) = Lambda_6989586621679113805Sym4 xv6989586621679113795 xl6989586621679113796 xs6989586621679113797 yv6989586621679113798

The generalized tensor rank is a list of vector spaces and associated index lists. Sane generalized ranks have their vector spaces in ascending order.

type GRank s n = [(VSpace s n, IList s)] Source #

The specialisation used for the parameterisation of the tensor type.

As explained above, the contravariant or covariant indices for each vector space must be unique. They must also be sorted for more efficiency. The same applies for the vector spaces: Each distinct vector space must have a unique representation, generalized ranks are sorted by the vector spaces. This is checked by the function sane.

sane :: (Ord a, Ord b) => [(VSpace a b, IList a)] -> Bool Source #

The function headR extracts the first index within a generalized rank. The first index is always referring to the first vector space within the rank. If the rank is purely covariant or purley contravariant, the first index ist the first element of the respective index list. For mixed ranks, the first index is the one which compares less. If they compare equal, it is always the contravariant index. This defines an order where contractible indices always appear next to each other, which greatly facilitates contraction.

headR :: Ord s => GRank s n -> (VSpace s n, Ix s) Source #

The remaining rank after popping the headR is obtained by the function tailR.

tailR :: Ord s => GRank s n -> GRank s n Source #

The total number of indices.

lengthR :: GRank s n -> N Source #

A generalized rank is contracted by considering each vector space separately. Indices appearing in both upper and lower position are removed from the rank. If that leaves a vector space without indices, it is also discarded.

contractR :: Ord s => GRank s n -> GRank s n Source #

Merging two generalized ranks in order to obtain the generalized rank of the tensor product. Returns Nothing for incompatible ranks.

mergeR :: (Ord s, Ord n) => GRank s n -> GRank s n -> Maybe (GRank s n) Source #

To perform transpositions of two indices, single contravariant or covariant indices have to be specified. A representation for single indices is provided by the sum type Ix.

data Ix a Source #

Constructors

ICon a 
ICov a 

Instances

Instances details
NFData1 Ix Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

liftRnf :: (a -> ()) -> Ix a -> () #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

compare :: Ix a -> Ix a -> Ordering #

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

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

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

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

max :: Ix a -> Ix a -> Ix a #

min :: Ix a -> Ix a -> Ix a #

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

Defined in Math.Tensor.Safe.TH

Methods

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

show :: Ix a -> String #

showList :: [Ix a] -> ShowS #

Generic (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

rnf :: Ix a -> () #

PShow (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

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

Defined in Math.Tensor.Safe.TH

Methods

sShowsPrec :: forall (t1 :: Nat) (t2 :: Ix a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: Ix a). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [Ix a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

POrd (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

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

Defined in Math.Tensor.Safe.TH

Methods

sCompare :: forall (t1 :: Ix a) (t2 :: Ix a). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: forall (t1 :: Ix a) (t2 :: Ix a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: forall (t1 :: Ix a) (t2 :: Ix a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: forall (t1 :: Ix a) (t2 :: Ix a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: forall (t1 :: Ix a) (t2 :: Ix a). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: forall (t1 :: Ix a) (t2 :: Ix a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

sMin :: forall (t1 :: Ix a) (t2 :: Ix a). Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) #

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

Defined in Math.Tensor.Safe.TH

Methods

(%==) :: forall (a0 :: Ix a) (b :: Ix a). Sing a0 -> Sing b -> Sing (a0 == b) #

(%/=) :: forall (a0 :: Ix a) (b :: Ix a). Sing a0 -> Sing b -> Sing (a0 /= b) #

PEq (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

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

Defined in Math.Tensor.Safe.TH

Methods

(%~) :: forall (a0 :: Ix a) (b :: Ix a). Sing a0 -> Sing b -> Decision (a0 :~: b) #

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

Defined in Math.Tensor.Safe.TH

Associated Types

type Demote (Ix a) = (r :: Type) #

Methods

fromSing :: forall (a0 :: Ix a). Sing a0 -> Demote (Ix a) #

toSing :: Demote (Ix a) -> SomeSing (Ix a) #

Generic1 Ix Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Rep1 Ix :: k -> Type #

Methods

from1 :: forall (a :: k). Ix a -> Rep1 Ix a #

to1 :: forall (a :: k). Rep1 Ix a -> Ix a #

SDecide a => TestCoercion (SIx :: Ix a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testCoercion :: forall (a0 :: k) (b :: k). SIx a0 -> SIx b -> Maybe (Coercion a0 b) #

SDecide a => TestEquality (SIx :: Ix a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testEquality :: forall (a0 :: k) (b :: k). SIx a0 -> SIx b -> Maybe (a0 :~: b) #

SingI n => SingI ('ICon n :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('ICon n) #

SingI n => SingI ('ICov n :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('ICov n) #

SuppressUnusedWarnings (ShowsPrec_6989586621679117782Sym0 :: TyFun Nat (Ix a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (IxCompareSym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679117803Sym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (IConSym0 :: TyFun a (Ix a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ICovSym0 :: TyFun a (Ix a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (IxCompareSym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (ICovSym0 :: TyFun a (Ix a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ICovSym0 #

SingI (IConSym0 :: TyFun a (Ix a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing IConSym0 #

SuppressUnusedWarnings (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (IxCompareSym1 a6989586621679113942 :: TyFun (Ix a) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679117782Sym1 a6989586621679117792 :: TyFun (Ix a) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679117803Sym1 a6989586621679117808 :: TyFun (Ix a) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd s => SingI (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing HeadRSym0 #

(SOrd s, SOrd n) => SingI (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd s => SingI (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd a, SingI d) => SingI (IxCompareSym1 d :: TyFun (Ix a) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (IxCompareSym1 d) #

SuppressUnusedWarnings (CanTransposeSym1 a6989586621679113455 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113436GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d) => SingI (CanTransposeSym1 d :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym1 d) #

SuppressUnusedWarnings (CanTransposeSym2 a6989586621679113455 a6989586621679113456 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (CanTransposeSym2 d1 d2 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym2 d1 d2) #

SuppressUnusedWarnings (Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IConSym0 :: TyFun a (Ix a) -> Type) (a6989586621679112981 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IConSym0 :: TyFun a (Ix a) -> Type) (a6989586621679112981 :: a) = IConSym1 a6989586621679112981
type Apply (ICovSym0 :: TyFun a (Ix a) -> Type) (a6989586621679112983 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ICovSym0 :: TyFun a (Ix a) -> Type) (a6989586621679112983 :: a) = ICovSym1 a6989586621679112983
type Apply (ShowsPrec_6989586621679117782Sym0 :: TyFun Nat (Ix a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679117792 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679117782Sym0 :: TyFun Nat (Ix a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679117792 :: Nat) = ShowsPrec_6989586621679117782Sym1 a6989586621679117792 :: TyFun (Ix a) (Symbol ~> Symbol) -> Type
type Apply (Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679113435 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679113435 :: k) = Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type
type Rep (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep (Ix a) = D1 ('MetaData "Ix" "Math.Tensor.Safe.TH" "safe-tensor-0.2.1.0-inplace" 'False) (C1 ('MetaCons "ICon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "ICov" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Sing Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing = SIx :: Ix a -> Type
type Demote (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Demote (Ix a) = Ix (Demote a)
type Rep1 Ix Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep1 Ix = D1 ('MetaData "Ix" "Math.Tensor.Safe.TH" "safe-tensor-0.2.1.0-inplace" 'False) (C1 ('MetaCons "ICon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1) :+: C1 ('MetaCons "ICov" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Show_ (arg :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: Ix a) = Apply (Show__6989586621680635830Sym0 :: TyFun (Ix a) Symbol -> Type) arg
type ShowList (arg :: [Ix a]) arg1 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type ShowList (arg :: [Ix a]) arg1 = Apply (Apply (ShowList_6989586621680635838Sym0 :: TyFun [Ix a] (Symbol ~> Symbol) -> Type) arg) arg1
type Min (arg :: Ix a) (arg1 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Min (arg :: Ix a) (arg1 :: Ix a) = Apply (Apply (Min_6989586621679837319Sym0 :: TyFun (Ix a) (Ix a ~> Ix a) -> Type) arg) arg1
type Max (arg :: Ix a) (arg1 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Max (arg :: Ix a) (arg1 :: Ix a) = Apply (Apply (Max_6989586621679837303Sym0 :: TyFun (Ix a) (Ix a ~> Ix a) -> Type) arg) arg1
type (arg :: Ix a) >= (arg1 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: Ix a) >= (arg1 :: Ix a) = Apply (Apply (TFHelper_6989586621679837287Sym0 :: TyFun (Ix a) (Ix a ~> Bool) -> Type) arg) arg1
type (arg :: Ix a) > (arg1 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: Ix a) > (arg1 :: Ix a) = Apply (Apply (TFHelper_6989586621679837271Sym0 :: TyFun (Ix a) (Ix a ~> Bool) -> Type) arg) arg1
type (arg :: Ix a) <= (arg1 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: Ix a) <= (arg1 :: Ix a) = Apply (Apply (TFHelper_6989586621679837255Sym0 :: TyFun (Ix a) (Ix a ~> Bool) -> Type) arg) arg1
type (arg :: Ix a) < (arg1 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: Ix a) < (arg1 :: Ix a) = Apply (Apply (TFHelper_6989586621679837239Sym0 :: TyFun (Ix a) (Ix a ~> Bool) -> Type) arg) arg1
type Compare (a2 :: Ix a1) (a3 :: Ix a1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Compare (a2 :: Ix a1) (a3 :: Ix a1) = Apply (Apply (Compare_6989586621679117803Sym0 :: TyFun (Ix a1) (Ix a1 ~> Ordering) -> Type) a2) a3
type (x :: Ix a) /= (y :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (x :: Ix a) /= (y :: Ix a) = Not (x == y)
type (a2 :: Ix a1) == (b :: Ix a1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (a2 :: Ix a1) == (b :: Ix a1) = Equals_6989586621679117897 a2 b
type ShowsPrec a2 (a3 :: Ix a1) a4 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type ShowsPrec a2 (a3 :: Ix a1) a4 = Apply (Apply (Apply (ShowsPrec_6989586621679117782Sym0 :: TyFun Nat (Ix a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (IxCompareSym1 a6989586621679113942 :: TyFun (Ix a) Ordering -> Type) (a6989586621679113943 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IxCompareSym1 a6989586621679113942 :: TyFun (Ix a) Ordering -> Type) (a6989586621679113943 :: Ix a) = IxCompareSym2 a6989586621679113942 a6989586621679113943
type Apply (Compare_6989586621679117803Sym1 a6989586621679117808 :: TyFun (Ix a) Ordering -> Type) (a6989586621679117809 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679117803Sym1 a6989586621679117808 :: TyFun (Ix a) Ordering -> Type) (a6989586621679117809 :: Ix a) = Compare_6989586621679117803Sym2 a6989586621679117808 a6989586621679117809
type Apply (IxCompareSym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679113942 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IxCompareSym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679113942 :: Ix a) = IxCompareSym1 a6989586621679113942
type Apply (Compare_6989586621679117803Sym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679117808 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679117803Sym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679117808 :: Ix a) = Compare_6989586621679117803Sym1 a6989586621679117808
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679113871 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679113871 :: [(VSpace s n, IList s)]) = HeadRSym1 a6989586621679113871
type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113432 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113432 :: Ix s) = RemoveUntilSym1 a6989586621679113432 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (ShowsPrec_6989586621679117782Sym1 a6989586621679117792 :: TyFun (Ix a) (Symbol ~> Symbol) -> Type) (a6989586621679117793 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679117782Sym1 a6989586621679117792 :: TyFun (Ix a) (Symbol ~> Symbol) -> Type) (a6989586621679117793 :: Ix a) = ShowsPrec_6989586621679117782Sym2 a6989586621679117792 a6989586621679117793
type Apply (CanTransposeSym1 a6989586621679113455 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113456 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679113455 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113456 :: Ix s) = CanTransposeSym2 a6989586621679113455 a6989586621679113456
type Apply (Let6989586621679113436GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679113434 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113436GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679113434 :: Ix s) = Let6989586621679113436GoSym1 i6989586621679113434 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type
type Apply (CanTransposeSym2 a6989586621679113455 a6989586621679113456 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113457 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679113455 a6989586621679113456 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113457 :: Ix s) = CanTransposeSym3 a6989586621679113455 a6989586621679113456 a6989586621679113457
type Apply (Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113437 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113436GoSym2 i6989586621679113434 r6989586621679113435 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679113437 :: Ix s) = Let6989586621679113436GoSym3 i6989586621679113434 r6989586621679113435 a6989586621679113437 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113455 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679113455 :: VSpace s n) = CanTransposeSym1 a6989586621679113455

To perform transpositions of multiple indices at once, a list of source and a list of target indices has to be provided. Both lists must be permutations of each other. A suitable representation is provided by the sum type TransRule.

Note that transposing indices in a tensor does not change its generalized rank.

data TransRule a Source #

Constructors

TransCon (NonEmpty a) (NonEmpty a) 
TransCov (NonEmpty a) (NonEmpty a) 

Instances

Instances details
NFData1 TransRule Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

liftRnf :: (a -> ()) -> TransRule a -> () #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Generic (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

NFData a => NFData (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

rnf :: TransRule a -> () #

PShow (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

SShow (NonEmpty a) => SShow (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sShowsPrec :: forall (t1 :: Nat) (t2 :: TransRule a) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: TransRule a). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [TransRule a]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

SEq (NonEmpty a) => SEq (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(%==) :: forall (a0 :: TransRule a) (b :: TransRule a). Sing a0 -> Sing b -> Sing (a0 == b) #

(%/=) :: forall (a0 :: TransRule a) (b :: TransRule a). Sing a0 -> Sing b -> Sing (a0 /= b) #

PEq (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

SDecide (NonEmpty a) => SDecide (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(%~) :: forall (a0 :: TransRule a) (b :: TransRule a). Sing a0 -> Sing b -> Decision (a0 :~: b) #

SingKind a => SingKind (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Demote (TransRule a) = (r :: Type) #

Methods

fromSing :: forall (a0 :: TransRule a). Sing a0 -> Demote (TransRule a) #

toSing :: Demote (TransRule a) -> SomeSing (TransRule a) #

Generic1 TransRule Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Rep1 TransRule :: k -> Type #

Methods

from1 :: forall (a :: k). TransRule a -> Rep1 TransRule a #

to1 :: forall (a :: k). Rep1 TransRule a -> TransRule a #

SDecide (NonEmpty a) => TestCoercion (STransRule :: TransRule a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testCoercion :: forall (a0 :: k) (b :: k). STransRule a0 -> STransRule b -> Maybe (Coercion a0 b) #

SDecide (NonEmpty a) => TestEquality (STransRule :: TransRule a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testEquality :: forall (a0 :: k) (b :: k). STransRule a0 -> STransRule b -> Maybe (a0 :~: b) #

(SingI n1, SingI n2) => SingI ('TransCon n1 n2 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('TransCon n1 n2) #

(SingI n1, SingI n2) => SingI ('TransCov n1 n2 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('TransCov n1 n2) #

SuppressUnusedWarnings (ShowsPrec_6989586621679117862Sym0 :: TyFun Nat (TransRule a ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (SaneTransRuleSym0 :: TyFun (TransRule a) Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransConSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (SaneTransRuleSym0 :: TyFun (TransRule a) Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (TransCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (TransConSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679117862Sym1 a6989586621679117872 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransConSym1 a6989586621679112992 :: TyFun (NonEmpty a) (TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransCovSym1 a6989586621679112995 :: TyFun (NonEmpty a) (TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI d => SingI (TransCovSym1 d :: TyFun (NonEmpty a) (TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TransCovSym1 d) #

SingI d => SingI (TransConSym1 d :: TyFun (NonEmpty a) (TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TransConSym1 d) #

SuppressUnusedWarnings (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym1 a6989586621679113407 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d) => SingI (TranspositionsSym1 d :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d) => SingI (CanTransposeMultSym1 d :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113369Scrutinee_6989586621679107350Sym0 :: TyFun k1 (TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113369Scrutinee_6989586621679107350Sym1 vs6989586621679113364 :: TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679117862Sym0 :: TyFun Nat (TransRule a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679117872 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679117862Sym0 :: TyFun Nat (TransRule a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679117872 :: Nat) = ShowsPrec_6989586621679117862Sym1 a6989586621679117872 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type
type Apply (Let6989586621679113369Scrutinee_6989586621679107350Sym0 :: TyFun k1 (TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (vs6989586621679113364 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113369Scrutinee_6989586621679107350Sym0 :: TyFun k1 (TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (vs6989586621679113364 :: k1) = Let6989586621679113369Scrutinee_6989586621679107350Sym1 vs6989586621679113364 :: TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type
type Rep (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing = STransRule :: TransRule a -> Type
type Demote (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep1 TransRule Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: TransRule a) = Apply (Show__6989586621680635830Sym0 :: TyFun (TransRule a) Symbol -> Type) arg
type ShowList (arg :: [TransRule a]) arg1 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type ShowList (arg :: [TransRule a]) arg1 = Apply (Apply (ShowList_6989586621680635838Sym0 :: TyFun [TransRule a] (Symbol ~> Symbol) -> Type) arg) arg1
type (x :: TransRule a) /= (y :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (x :: TransRule a) /= (y :: TransRule a) = Not (x == y)
type (a2 :: TransRule a1) == (b :: TransRule a1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (a2 :: TransRule a1) == (b :: TransRule a1) = Equals_6989586621679117917 a2 b
type ShowsPrec a2 (a3 :: TransRule a1) a4 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (SaneTransRuleSym0 :: TyFun (TransRule a) Bool -> Type) (a6989586621679113420 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (SaneTransRuleSym0 :: TyFun (TransRule a) Bool -> Type) (a6989586621679113420 :: TransRule a) = SaneTransRuleSym1 a6989586621679113420
type Apply (TransConSym1 a6989586621679112992 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679112993 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransConSym1 a6989586621679112992 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679112993 :: NonEmpty a) = TransConSym2 a6989586621679112992 a6989586621679112993
type Apply (TransCovSym1 a6989586621679112995 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679112996 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransCovSym1 a6989586621679112995 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679112996 :: NonEmpty a) = TransCovSym2 a6989586621679112995 a6989586621679112996
type Apply (TransConSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) (a6989586621679112992 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransConSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) (a6989586621679112992 :: NonEmpty a) = TransConSym1 a6989586621679112992
type Apply (TransCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) (a6989586621679112995 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) (a6989586621679112995 :: NonEmpty a) = TransCovSym1 a6989586621679112995
type Apply (ShowsPrec_6989586621679117862Sym1 a6989586621679117872 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type) (a6989586621679117873 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679117862Sym1 a6989586621679117872 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type) (a6989586621679117873 :: TransRule a) = ShowsPrec_6989586621679117862Sym2 a6989586621679117872 a6989586621679117873
type Apply (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679113362 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679113362 :: TransRule s) = TranspositionsSym2 a6989586621679113361 a6989586621679113362
type Apply (CanTransposeMultSym1 a6989586621679113407 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113408 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679113407 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679113408 :: TransRule s) = CanTransposeMultSym2 a6989586621679113407 a6989586621679113408
type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679113411 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679113411 :: TransRule s) = Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411
type Apply (Let6989586621679113369Scrutinee_6989586621679107350Sym1 vs6989586621679113364 :: TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (tl6989586621679113365 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113369Scrutinee_6989586621679107350Sym1 vs6989586621679113364 :: TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (tl6989586621679113365 :: TransRule a) = Let6989586621679113369Scrutinee_6989586621679107350Sym2 vs6989586621679113364 tl6989586621679113365 :: TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type
type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679113361 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679113361 :: VSpace s n) = TranspositionsSym1 a6989586621679113361
type Apply (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113407 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679113407 :: VSpace s n) = CanTransposeMultSym1 a6989586621679113407
type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679113410 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679113410 :: VSpace s n) = Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410

To relabel a tensor, a list of source-target pairs has to be provided. Relabelling affects each index regardless of upper or lower position, so it suffices to have the type synonym RelabelRule.

type RelabelRule s = NonEmpty (s, s) Source #

Relabelling a tensor changes its generalized rank. If tensor indices corresponding to a given vector space can be relabelled using a given RelabelRule, relabelR returns the new generalized rank. Otherwise, it returns Nothing.

relabelR :: (Ord s, Ord n) => VSpace s n -> RelabelRule s -> GRank s n -> Maybe (GRank s n) Source #

The Tensor GADT

The Tensor type parameterised by a generalized rank r and a value type v is a recursive container for tensor components of value v.

  • The base case is a Scalar, which represents a tensor with empty rank. A scalar holds a single value of type v.
  • For non-empty ranks, a tensor is represented of as a mapping from all possible index values for the first index headR r to tensors of lower rank tailR r, implemented as sparse ascending assocs list (omitting zero values).
  • There is a shortcut for zero tensors, which are represented as ZeroTensor regardless of the generalized rank.

Generalized ranks must be Sane. The empty rank '[] is always sane.

data Tensor :: Rank -> Type -> Type where Source #

The Tensor type parameterized by its generalized rank r and arbitrary value type v.

Constructors

ZeroTensor :: forall (r :: Rank) v. Sane r ~ 'True => Tensor r v 
Scalar :: forall v. !v -> Tensor '[] v 
Tensor :: forall (r :: Rank) (r' :: Rank) v. (Sane r ~ 'True, TailR r ~ r') => [(Int, Tensor r' v)] -> Tensor r v 

Instances

Instances details
Functor (Tensor r) Source # 
Instance details

Defined in Math.Tensor.Safe

Methods

fmap :: (a -> b) -> Tensor r a -> Tensor r b #

(<$) :: a -> Tensor r b -> Tensor r a #

Eq v => Eq (Tensor r v) Source # 
Instance details

Defined in Math.Tensor.Safe

Methods

(==) :: Tensor r v -> Tensor r v -> Bool #

(/=) :: Tensor r v -> Tensor r v -> Bool #

Show v => Show (Tensor r v) Source # 
Instance details

Defined in Math.Tensor.Safe

Methods

showsPrec :: Int -> Tensor r v -> ShowS #

show :: Tensor r v -> String #

showList :: [Tensor r v] -> ShowS #

NFData v => NFData (Tensor r v) Source # 
Instance details

Defined in Math.Tensor.Safe

Methods

rnf :: Tensor r v -> () #

Conversion from and to lists

A Tensor r v can be constructed from a list of key-value pairs, where keys are length-typed vectors Vec of n = lengthR r indices and values are the corresponding components.

The index values must be given in the order defined by repeatedly applying headR to the rank.

Given a value, such an assocs list is obtained by toList.

fromList :: forall r v n. (SingI r, Sane r ~ 'True, LengthR r ~ n) => [(Vec n Int, v)] -> Tensor r v Source #

Construct Tensor from assocs list. Keys are length-typed vectors of indices.

fromList' :: forall r v n. (Sane r ~ 'True, LengthR r ~ n) => Sing r -> [(Vec n Int, v)] -> Tensor r v Source #

Construct Tensor from assocs list. Keys are length-typed vectors of indices. Generalized rank is passed explicitly as singleton.

toList :: forall r v n. (SingI r, SingI n, LengthR r ~ n) => Tensor r v -> [(Vec n Int, v)] Source #

Get assocs list from Tensor. Keys are length-typed vectors of indices.

Basic operations

We have now everything at our disposal to define basic tensor operations using the rank-parameterised Tensor type. These operations (algebra, contraction, transposition, relabelling) are safe in the sense that they can only be performed between tensors of matching type and the type of the resulting tensor is predetermined. There is also an existentially quantified variant of these operations available from Math.Tensor.

Tensor algebra

(&+) :: forall (r :: Rank) (r' :: Rank) v. (r ~ r', Num v, Eq v) => Tensor r v -> Tensor r' v -> Tensor r v infixl 6 Source #

Tensor addition. Generalized ranks of summands and sum coincide. Zero values are removed from the result.

(&-) :: forall (r :: Rank) (r' :: Rank) v. (r ~ r', Num v, Eq v) => Tensor r v -> Tensor r' v -> Tensor r v infixl 6 Source #

Tensor subtraction. Generalized ranks of operands and difference coincide. Zero values are removed from the result.

(&*) :: forall (r :: Rank) (r' :: Rank) (r'' :: Rank) v. (Num v, 'Just r'' ~ MergeR r r', SingI r, SingI r') => Tensor r v -> Tensor r' v -> Tensor r'' v infixl 7 Source #

Tensor multiplication. Generalized anks r, r' of factors must not overlap. The product rank is the merged rank MergeR r r' of the factor ranks.

removeZeros :: (Num v, Eq v) => Tensor r v -> Tensor r v Source #

Given a Num and Eq instance, remove all zero values from the tensor, eventually replacing a zero Scalar or an empty Tensor with ZeroTensor.

Contraction

contract :: forall (r :: Rank) (r' :: Rank) v. (r' ~ ContractR r, SingI r, Num v, Eq v) => Tensor r v -> Tensor r' v Source #

Tensor contraction. Contracting a tensor is the identity function on non-contractible tensors. Otherwise, the result is the contracted tensor with the contracted labels removed from the generalized rank.

Transpositions

transpose :: forall (vs :: VSpace Symbol Nat) (a :: Ix Symbol) (b :: Ix Symbol) (r :: Rank) v. (CanTranspose vs a b r ~ 'True, SingI r) => Sing vs -> Sing a -> Sing b -> Tensor r v -> Tensor r v Source #

Tensor transposition. Given a vector space and two index labels, the result is a tensor with the corresponding entries swapped. Only possible if the indices are part of the rank. The generalized rank remains untouched.

transposeMult :: forall (vs :: VSpace Symbol Nat) (tl :: TransRule Symbol) (r :: Rank) v. (IsJust (Transpositions vs tl r) ~ 'True, SingI r) => Sing vs -> Sing tl -> Tensor r v -> Tensor r v Source #

Transposition of multiple labels. Given a vector space and a transposition rule, the result is a tensor with the corresponding entries swapped. Only possible if the indices are part of the generalized rank. The generalized rank remains untouched.

Relabelling

relabel :: forall (vs :: VSpace Symbol Nat) (rl :: RelabelRule Symbol) (r1 :: Rank) (r2 :: Rank) v. (RelabelR vs rl r1 ~ 'Just r2, Sane r2 ~ 'True, SingI r1, SingI r2) => Sing vs -> Sing rl -> Tensor r1 v -> Tensor r2 v Source #

Tensor relabelling. Given a vector space and a relabelling rule, the result is a tensor with the resulting generalized rank after relabelling. Only possible if labels to be renamed are part of the generalized rank and if uniqueness of labels after relabelling is preserved.

Length-typed vectors

Type-level naturals used for tensor construction and also internally.

data N where Source #

Constructors

Z :: N 
S :: N -> N 

Instances

Instances details
Eq N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(==) :: N -> N -> Bool #

(/=) :: N -> N -> Bool #

Num N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(+) :: N -> N -> N #

(-) :: N -> N -> N #

(*) :: N -> N -> N #

negate :: N -> N #

abs :: N -> N #

signum :: N -> N #

fromInteger :: Integer -> N #

Ord N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

compare :: N -> N -> Ordering #

(<) :: N -> N -> Bool #

(<=) :: N -> N -> Bool #

(>) :: N -> N -> Bool #

(>=) :: N -> N -> Bool #

max :: N -> N -> N #

min :: N -> N -> N #

Show N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

showsPrec :: Int -> N -> ShowS #

show :: N -> String #

showList :: [N] -> ShowS #

Generic N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Rep N :: Type -> Type #

Methods

from :: N -> Rep N x #

to :: Rep N x -> N #

NFData N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

rnf :: N -> () #

PShow N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

SShow N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sShowsPrec :: forall (t1 :: Nat) (t2 :: N) (t3 :: Symbol). Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: forall (t :: N). Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: forall (t1 :: [N]) (t2 :: Symbol). Sing t1 -> Sing t2 -> Sing (Apply (Apply ShowListSym0 t1) t2) #

PNum N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type arg + arg1 :: a #

type arg - arg1 :: a #

type arg * arg1 :: a #

type Negate arg :: a #

type Abs arg :: a #

type Signum arg :: a #

type FromInteger arg :: a #

SNum N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(%+) :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply (+@#@$) t1) t2) #

(%-) :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply (-@#@$) t1) t2) #

(%*) :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply (*@#@$) t1) t2) #

sNegate :: forall (t :: N). Sing t -> Sing (Apply NegateSym0 t) #

sAbs :: forall (t :: N). Sing t -> Sing (Apply AbsSym0 t) #

sSignum :: forall (t :: N). Sing t -> Sing (Apply SignumSym0 t) #

sFromInteger :: forall (t :: Nat). Sing t -> Sing (Apply FromIntegerSym0 t) #

POrd N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

SOrd N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sCompare :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

sMin :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) #

SEq N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(%==) :: forall (a :: N) (b :: N). Sing a -> Sing b -> Sing (a == b) #

(%/=) :: forall (a :: N) (b :: N). Sing a -> Sing b -> Sing (a /= b) #

PEq N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

SDecide N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(%~) :: forall (a :: N) (b :: N). Sing a -> Sing b -> Decision (a :~: b) #

SingKind N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Demote N = (r :: Type) #

Methods

fromSing :: forall (a :: N). Sing a -> Demote N #

toSing :: Demote N -> SomeSing N #

TestCoercion SN Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testCoercion :: forall (a :: k) (b :: k). SN a -> SN b -> Maybe (Coercion a b) #

TestEquality SN Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testEquality :: forall (a :: k) (b :: k). SN a -> SN b -> Maybe (a :~: b) #

SingI 'Z Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing 'Z #

SingI n => SingI ('S n :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('S n) #

SuppressUnusedWarnings FromInteger_6989586621679117735Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings FromNatSym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings ShowsPrec_6989586621679115969Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Signum_6989586621679117728Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Abs_6989586621679117721Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Negate_6989586621679117704Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings SSym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679117270Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679117711Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679117693Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679117681Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI FromNatSym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI SSym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing SSym0 #

SuppressUnusedWarnings (TFHelper_6989586621679117270Sym1 a6989586621679117275 :: TyFun N Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679117711Sym1 a6989586621679117716 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679117693Sym1 a6989586621679117698 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679117681Sym1 a6989586621679117686 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679115969Sym1 a6989586621679115979 :: TyFun N (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (LengthILSym0 :: TyFun (IList a) N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelTranspositions'Sym0 :: TyFun (NonEmpty (a, a)) [(N, N)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Transpositions'Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> (NonEmpty (Maybe a) ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (LengthNESym0 :: TyFun (NonEmpty a) N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (LengthILSym0 :: TyFun (IList a) N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (RelabelTranspositions'Sym0 :: TyFun (NonEmpty (a, a)) [(N, N)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SEq a => SingI (Transpositions'Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> (NonEmpty (Maybe a) ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (LengthNESym0 :: TyFun (NonEmpty a) N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelTranspositionsSym1 a6989586621679113078 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113001Is'''Sym0 :: TyFun (NonEmpty (a6989586621679107207, b6989586621679107210)) (NonEmpty (N, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113001Is''Sym0 :: TyFun (NonEmpty (a6989586621679107207, k1)) (NonEmpty (N, k1)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113001Is'Sym0 :: TyFun (NonEmpty (a6989586621679107207, b6989586621679107208)) (NonEmpty (N, b6989586621679107208)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Transpositions'Sym1 a6989586621679113245 :: TyFun (NonEmpty a) (NonEmpty (Maybe a) ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n) => SingI (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd a, SingI d) => SingI (RelabelTranspositionsSym1 d :: TyFun (IList a) (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SEq a, SingI d) => SingI (Transpositions'Sym1 d :: TyFun (NonEmpty a) (NonEmpty (Maybe a) ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113001Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679107209, b6989586621679107210) ~> NonEmpty (a6989586621679107209, N)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113001GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679107207, b6989586621679107208) ~> NonEmpty (N, b6989586621679107208)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251Xs'Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113293Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113297Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Transpositions'Sym2 a6989586621679113245 a6989586621679113246 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d) => SingI (TranspositionsSym1 d :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SEq a, SingI d1, SingI d2) => SingI (Transpositions'Sym2 d1 d2 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (Transpositions'Sym2 d1 d2) #

SuppressUnusedWarnings (TranspositionsSym2 a6989586621679113361 a6989586621679113362 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113001Go'Sym1 is6989586621679113000 :: TyFun N (NonEmpty (a6989586621679107209, b6989586621679107210) ~> NonEmpty (a6989586621679107209, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113001GoSym1 is6989586621679113000 :: TyFun N (NonEmpty (a6989586621679107207, b6989586621679107208) ~> NonEmpty (N, b6989586621679107208)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251FindSym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251Go'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251Xs'Sym1 sources6989586621679113248 :: TyFun k2 (TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113293Sym1 sources6989586621679113248 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113300Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113297Sym1 sources6989586621679113248 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SOrd n, SingI d1, SingI d2) => SingI (TranspositionsSym2 d1 d2 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TranspositionsSym2 d1 d2) #

SuppressUnusedWarnings (Let6989586621679113251FindSym1 sources6989586621679113248 :: TyFun k2 (TyFun k3 (TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251Go'Sym1 sources6989586621679113248 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113300Sym1 ss6989586621679113299 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113293Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113297Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113001Go'Sym2 is6989586621679113000 a6989586621679113010 :: TyFun (NonEmpty (a6989586621679107209, b6989586621679107210)) (NonEmpty (a6989586621679107209, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113001GoSym2 is6989586621679113000 a6989586621679113019 :: TyFun (NonEmpty (a6989586621679107207, b6989586621679107208)) (NonEmpty (N, b6989586621679107208)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251Xs'Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251FindSym2 sources6989586621679113248 targets6989586621679113249 :: TyFun k3 (TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251Go'Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun k3 (TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113293Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun k3 (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113300Sym2 ss6989586621679113299 sources6989586621679113248 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113297Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251Go'Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251FindSym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113300Sym3 ss6989586621679113299 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679113300Sym4 ss6989586621679113299 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun k4 (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251FindSym4 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 a6989586621679113263 :: TyFun (NonEmpty (N, Maybe a6989586621679107110)) (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679113251Go'Sym4 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 a6989586621679113283 :: TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep N = D1 ('MetaData "N" "Math.Tensor.Safe.TH" "safe-tensor-0.2.1.0-inplace" 'False) (C1 ('MetaCons "Z" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "S" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 N)))
type Sing Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing = SN
type Demote N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Demote N = N
type Show_ (arg :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: N) = Apply (Show__6989586621680635830Sym0 :: TyFun N Symbol -> Type) arg
type FromInteger a Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Signum (a :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Abs (a :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Negate (a :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type ShowList (arg :: [N]) arg1 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type ShowList (arg :: [N]) arg1 = Apply (Apply (ShowList_6989586621680635838Sym0 :: TyFun [N] (Symbol ~> Symbol) -> Type) arg) arg1
type (a1 :: N) * (a2 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (a1 :: N) * (a2 :: N) = Apply (Apply TFHelper_6989586621679117711Sym0 a1) a2
type (a1 :: N) - (a2 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (a1 :: N) - (a2 :: N) = Apply (Apply TFHelper_6989586621679117693Sym0 a1) a2
type (a1 :: N) + (a2 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (a1 :: N) + (a2 :: N) = Apply (Apply TFHelper_6989586621679117681Sym0 a1) a2
type Min (arg :: N) (arg1 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Min (arg :: N) (arg1 :: N) = Apply (Apply (Min_6989586621679837319Sym0 :: TyFun N (N ~> N) -> Type) arg) arg1
type Max (arg :: N) (arg1 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Max (arg :: N) (arg1 :: N) = Apply (Apply (Max_6989586621679837303Sym0 :: TyFun N (N ~> N) -> Type) arg) arg1
type (arg :: N) >= (arg1 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: N) >= (arg1 :: N) = Apply (Apply (TFHelper_6989586621679837287Sym0 :: TyFun N (N ~> Bool) -> Type) arg) arg1
type (arg :: N) > (arg1 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: N) > (arg1 :: N) = Apply (Apply (TFHelper_6989586621679837271Sym0 :: TyFun N (N ~> Bool) -> Type) arg) arg1
type (a1 :: N) <= (a2 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (a1 :: N) <= (a2 :: N) = Apply (Apply TFHelper_6989586621679117270Sym0 a1) a2
type (arg :: N) < (arg1 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: N) < (arg1 :: N) = Apply (Apply (TFHelper_6989586621679837239Sym0 :: TyFun N (N ~> Bool) -> Type) arg) arg1
type Compare (arg :: N) (arg1 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Compare (arg :: N) (arg1 :: N) = Apply (Apply (Compare_6989586621679837218Sym0 :: TyFun N (N ~> Ordering) -> Type) arg) arg1
type (x :: N) /= (y :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (x :: N) /= (y :: N) = Not (x == y)
type (a :: N) == (b :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (a :: N) == (b :: N) = Equals_6989586621679117883 a b
type ShowsPrec a1 (a2 :: N) a3 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type ShowsPrec a1 (a2 :: N) a3 = Apply (Apply (Apply ShowsPrec_6989586621679115969Sym0 a1) a2) a3
type Apply FromInteger_6989586621679117735Sym0 (a6989586621679117739 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply FromInteger_6989586621679117735Sym0 (a6989586621679117739 :: Nat) = FromInteger_6989586621679117735Sym1 a6989586621679117739
type Apply FromNatSym0 (a6989586621679113964 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply FromNatSym0 (a6989586621679113964 :: Nat) = FromNatSym1 a6989586621679113964
type Apply Signum_6989586621679117728Sym0 (a6989586621679117732 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Signum_6989586621679117728Sym0 (a6989586621679117732 :: N) = Signum_6989586621679117728Sym1 a6989586621679117732
type Apply Abs_6989586621679117721Sym0 (a6989586621679117725 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Abs_6989586621679117721Sym0 (a6989586621679117725 :: N) = Abs_6989586621679117721Sym1 a6989586621679117725
type Apply Negate_6989586621679117704Sym0 (a6989586621679117708 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Negate_6989586621679117704Sym0 (a6989586621679117708 :: N) = Negate_6989586621679117704Sym1 a6989586621679117708
type Apply SSym0 (a6989586621679112975 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply SSym0 (a6989586621679112975 :: N) = SSym1 a6989586621679112975
type Apply (TFHelper_6989586621679117270Sym1 a6989586621679117275 :: TyFun N Bool -> Type) (a6989586621679117276 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679117270Sym1 a6989586621679117275 :: TyFun N Bool -> Type) (a6989586621679117276 :: N) = TFHelper_6989586621679117270Sym2 a6989586621679117275 a6989586621679117276
type Apply (TFHelper_6989586621679117711Sym1 a6989586621679117716 :: TyFun N N -> Type) (a6989586621679117717 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679117711Sym1 a6989586621679117716 :: TyFun N N -> Type) (a6989586621679117717 :: N) = TFHelper_6989586621679117711Sym2 a6989586621679117716 a6989586621679117717
type Apply (TFHelper_6989586621679117693Sym1 a6989586621679117698 :: TyFun N N -> Type) (a6989586621679117699 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679117693Sym1 a6989586621679117698 :: TyFun N N -> Type) (a6989586621679117699 :: N) = TFHelper_6989586621679117693Sym2 a6989586621679117698 a6989586621679117699
type Apply (TFHelper_6989586621679117681Sym1 a6989586621679117686 :: TyFun N N -> Type) (a6989586621679117687 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679117681Sym1 a6989586621679117686 :: TyFun N N -> Type) (a6989586621679117687 :: N) = TFHelper_6989586621679117681Sym2 a6989586621679117686 a6989586621679117687
type Apply (Lambda_6989586621679113293Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun k3 (Maybe N) -> Type) (lhs_69895866216791073766989586621679113295 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113293Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun k3 (Maybe N) -> Type) (lhs_69895866216791073766989586621679113295 :: k3) = Lambda_6989586621679113293Sym4 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 lhs_69895866216791073766989586621679113295
type Apply (Lambda_6989586621679113300Sym4 ss6989586621679113299 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun k4 (Maybe N) -> Type) (lhs_69895866216791073746989586621679113302 :: k4) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113300Sym4 ss6989586621679113299 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun k4 (Maybe N) -> Type) (lhs_69895866216791073746989586621679113302 :: k4) = Lambda_6989586621679113300Sym5 ss6989586621679113299 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 lhs_69895866216791073746989586621679113302
type Apply ShowsPrec_6989586621679115969Sym0 (a6989586621679115979 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply ShowsPrec_6989586621679115969Sym0 (a6989586621679115979 :: Nat) = ShowsPrec_6989586621679115969Sym1 a6989586621679115979
type Apply TFHelper_6989586621679117270Sym0 (a6989586621679117275 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679117270Sym0 (a6989586621679117275 :: N) = TFHelper_6989586621679117270Sym1 a6989586621679117275
type Apply TFHelper_6989586621679117711Sym0 (a6989586621679117716 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679117711Sym0 (a6989586621679117716 :: N) = TFHelper_6989586621679117711Sym1 a6989586621679117716
type Apply TFHelper_6989586621679117693Sym0 (a6989586621679117698 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679117693Sym0 (a6989586621679117698 :: N) = TFHelper_6989586621679117693Sym1 a6989586621679117698
type Apply TFHelper_6989586621679117681Sym0 (a6989586621679117686 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679117681Sym0 (a6989586621679117686 :: N) = TFHelper_6989586621679117681Sym1 a6989586621679117686
type Apply (ShowsPrec_6989586621679115969Sym1 a6989586621679115979 :: TyFun N (Symbol ~> Symbol) -> Type) (a6989586621679115980 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679115969Sym1 a6989586621679115979 :: TyFun N (Symbol ~> Symbol) -> Type) (a6989586621679115980 :: N) = ShowsPrec_6989586621679115969Sym2 a6989586621679115979 a6989586621679115980
type Apply (Let6989586621679113001Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679107209, b6989586621679107210) ~> NonEmpty (a6989586621679107209, N)) -> Type) -> Type) (is6989586621679113000 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113001Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679107209, b6989586621679107210) ~> NonEmpty (a6989586621679107209, N)) -> Type) -> Type) (is6989586621679113000 :: k) = Let6989586621679113001Go'Sym1 is6989586621679113000 :: TyFun N (NonEmpty (a6989586621679107209, b6989586621679107210) ~> NonEmpty (a6989586621679107209, N)) -> Type
type Apply (Let6989586621679113001GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679107207, b6989586621679107208) ~> NonEmpty (N, b6989586621679107208)) -> Type) -> Type) (is6989586621679113000 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113001GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679107207, b6989586621679107208) ~> NonEmpty (N, b6989586621679107208)) -> Type) -> Type) (is6989586621679113000 :: k) = Let6989586621679113001GoSym1 is6989586621679113000 :: TyFun N (NonEmpty (a6989586621679107207, b6989586621679107208) ~> NonEmpty (N, b6989586621679107208)) -> Type
type Apply (Let6989586621679113251Xs'Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251Xs'Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k1) = Let6989586621679113251Xs'Sym1 sources6989586621679113248 :: TyFun k2 (TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) -> Type
type Apply (Lambda_6989586621679113293Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113293Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k1) = Lambda_6989586621679113293Sym1 sources6989586621679113248 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679113297Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113297Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k1) = Lambda_6989586621679113297Sym1 sources6989586621679113248 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) -> Type) -> Type
type Apply (Let6989586621679113001Go'Sym1 is6989586621679113000 :: TyFun N (NonEmpty (a6989586621679107209, b6989586621679107210) ~> NonEmpty (a6989586621679107209, N)) -> Type) (a6989586621679113010 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113001Go'Sym1 is6989586621679113000 :: TyFun N (NonEmpty (a6989586621679107209, b6989586621679107210) ~> NonEmpty (a6989586621679107209, N)) -> Type) (a6989586621679113010 :: N) = Let6989586621679113001Go'Sym2 is6989586621679113000 a6989586621679113010 :: TyFun (NonEmpty (a6989586621679107209, b6989586621679107210)) (NonEmpty (a6989586621679107209, N)) -> Type
type Apply (Let6989586621679113001GoSym1 is6989586621679113000 :: TyFun N (NonEmpty (a6989586621679107207, b6989586621679107208) ~> NonEmpty (N, b6989586621679107208)) -> Type) (a6989586621679113019 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113001GoSym1 is6989586621679113000 :: TyFun N (NonEmpty (a6989586621679107207, b6989586621679107208) ~> NonEmpty (N, b6989586621679107208)) -> Type) (a6989586621679113019 :: N) = Let6989586621679113001GoSym2 is6989586621679113000 a6989586621679113019 :: TyFun (NonEmpty (a6989586621679107207, b6989586621679107208)) (NonEmpty (N, b6989586621679107208)) -> Type
type Apply (Let6989586621679113251FindSym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251FindSym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k1) = Let6989586621679113251FindSym1 sources6989586621679113248 :: TyFun k2 (TyFun k3 (TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) -> Type) -> Type
type Apply (Let6989586621679113251Go'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251Go'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k1) = Let6989586621679113251Go'Sym1 sources6989586621679113248 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) -> Type) -> Type
type Apply (Let6989586621679113251Xs'Sym1 sources6989586621679113248 :: TyFun k2 (TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) -> Type) (targets6989586621679113249 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251Xs'Sym1 sources6989586621679113248 :: TyFun k2 (TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) -> Type) (targets6989586621679113249 :: k2) = Let6989586621679113251Xs'Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type
type Apply (Lambda_6989586621679113293Sym1 sources6989586621679113248 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679113249 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113293Sym1 sources6989586621679113248 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679113249 :: k2) = Lambda_6989586621679113293Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type
type Apply (Lambda_6989586621679113300Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) -> Type) (ss6989586621679113299 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113300Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) -> Type) (ss6989586621679113299 :: k1) = Lambda_6989586621679113300Sym1 ss6989586621679113299 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679113251FindSym1 sources6989586621679113248 :: TyFun k2 (TyFun k3 (TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) -> Type) -> Type) (targets6989586621679113249 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251FindSym1 sources6989586621679113248 :: TyFun k2 (TyFun k3 (TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) -> Type) -> Type) (targets6989586621679113249 :: k2) = Let6989586621679113251FindSym2 sources6989586621679113248 targets6989586621679113249 :: TyFun k3 (TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) -> Type
type Apply (Let6989586621679113251Go'Sym1 sources6989586621679113248 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) -> Type) -> Type) (targets6989586621679113249 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251Go'Sym1 sources6989586621679113248 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) -> Type) -> Type) (targets6989586621679113249 :: k2) = Let6989586621679113251Go'Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun k3 (TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) -> Type
type Apply (Lambda_6989586621679113300Sym1 ss6989586621679113299 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113300Sym1 ss6989586621679113299 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679113248 :: k2) = Lambda_6989586621679113300Sym2 ss6989586621679113299 sources6989586621679113248 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type
type Apply (Let6989586621679113251FindSym2 sources6989586621679113248 targets6989586621679113249 :: TyFun k3 (TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) -> Type) (xs6989586621679113250 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251FindSym2 sources6989586621679113248 targets6989586621679113249 :: TyFun k3 (TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) -> Type) (xs6989586621679113250 :: k3) = Let6989586621679113251FindSym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type
type Apply (Let6989586621679113251Go'Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun k3 (TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) -> Type) (xs6989586621679113250 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251Go'Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun k3 (TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) -> Type) (xs6989586621679113250 :: k3) = Let6989586621679113251Go'Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type
type Apply (Lambda_6989586621679113300Sym2 ss6989586621679113299 sources6989586621679113248 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679113249 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113300Sym2 ss6989586621679113299 sources6989586621679113248 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679113249 :: k3) = Lambda_6989586621679113300Sym3 ss6989586621679113299 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type
type Apply (Let6989586621679113251Go'Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) (a6989586621679113283 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251Go'Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun N (NonEmpty a6989586621679107109 ~> NonEmpty (N, a6989586621679107109)) -> Type) (a6989586621679113283 :: N) = Let6989586621679113251Go'Sym4 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 a6989586621679113283 :: TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type
type Apply (Let6989586621679113251FindSym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) (a6989586621679113263 :: a6989586621679107110) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251FindSym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun a6989586621679107110 (NonEmpty (N, Maybe a6989586621679107110) ~> Maybe N) -> Type) (a6989586621679113263 :: a6989586621679107110) = Let6989586621679113251FindSym4 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 a6989586621679113263
type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679113902 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679113902 :: IList a) = LengthILSym1 a6989586621679113902
type Apply (LengthNESym0 :: TyFun (NonEmpty a) N -> Type) (a6989586621679113909 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthNESym0 :: TyFun (NonEmpty a) N -> Type) (a6989586621679113909 :: NonEmpty a) = LengthNESym1 a6989586621679113909
type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679113897 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679113897 :: [(VSpace s n, IList s)]) = LengthRSym1 a6989586621679113897
type Apply (RelabelTranspositions'Sym0 :: TyFun (NonEmpty (a, a)) [(N, N)] -> Type) (a6989586621679112999 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositions'Sym0 :: TyFun (NonEmpty (a, a)) [(N, N)] -> Type) (a6989586621679112999 :: NonEmpty (a, a)) = RelabelTranspositions'Sym1 a6989586621679112999
type Apply (RelabelTranspositionsSym1 a6989586621679113078 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679113079 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym1 a6989586621679113078 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679113079 :: IList a) = RelabelTranspositionsSym2 a6989586621679113078 a6989586621679113079
type Apply (Let6989586621679113001Is'''Sym0 :: TyFun (NonEmpty (a6989586621679107207, b6989586621679107210)) (NonEmpty (N, N)) -> Type) (is6989586621679113000 :: NonEmpty (a6989586621679107207, b6989586621679107210)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113001Is'''Sym0 :: TyFun (NonEmpty (a6989586621679107207, b6989586621679107210)) (NonEmpty (N, N)) -> Type) (is6989586621679113000 :: NonEmpty (a6989586621679107207, b6989586621679107210)) = Let6989586621679113001Is'''Sym1 is6989586621679113000
type Apply (Let6989586621679113001Is''Sym0 :: TyFun (NonEmpty (a6989586621679107207, k1)) (NonEmpty (N, k1)) -> Type) (is6989586621679113000 :: NonEmpty (a6989586621679107207, k1)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113001Is''Sym0 :: TyFun (NonEmpty (a6989586621679107207, k1)) (NonEmpty (N, k1)) -> Type) (is6989586621679113000 :: NonEmpty (a6989586621679107207, k1)) = Let6989586621679113001Is''Sym1 is6989586621679113000
type Apply (Let6989586621679113001Is'Sym0 :: TyFun (NonEmpty (a6989586621679107207, b6989586621679107208)) (NonEmpty (N, b6989586621679107208)) -> Type) (is6989586621679113000 :: NonEmpty (a6989586621679107207, b6989586621679107208)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113001Is'Sym0 :: TyFun (NonEmpty (a6989586621679107207, b6989586621679107208)) (NonEmpty (N, b6989586621679107208)) -> Type) (is6989586621679113000 :: NonEmpty (a6989586621679107207, b6989586621679107208)) = Let6989586621679113001Is'Sym1 is6989586621679113000
type Apply (Transpositions'Sym2 a6989586621679113245 a6989586621679113246 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) (a6989586621679113247 :: NonEmpty (Maybe a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Transpositions'Sym2 a6989586621679113245 a6989586621679113246 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) (a6989586621679113247 :: NonEmpty (Maybe a)) = Transpositions'Sym3 a6989586621679113245 a6989586621679113246 a6989586621679113247
type Apply (TranspositionsSym2 a6989586621679113361 a6989586621679113362 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679113363 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679113361 a6989586621679113362 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679113363 :: [(VSpace s n, IList s)]) = TranspositionsSym3 a6989586621679113361 a6989586621679113362 a6989586621679113363
type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679113412 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679113412 :: [(VSpace s n, IList s)]) = Let6989586621679113413Scrutinee_6989586621679107344Sym3 vs6989586621679113410 tl6989586621679113411 r6989586621679113412
type Apply (Let6989586621679113001Go'Sym2 is6989586621679113000 a6989586621679113010 :: TyFun (NonEmpty (a6989586621679107209, b6989586621679107210)) (NonEmpty (a6989586621679107209, N)) -> Type) (a6989586621679113011 :: NonEmpty (a6989586621679107209, b6989586621679107210)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113001Go'Sym2 is6989586621679113000 a6989586621679113010 :: TyFun (NonEmpty (a6989586621679107209, b6989586621679107210)) (NonEmpty (a6989586621679107209, N)) -> Type) (a6989586621679113011 :: NonEmpty (a6989586621679107209, b6989586621679107210)) = Let6989586621679113001Go'Sym3 is6989586621679113000 a6989586621679113010 a6989586621679113011
type Apply (Let6989586621679113001GoSym2 is6989586621679113000 a6989586621679113019 :: TyFun (NonEmpty (a6989586621679107207, b6989586621679107208)) (NonEmpty (N, b6989586621679107208)) -> Type) (a6989586621679113020 :: NonEmpty (a6989586621679107207, b6989586621679107208)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113001GoSym2 is6989586621679113000 a6989586621679113019 :: TyFun (NonEmpty (a6989586621679107207, b6989586621679107208)) (NonEmpty (N, b6989586621679107208)) -> Type) (a6989586621679113020 :: NonEmpty (a6989586621679107207, b6989586621679107208)) = Let6989586621679113001GoSym3 is6989586621679113000 a6989586621679113019 a6989586621679113020
type Apply (Let6989586621679113251Xs'Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) (xs6989586621679113250 :: NonEmpty a6989586621679107109) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251Xs'Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) (xs6989586621679113250 :: NonEmpty a6989586621679107109) = Let6989586621679113251Xs'Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250
type Apply (Lambda_6989586621679113297Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) (ss6989586621679113299 :: NonEmpty a6989586621679107111) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113297Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) (ss6989586621679113299 :: NonEmpty a6989586621679107111) = Lambda_6989586621679113297Sym4 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 ss6989586621679113299
type Apply (Let6989586621679113251FindSym4 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 a6989586621679113263 :: TyFun (NonEmpty (N, Maybe a6989586621679107110)) (Maybe N) -> Type) (a6989586621679113264 :: NonEmpty (N, Maybe a6989586621679107110)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251FindSym4 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 a6989586621679113263 :: TyFun (NonEmpty (N, Maybe a6989586621679107110)) (Maybe N) -> Type) (a6989586621679113264 :: NonEmpty (N, Maybe a6989586621679107110)) = Let6989586621679113251FindSym5 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 a6989586621679113263 a6989586621679113264
type Apply (Let6989586621679113251Go'Sym4 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 a6989586621679113283 :: TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) (a6989586621679113284 :: NonEmpty a6989586621679107109) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113251Go'Sym4 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 a6989586621679113283 :: TyFun (NonEmpty a6989586621679107109) (NonEmpty (N, a6989586621679107109)) -> Type) (a6989586621679113284 :: NonEmpty a6989586621679107109) = Let6989586621679113251Go'Sym5 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 a6989586621679113283 a6989586621679113284
type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) (a6989586621679113078 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) (a6989586621679113078 :: NonEmpty (a, a)) = RelabelTranspositionsSym1 a6989586621679113078
type Apply (Transpositions'Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> (NonEmpty (Maybe a) ~> Maybe [(N, N)])) -> Type) (a6989586621679113245 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Transpositions'Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> (NonEmpty (Maybe a) ~> Maybe [(N, N)])) -> Type) (a6989586621679113245 :: NonEmpty a) = Transpositions'Sym1 a6989586621679113245
type Apply (Transpositions'Sym1 a6989586621679113245 :: TyFun (NonEmpty a) (NonEmpty (Maybe a) ~> Maybe [(N, N)]) -> Type) (a6989586621679113246 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Transpositions'Sym1 a6989586621679113245 :: TyFun (NonEmpty a) (NonEmpty (Maybe a) ~> Maybe [(N, N)]) -> Type) (a6989586621679113246 :: NonEmpty a) = Transpositions'Sym2 a6989586621679113245 a6989586621679113246
type Apply (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679113362 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679113361 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679113362 :: TransRule s) = TranspositionsSym2 a6989586621679113361 a6989586621679113362
type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679113411 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679113411 :: TransRule s) = Let6989586621679113413Scrutinee_6989586621679107344Sym2 vs6989586621679113410 tl6989586621679113411
type Apply (Lambda_6989586621679113297Sym1 sources6989586621679113248 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) -> Type) -> Type) (targets6989586621679113249 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113297Sym1 sources6989586621679113248 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) -> Type) -> Type) (targets6989586621679113249 :: NonEmpty a) = Lambda_6989586621679113297Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) -> Type
type Apply (Lambda_6989586621679113293Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) (xs6989586621679113250 :: NonEmpty (Maybe k3)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113293Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) (xs6989586621679113250 :: NonEmpty (Maybe k3)) = Lambda_6989586621679113293Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250
type Apply (Lambda_6989586621679113297Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) -> Type) (xs6989586621679113250 :: NonEmpty (Maybe a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113297Sym2 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type) -> Type) (xs6989586621679113250 :: NonEmpty (Maybe a)) = Lambda_6989586621679113297Sym3 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250 :: TyFun (NonEmpty a6989586621679107111) (Maybe [(a6989586621679107111, N)]) -> Type
type Apply (Lambda_6989586621679113300Sym3 ss6989586621679113299 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) (xs6989586621679113250 :: NonEmpty (Maybe k4)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679113300Sym3 ss6989586621679113299 sources6989586621679113248 targets6989586621679113249 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) (xs6989586621679113250 :: NonEmpty (Maybe k4)) = Lambda_6989586621679113300Sym4 ss6989586621679113299 sources6989586621679113248 targets6989586621679113249 xs6989586621679113250
type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679113361 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679113361 :: VSpace s n) = TranspositionsSym1 a6989586621679113361
type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679113410 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679113413Scrutinee_6989586621679107344Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679113410 :: VSpace s n) = Let6989586621679113413Scrutinee_6989586621679107344Sym1 vs6989586621679113410

Length-typed vector used for tensor construction and also internally.

data Vec :: N -> Type -> Type where Source #

Constructors

VNil :: Vec 'Z a 
VCons :: a -> Vec n a -> Vec ('S n) a 

Instances

Instances details
Eq a => Eq (Vec n a) Source # 
Instance details

Defined in Math.Tensor.Safe.Vector

Methods

(==) :: Vec n a -> Vec n a -> Bool #

(/=) :: Vec n a -> Vec n a -> Bool #

Ord a => Ord (Vec n a) Source # 
Instance details

Defined in Math.Tensor.Safe.Vector

Methods

compare :: Vec n a -> Vec n a -> Ordering #

(<) :: Vec n a -> Vec n a -> Bool #

(<=) :: Vec n a -> Vec n a -> Bool #

(>) :: Vec n a -> Vec n a -> Bool #

(>=) :: Vec n a -> Vec n a -> Bool #

max :: Vec n a -> Vec n a -> Vec n a #

min :: Vec n a -> Vec n a -> Vec n a #

Show a => Show (Vec n a) Source # 
Instance details

Defined in Math.Tensor.Safe.Vector

Methods

showsPrec :: Int -> Vec n a -> ShowS #

show :: Vec n a -> String #

showList :: [Vec n a] -> ShowS #

NFData a => NFData (Vec n a) Source # 
Instance details

Defined in Math.Tensor.Safe.Vector

Methods

rnf :: Vec n a -> () #

vecFromListUnsafe :: forall (n :: N) a. Sing n -> [a] -> Vec n a Source #