safe-tensor-0.2.0.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
(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 #

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 a6989586621679568985 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym1 a6989586621679568728 :: 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_6989586621679112425Sym0 :: TyFun Nat (VSpace a b ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym2 a6989586621679568728 a6989586621679568729 :: 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_6989586621679108479Sym0 :: 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 (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: 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_6989586621679112442Sym0 :: 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 (Let6989586621679568740RSym0 :: 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 (Let6989586621679568766RSym0 :: 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 (Let6989586621679568792RSym0 :: 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 (Let6989586621679568818RSym0 :: 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 (Let6989586621679568916RSym0 :: 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 (Let6989586621679568893RSym0 :: 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 a6989586621679568964 a6989586621679568965 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (EpsilonInvRankSym2 a6989586621679568944 a6989586621679568945 :: 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 a6989586621679108465 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679568916RSym1 vid6989586621679568911 :: 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 (Let6989586621679568893RSym1 vid6989586621679568888 :: 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 a6989586621679568985 a6989586621679568986 a6989586621679568987 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym3 a6989586621679568906 a6989586621679568907 a6989586621679568908 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym3 a6989586621679568883 a6989586621679568884 a6989586621679568885 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym3 a6989586621679568867 a6989586621679568868 a6989586621679568869 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym3 a6989586621679568841 a6989586621679568842 a6989586621679568843 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym3 a6989586621679568806 a6989586621679568807 a6989586621679568808 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym3 a6989586621679568780 a6989586621679568781 a6989586621679568782 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym3 a6989586621679568754 a6989586621679568755 a6989586621679568756 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym3 a6989586621679568728 a6989586621679568729 a6989586621679568730 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108110GoSym0 :: 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_6989586621679108479Sym1 xv6989586621679108469 :: 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 a6989586621679108035 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084 :: 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 a6989586621679107652 :: TyFun b (VSpace a b) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679568740RSym1 vid6989586621679568734 :: 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 (Let6989586621679568766RSym1 vid6989586621679568760 :: 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 (Let6989586621679568792RSym1 vid6989586621679568786 :: 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 (Let6989586621679568818RSym1 vid6989586621679568812 :: 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 a6989586621679107830 :: 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_6989586621679108479Sym2 xv6989586621679108469 xl6989586621679108470 :: 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 a6989586621679107830 a6989586621679107831 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjSym2ConRankSym4 a6989586621679568906 a6989586621679568907 a6989586621679568908 a6989586621679568909 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym4 a6989586621679568883 a6989586621679568884 a6989586621679568885 a6989586621679568886 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym4 a6989586621679568867 a6989586621679568868 a6989586621679568869 a6989586621679568870 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym4 a6989586621679568841 a6989586621679568842 a6989586621679568843 a6989586621679568844 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym4 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym4 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym4 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym4 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108110GoSym1 i6989586621679108108 :: 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 (Let6989586621679568740RSym2 vid6989586621679568734 a6989586621679568735 :: 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 (Let6989586621679568766RSym2 vid6989586621679568760 a6989586621679568761 :: 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 (Let6989586621679568792RSym2 vid6989586621679568786 a6989586621679568787 :: 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 (Let6989586621679568818RSym2 vid6989586621679568812 a6989586621679568813 :: 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 (Let6989586621679568916RSym2 vid6989586621679568911 vdim6989586621679568912 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568893RSym2 vid6989586621679568888 vdim6989586621679568889 :: 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 a6989586621679108211 a6989586621679108212 a6989586621679108213 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym3 a6989586621679108156 a6989586621679108157 a6989586621679108158 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym3 a6989586621679108129 a6989586621679108130 a6989586621679108131 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjAreaConRankSym5 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 a6989586621679568810 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym5 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 a6989586621679568784 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym5 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 a6989586621679568758 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym5 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 a6989586621679568732 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679108479Sym3 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 :: 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 (Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568893RSym3 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 :: 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 (Let6989586621679108110GoSym3 i6989586621679108108 r6989586621679108109 a6989586621679108111 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108479Sym4 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 :: 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 (Let6989586621679568740RSym4 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568766RSym4 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568792RSym4 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568818RSym4 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568916RSym4 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 b6989586621679568914 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568893RSym4 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 b6989586621679568891 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679108479Sym5 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 :: 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 (Let6989586621679568740RSym5 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 d6989586621679568738 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568766RSym5 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 d6989586621679568764 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568792RSym5 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 d6989586621679568790 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568818RSym5 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 d6989586621679568816 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679108479Sym6 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 ys6989586621679108474 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (DeltaRankSym3 a6989586621679568985 a6989586621679568986 a6989586621679568987 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679568988 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym3 a6989586621679568985 a6989586621679568986 a6989586621679568987 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679568988 :: Symbol) = DeltaRankSym4 a6989586621679568985 a6989586621679568986 a6989586621679568987 a6989586621679568988
type Apply (InjSym2ConRankSym4 a6989586621679568906 a6989586621679568907 a6989586621679568908 a6989586621679568909 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568910 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym4 a6989586621679568906 a6989586621679568907 a6989586621679568908 a6989586621679568909 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568910 :: Symbol) = InjSym2ConRankSym5 a6989586621679568906 a6989586621679568907 a6989586621679568908 a6989586621679568909 a6989586621679568910
type Apply (InjSym2CovRankSym4 a6989586621679568883 a6989586621679568884 a6989586621679568885 a6989586621679568886 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568887 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym4 a6989586621679568883 a6989586621679568884 a6989586621679568885 a6989586621679568886 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568887 :: Symbol) = InjSym2CovRankSym5 a6989586621679568883 a6989586621679568884 a6989586621679568885 a6989586621679568886 a6989586621679568887
type Apply (SurjSym2ConRankSym4 a6989586621679568867 a6989586621679568868 a6989586621679568869 a6989586621679568870 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568871 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym4 a6989586621679568867 a6989586621679568868 a6989586621679568869 a6989586621679568870 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568871 :: Symbol) = SurjSym2ConRankSym5 a6989586621679568867 a6989586621679568868 a6989586621679568869 a6989586621679568870 a6989586621679568871
type Apply (SurjSym2CovRankSym4 a6989586621679568841 a6989586621679568842 a6989586621679568843 a6989586621679568844 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568845 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym4 a6989586621679568841 a6989586621679568842 a6989586621679568843 a6989586621679568844 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568845 :: Symbol) = SurjSym2CovRankSym5 a6989586621679568841 a6989586621679568842 a6989586621679568843 a6989586621679568844 a6989586621679568845
type Apply (InjAreaConRankSym5 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 a6989586621679568810 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568811 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym5 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 a6989586621679568810 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568811 :: Symbol) = InjAreaConRankSym6 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 a6989586621679568810 a6989586621679568811
type Apply (InjAreaCovRankSym5 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 a6989586621679568784 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568785 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym5 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 a6989586621679568784 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568785 :: Symbol) = InjAreaCovRankSym6 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 a6989586621679568784 a6989586621679568785
type Apply (SurjAreaConRankSym5 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 a6989586621679568758 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568759 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym5 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 a6989586621679568758 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568759 :: Symbol) = SurjAreaConRankSym6 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 a6989586621679568758 a6989586621679568759
type Apply (SurjAreaCovRankSym5 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 a6989586621679568732 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568733 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym5 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 a6989586621679568732 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568733 :: Symbol) = SurjAreaCovRankSym6 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 a6989586621679568732 a6989586621679568733
type Apply (Let6989586621679568916RSym4 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 b6989586621679568914 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568915 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568916RSym4 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 b6989586621679568914 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568915 :: a) = Let6989586621679568916RSym5 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 b6989586621679568914 i6989586621679568915
type Apply (Let6989586621679568893RSym4 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 b6989586621679568891 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568892 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568893RSym4 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 b6989586621679568891 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568892 :: a) = Let6989586621679568893RSym5 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 b6989586621679568891 i6989586621679568892
type Apply (Let6989586621679568740RSym5 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 d6989586621679568738 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568739 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym5 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 d6989586621679568738 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568739 :: a) = Let6989586621679568740RSym6 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 d6989586621679568738 i6989586621679568739
type Apply (Let6989586621679568766RSym5 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 d6989586621679568764 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568765 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym5 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 d6989586621679568764 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568765 :: a) = Let6989586621679568766RSym6 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 d6989586621679568764 i6989586621679568765
type Apply (Let6989586621679568792RSym5 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 d6989586621679568790 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568791 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym5 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 d6989586621679568790 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568791 :: a) = Let6989586621679568792RSym6 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 d6989586621679568790 i6989586621679568791
type Apply (Let6989586621679568818RSym5 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 d6989586621679568816 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568817 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym5 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 d6989586621679568816 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568817 :: a) = Let6989586621679568818RSym6 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 d6989586621679568816 i6989586621679568817
type Apply DeltaRankSym0 (a6989586621679568985 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply DeltaRankSym0 (a6989586621679568985 :: Symbol) = DeltaRankSym1 a6989586621679568985
type Apply InjSym2ConRankSym0 (a6989586621679568906 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2ConRankSym0 (a6989586621679568906 :: Symbol) = InjSym2ConRankSym1 a6989586621679568906
type Apply InjSym2CovRankSym0 (a6989586621679568883 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2CovRankSym0 (a6989586621679568883 :: Symbol) = InjSym2CovRankSym1 a6989586621679568883
type Apply SurjSym2ConRankSym0 (a6989586621679568867 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2ConRankSym0 (a6989586621679568867 :: Symbol) = SurjSym2ConRankSym1 a6989586621679568867
type Apply SurjSym2CovRankSym0 (a6989586621679568841 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2CovRankSym0 (a6989586621679568841 :: Symbol) = SurjSym2CovRankSym1 a6989586621679568841
type Apply EpsilonRankSym0 (a6989586621679568964 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonRankSym0 (a6989586621679568964 :: Symbol) = EpsilonRankSym1 a6989586621679568964
type Apply EpsilonInvRankSym0 (a6989586621679568944 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonInvRankSym0 (a6989586621679568944 :: Symbol) = EpsilonInvRankSym1 a6989586621679568944
type Apply InjAreaConRankSym0 (a6989586621679568806 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaConRankSym0 (a6989586621679568806 :: Symbol) = InjAreaConRankSym1 a6989586621679568806
type Apply InjAreaCovRankSym0 (a6989586621679568780 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaCovRankSym0 (a6989586621679568780 :: Symbol) = InjAreaCovRankSym1 a6989586621679568780
type Apply SurjAreaConRankSym0 (a6989586621679568754 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjAreaConRankSym0 (a6989586621679568754 :: Symbol) = SurjAreaConRankSym1 a6989586621679568754
type Apply SurjAreaCovRankSym0 (a6989586621679568728 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym1 a6989586621679568985 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568986 :: Nat) = DeltaRankSym2 a6989586621679568985 a6989586621679568986
type Apply (InjSym2ConRankSym1 a6989586621679568906 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568907 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym1 a6989586621679568906 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568907 :: Nat) = InjSym2ConRankSym2 a6989586621679568906 a6989586621679568907
type Apply (InjSym2CovRankSym1 a6989586621679568883 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568884 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym1 a6989586621679568883 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568884 :: Nat) = InjSym2CovRankSym2 a6989586621679568883 a6989586621679568884
type Apply (SurjSym2ConRankSym1 a6989586621679568867 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568868 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym1 a6989586621679568867 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568868 :: Nat) = SurjSym2ConRankSym2 a6989586621679568867 a6989586621679568868
type Apply (SurjSym2CovRankSym1 a6989586621679568841 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568842 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym1 a6989586621679568841 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568842 :: Nat) = SurjSym2CovRankSym2 a6989586621679568841 a6989586621679568842
type Apply (EpsilonRankSym1 a6989586621679568964 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568965 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym1 a6989586621679568964 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568965 :: Nat) = EpsilonRankSym2 a6989586621679568964 a6989586621679568965
type Apply (EpsilonInvRankSym1 a6989586621679568944 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568945 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym1 a6989586621679568944 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568945 :: Nat) = EpsilonInvRankSym2 a6989586621679568944 a6989586621679568945
type Apply (InjAreaConRankSym1 a6989586621679568806 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568807 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym1 a6989586621679568806 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568807 :: Symbol) = InjAreaConRankSym2 a6989586621679568806 a6989586621679568807
type Apply (InjAreaCovRankSym1 a6989586621679568780 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568781 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym1 a6989586621679568780 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568781 :: Symbol) = InjAreaCovRankSym2 a6989586621679568780 a6989586621679568781
type Apply (SurjAreaConRankSym1 a6989586621679568754 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568755 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym1 a6989586621679568754 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568755 :: Symbol) = SurjAreaConRankSym2 a6989586621679568754 a6989586621679568755
type Apply (SurjAreaCovRankSym1 a6989586621679568728 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568729 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym1 a6989586621679568728 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568729 :: Symbol) = SurjAreaCovRankSym2 a6989586621679568728 a6989586621679568729
type Apply (ShowsPrec_6989586621679112425Sym0 :: TyFun Nat (VSpace a b ~> (Symbol ~> Symbol)) -> Type) (a6989586621679112433 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679112425Sym0 :: TyFun Nat (VSpace a b ~> (Symbol ~> Symbol)) -> Type) (a6989586621679112433 :: Nat) = ShowsPrec_6989586621679112425Sym1 a6989586621679112433 :: TyFun (VSpace a b) (Symbol ~> Symbol) -> Type
type Apply (DeltaRankSym2 a6989586621679568985 a6989586621679568986 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568987 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym2 a6989586621679568985 a6989586621679568986 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568987 :: Symbol) = DeltaRankSym3 a6989586621679568985 a6989586621679568986 a6989586621679568987
type Apply (InjSym2ConRankSym2 a6989586621679568906 a6989586621679568907 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568908 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym2 a6989586621679568906 a6989586621679568907 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568908 :: Symbol) = InjSym2ConRankSym3 a6989586621679568906 a6989586621679568907 a6989586621679568908
type Apply (InjSym2CovRankSym2 a6989586621679568883 a6989586621679568884 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568885 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym2 a6989586621679568883 a6989586621679568884 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568885 :: Symbol) = InjSym2CovRankSym3 a6989586621679568883 a6989586621679568884 a6989586621679568885
type Apply (SurjSym2ConRankSym2 a6989586621679568867 a6989586621679568868 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568869 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym2 a6989586621679568867 a6989586621679568868 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568869 :: Symbol) = SurjSym2ConRankSym3 a6989586621679568867 a6989586621679568868 a6989586621679568869
type Apply (SurjSym2CovRankSym2 a6989586621679568841 a6989586621679568842 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568843 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym2 a6989586621679568841 a6989586621679568842 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568843 :: Symbol) = SurjSym2CovRankSym3 a6989586621679568841 a6989586621679568842 a6989586621679568843
type Apply (InjAreaConRankSym2 a6989586621679568806 a6989586621679568807 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568808 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym2 a6989586621679568806 a6989586621679568807 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568808 :: Symbol) = InjAreaConRankSym3 a6989586621679568806 a6989586621679568807 a6989586621679568808
type Apply (InjAreaCovRankSym2 a6989586621679568780 a6989586621679568781 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568782 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym2 a6989586621679568780 a6989586621679568781 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568782 :: Symbol) = InjAreaCovRankSym3 a6989586621679568780 a6989586621679568781 a6989586621679568782
type Apply (SurjAreaConRankSym2 a6989586621679568754 a6989586621679568755 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568756 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym2 a6989586621679568754 a6989586621679568755 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568756 :: Symbol) = SurjAreaConRankSym3 a6989586621679568754 a6989586621679568755 a6989586621679568756
type Apply (SurjAreaCovRankSym2 a6989586621679568728 a6989586621679568729 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568730 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym2 a6989586621679568728 a6989586621679568729 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568730 :: Symbol) = SurjAreaCovRankSym3 a6989586621679568728 a6989586621679568729 a6989586621679568730
type Apply (VSpaceSym0 :: TyFun a (b ~> VSpace a b) -> Type) (a6989586621679107652 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568734 :: k1) = Let6989586621679568740RSym1 vid6989586621679568734 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568766RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568760 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568760 :: k1) = Let6989586621679568766RSym1 vid6989586621679568760 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568792RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568786 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568786 :: k1) = Let6989586621679568792RSym1 vid6989586621679568786 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568818RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568812 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568812 :: k1) = Let6989586621679568818RSym1 vid6989586621679568812 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568916RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568911 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568916RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568911 :: k1) = Let6989586621679568916RSym1 vid6989586621679568911 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568893RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568888 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568893RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568888 :: k1) = Let6989586621679568893RSym1 vid6989586621679568888 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568916RSym1 vid6989586621679568911 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679568912 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568916RSym1 vid6989586621679568911 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679568912 :: Nat) = Let6989586621679568916RSym2 vid6989586621679568911 vdim6989586621679568912 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (Let6989586621679568893RSym1 vid6989586621679568888 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679568889 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568893RSym1 vid6989586621679568888 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679568889 :: Nat) = Let6989586621679568893RSym2 vid6989586621679568888 vdim6989586621679568889 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (InjSym2ConRankSym3 a6989586621679568906 a6989586621679568907 a6989586621679568908 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568909 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym3 a6989586621679568906 a6989586621679568907 a6989586621679568908 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568909 :: Symbol) = InjSym2ConRankSym4 a6989586621679568906 a6989586621679568907 a6989586621679568908 a6989586621679568909
type Apply (InjSym2CovRankSym3 a6989586621679568883 a6989586621679568884 a6989586621679568885 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568886 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym3 a6989586621679568883 a6989586621679568884 a6989586621679568885 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568886 :: Symbol) = InjSym2CovRankSym4 a6989586621679568883 a6989586621679568884 a6989586621679568885 a6989586621679568886
type Apply (SurjSym2ConRankSym3 a6989586621679568867 a6989586621679568868 a6989586621679568869 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568870 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym3 a6989586621679568867 a6989586621679568868 a6989586621679568869 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568870 :: Symbol) = SurjSym2ConRankSym4 a6989586621679568867 a6989586621679568868 a6989586621679568869 a6989586621679568870
type Apply (SurjSym2CovRankSym3 a6989586621679568841 a6989586621679568842 a6989586621679568843 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568844 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym3 a6989586621679568841 a6989586621679568842 a6989586621679568843 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568844 :: Symbol) = SurjSym2CovRankSym4 a6989586621679568841 a6989586621679568842 a6989586621679568843 a6989586621679568844
type Apply (InjAreaConRankSym3 a6989586621679568806 a6989586621679568807 a6989586621679568808 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568809 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym3 a6989586621679568806 a6989586621679568807 a6989586621679568808 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568809 :: Symbol) = InjAreaConRankSym4 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809
type Apply (InjAreaCovRankSym3 a6989586621679568780 a6989586621679568781 a6989586621679568782 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568783 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym3 a6989586621679568780 a6989586621679568781 a6989586621679568782 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568783 :: Symbol) = InjAreaCovRankSym4 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783
type Apply (SurjAreaConRankSym3 a6989586621679568754 a6989586621679568755 a6989586621679568756 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568757 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym3 a6989586621679568754 a6989586621679568755 a6989586621679568756 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568757 :: Symbol) = SurjAreaConRankSym4 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757
type Apply (SurjAreaCovRankSym3 a6989586621679568728 a6989586621679568729 a6989586621679568730 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568731 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym3 a6989586621679568728 a6989586621679568729 a6989586621679568730 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568731 :: Symbol) = SurjAreaCovRankSym4 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731
type Apply (VSpaceSym1 a6989586621679107652 :: TyFun b (VSpace a b) -> Type) (a6989586621679107653 :: b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (VSpaceSym1 a6989586621679107652 :: TyFun b (VSpace a b) -> Type) (a6989586621679107653 :: b) = VSpaceSym2 a6989586621679107652 a6989586621679107653
type Apply (CanTransposeConSym1 a6989586621679108211 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108212 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym1 a6989586621679108211 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108212 :: s) = CanTransposeConSym2 a6989586621679108211 a6989586621679108212
type Apply (CanTransposeCovSym1 a6989586621679108156 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108157 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym1 a6989586621679108156 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108157 :: s) = CanTransposeCovSym2 a6989586621679108156 a6989586621679108157
type Apply (Let6989586621679568740RSym1 vid6989586621679568734 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568735 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym1 vid6989586621679568734 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568735 :: a) = Let6989586621679568740RSym2 vid6989586621679568734 a6989586621679568735
type Apply (Let6989586621679568766RSym1 vid6989586621679568760 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568761 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym1 vid6989586621679568760 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568761 :: a) = Let6989586621679568766RSym2 vid6989586621679568760 a6989586621679568761
type Apply (Let6989586621679568792RSym1 vid6989586621679568786 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568787 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym1 vid6989586621679568786 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568787 :: a) = Let6989586621679568792RSym2 vid6989586621679568786 a6989586621679568787
type Apply (Let6989586621679568818RSym1 vid6989586621679568812 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568813 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym1 vid6989586621679568812 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568813 :: a) = Let6989586621679568818RSym2 vid6989586621679568812 a6989586621679568813
type Apply (InjAreaConRankSym4 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568810 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym4 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568810 :: Symbol) = InjAreaConRankSym5 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 a6989586621679568810
type Apply (InjAreaCovRankSym4 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568784 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym4 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568784 :: Symbol) = InjAreaCovRankSym5 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 a6989586621679568784
type Apply (SurjAreaConRankSym4 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568758 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym4 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568758 :: Symbol) = SurjAreaConRankSym5 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 a6989586621679568758
type Apply (SurjAreaCovRankSym4 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568732 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym4 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568732 :: Symbol) = SurjAreaCovRankSym5 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 a6989586621679568732
type Apply (CanTransposeConSym2 a6989586621679108211 a6989586621679108212 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108213 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym2 a6989586621679108211 a6989586621679108212 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108213 :: s) = CanTransposeConSym3 a6989586621679108211 a6989586621679108212 a6989586621679108213
type Apply (CanTransposeCovSym2 a6989586621679108156 a6989586621679108157 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108158 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym2 a6989586621679108156 a6989586621679108157 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108158 :: s) = CanTransposeCovSym3 a6989586621679108156 a6989586621679108157 a6989586621679108158
type Apply (Let6989586621679108110GoSym1 i6989586621679108108 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679108109 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108110GoSym1 i6989586621679108108 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679108109 :: k) = Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type
type Apply (Let6989586621679568740RSym2 vid6989586621679568734 a6989586621679568735 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568736 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym2 vid6989586621679568734 a6989586621679568735 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568736 :: a) = Let6989586621679568740RSym3 vid6989586621679568734 a6989586621679568735 b6989586621679568736
type Apply (Let6989586621679568766RSym2 vid6989586621679568760 a6989586621679568761 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568762 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym2 vid6989586621679568760 a6989586621679568761 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568762 :: a) = Let6989586621679568766RSym3 vid6989586621679568760 a6989586621679568761 b6989586621679568762
type Apply (Let6989586621679568792RSym2 vid6989586621679568786 a6989586621679568787 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568788 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym2 vid6989586621679568786 a6989586621679568787 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568788 :: a) = Let6989586621679568792RSym3 vid6989586621679568786 a6989586621679568787 b6989586621679568788
type Apply (Let6989586621679568818RSym2 vid6989586621679568812 a6989586621679568813 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568814 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym2 vid6989586621679568812 a6989586621679568813 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568814 :: a) = Let6989586621679568818RSym3 vid6989586621679568812 a6989586621679568813 b6989586621679568814
type Apply (Let6989586621679568916RSym2 vid6989586621679568911 vdim6989586621679568912 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679568913 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568916RSym2 vid6989586621679568911 vdim6989586621679568912 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679568913 :: a) = Let6989586621679568916RSym3 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913
type Apply (Let6989586621679568893RSym2 vid6989586621679568888 vdim6989586621679568889 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679568890 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568893RSym2 vid6989586621679568888 vdim6989586621679568889 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679568890 :: a) = Let6989586621679568893RSym3 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890
type Apply (Let6989586621679568740RSym3 vid6989586621679568734 a6989586621679568735 b6989586621679568736 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568737 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym3 vid6989586621679568734 a6989586621679568735 b6989586621679568736 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568737 :: a) = Let6989586621679568740RSym4 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737
type Apply (Let6989586621679568766RSym3 vid6989586621679568760 a6989586621679568761 b6989586621679568762 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568763 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym3 vid6989586621679568760 a6989586621679568761 b6989586621679568762 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568763 :: a) = Let6989586621679568766RSym4 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763
type Apply (Let6989586621679568792RSym3 vid6989586621679568786 a6989586621679568787 b6989586621679568788 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568789 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym3 vid6989586621679568786 a6989586621679568787 b6989586621679568788 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568789 :: a) = Let6989586621679568792RSym4 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789
type Apply (Let6989586621679568818RSym3 vid6989586621679568812 a6989586621679568813 b6989586621679568814 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568815 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym3 vid6989586621679568812 a6989586621679568813 b6989586621679568814 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568815 :: a) = Let6989586621679568818RSym4 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815
type Apply (Let6989586621679568916RSym3 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679568914 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568916RSym3 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679568914 :: a) = Let6989586621679568916RSym4 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 b6989586621679568914
type Apply (Let6989586621679568893RSym3 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679568891 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568893RSym3 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679568891 :: a) = Let6989586621679568893RSym4 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 b6989586621679568891
type Apply (Let6989586621679568740RSym4 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568738 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym4 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568738 :: a) = Let6989586621679568740RSym5 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 d6989586621679568738
type Apply (Let6989586621679568766RSym4 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568764 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym4 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568764 :: a) = Let6989586621679568766RSym5 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 d6989586621679568764
type Apply (Let6989586621679568792RSym4 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568790 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym4 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568790 :: a) = Let6989586621679568792RSym5 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 d6989586621679568790
type Apply (Let6989586621679568818RSym4 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568816 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym4 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568816 :: a) = Let6989586621679568818RSym5 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 d6989586621679568816
type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679108571 :: [(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) (a6989586621679108571 :: [(VSpace s n, IList s)]) = LengthRSym1 a6989586621679108571
type Apply (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) (a6989586621679108562 :: [(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) (a6989586621679108562 :: [(VSpace a b, IList a)]) = SaneSym1 a6989586621679108562
type Apply (CanTransposeMultSym2 a6989586621679108081 a6989586621679108082 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108083 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym2 a6989586621679108081 a6989586621679108082 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108083 :: [(VSpace s n, IList s)]) = CanTransposeMultSym3 a6989586621679108081 a6989586621679108082 a6989586621679108083
type Apply (CanTransposeConSym3 a6989586621679108211 a6989586621679108212 a6989586621679108213 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108214 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym3 a6989586621679108211 a6989586621679108212 a6989586621679108213 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108214 :: [(VSpace s n, IList s)]) = CanTransposeConSym4 a6989586621679108211 a6989586621679108212 a6989586621679108213 a6989586621679108214
type Apply (CanTransposeCovSym3 a6989586621679108156 a6989586621679108157 a6989586621679108158 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108159 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym3 a6989586621679108156 a6989586621679108157 a6989586621679108158 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108159 :: [(VSpace s n, IList s)]) = CanTransposeCovSym4 a6989586621679108156 a6989586621679108157 a6989586621679108158 a6989586621679108159
type Apply (CanTransposeSym3 a6989586621679108129 a6989586621679108130 a6989586621679108131 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108132 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym3 a6989586621679108129 a6989586621679108130 a6989586621679108131 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108132 :: [(VSpace s n, IList s)]) = CanTransposeSym4 a6989586621679108129 a6989586621679108130 a6989586621679108131 a6989586621679108132
type Apply (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108369 :: [(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) (a6989586621679108369 :: [(VSpace s n, IList s)]) = ContractRSym1 a6989586621679108369
type Apply (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108490 :: [(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) (a6989586621679108490 :: [(VSpace s n, IList s)]) = TailRSym1 a6989586621679108490
type Apply (EpsilonRankSym2 a6989586621679568964 a6989586621679568965 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568966 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym2 a6989586621679568964 a6989586621679568965 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568966 :: NonEmpty Symbol) = EpsilonRankSym3 a6989586621679568964 a6989586621679568965 a6989586621679568966
type Apply (EpsilonInvRankSym2 a6989586621679568944 a6989586621679568945 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568946 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym2 a6989586621679568944 a6989586621679568945 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568946 :: NonEmpty Symbol) = EpsilonInvRankSym3 a6989586621679568944 a6989586621679568945 a6989586621679568946
type Apply (MergeRSym1 a6989586621679108465 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679108466 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym1 a6989586621679108465 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679108466 :: [(VSpace s n, IList s)]) = MergeRSym2 a6989586621679108465 a6989586621679108466
type Apply (RemoveUntilSym1 a6989586621679108106 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108107 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym1 a6989586621679108106 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108107 :: [(VSpace s n, IList s)]) = RemoveUntilSym2 a6989586621679108106 a6989586621679108107
type Apply (RelabelRSym2 a6989586621679107830 a6989586621679107831 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679107832 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym2 a6989586621679107830 a6989586621679107831 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679107832 :: [(VSpace s n, IList s)]) = RelabelRSym3 a6989586621679107830 a6989586621679107831 a6989586621679107832
type Apply (TranspositionsSym2 a6989586621679108035 a6989586621679108036 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679108037 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679108035 a6989586621679108036 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679108037 :: [(VSpace s n, IList s)]) = TranspositionsSym3 a6989586621679108035 a6989586621679108036 a6989586621679108037
type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym2 vs6989586621679108084 tl6989586621679108085 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679108086 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym2 vs6989586621679108084 tl6989586621679108085 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679108086 :: [(VSpace s n, IList s)]) = Let6989586621679108087Scrutinee_6989586621679101859Sym3 vs6989586621679108084 tl6989586621679108085 r6989586621679108086
type Apply (Let6989586621679108110GoSym3 i6989586621679108108 r6989586621679108109 a6989586621679108111 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108112 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108110GoSym3 i6989586621679108108 r6989586621679108109 a6989586621679108111 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108112 :: [(VSpace s n, IList s)]) = Let6989586621679108110GoSym4 i6989586621679108108 r6989586621679108109 a6989586621679108111 a6989586621679108112
type Apply (Lambda_6989586621679108479Sym6 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 ys6989586621679108474 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679108481 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym6 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 ys6989586621679108474 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679108481 :: IList s) = Lambda_6989586621679108479Sym7 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 ys6989586621679108474 xl'6989586621679108481
type Apply (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679108465 :: [(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) (a6989586621679108465 :: [(VSpace s n, IList s)]) = MergeRSym1 a6989586621679108465
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679108545 :: [(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) (a6989586621679108545 :: [(VSpace s n, IList s)]) = HeadRSym1 a6989586621679108545
type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679108106 :: 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) (a6989586621679108106 :: Ix s) = RemoveUntilSym1 a6989586621679108106 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (CanTransposeSym1 a6989586621679108129 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108130 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679108129 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108130 :: Ix s) = CanTransposeSym2 a6989586621679108129 a6989586621679108130
type Apply (Let6989586621679108110GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679108108 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108110GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679108108 :: Ix s) = Let6989586621679108110GoSym1 i6989586621679108108 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type
type Apply (Lambda_6989586621679108479Sym1 xv6989586621679108469 :: 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) (xl6989586621679108470 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym1 xv6989586621679108469 :: 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) (xl6989586621679108470 :: IList s) = Lambda_6989586621679108479Sym2 xv6989586621679108469 xl6989586621679108470
type Apply (TranspositionsSym1 a6989586621679108035 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679108036 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679108035 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679108036 :: TransRule s) = TranspositionsSym2 a6989586621679108035 a6989586621679108036
type Apply (CanTransposeMultSym1 a6989586621679108081 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108082 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679108081 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108082 :: TransRule s) = CanTransposeMultSym2 a6989586621679108081 a6989586621679108082
type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679108085 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679108085 :: TransRule s) = Let6989586621679108087Scrutinee_6989586621679101859Sym2 vs6989586621679108084 tl6989586621679108085
type Apply (RelabelRSym1 a6989586621679107830 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679107831 :: NonEmpty (s, s)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym1 a6989586621679107830 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679107831 :: NonEmpty (s, s)) = RelabelRSym2 a6989586621679107830 a6989586621679107831
type Apply (Lambda_6989586621679108479Sym2 xv6989586621679108469 xl6989586621679108470 :: 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) (xs6989586621679108471 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym2 xv6989586621679108469 xl6989586621679108470 :: 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) (xs6989586621679108471 :: [(VSpace s n, IList s)]) = Lambda_6989586621679108479Sym3 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471
type Apply (CanTransposeSym2 a6989586621679108129 a6989586621679108130 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108131 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679108129 a6989586621679108130 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108131 :: Ix s) = CanTransposeSym3 a6989586621679108129 a6989586621679108130 a6989586621679108131
type Apply (Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679108111 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679108111 :: Ix s) = Let6989586621679108110GoSym3 i6989586621679108108 r6989586621679108109 a6989586621679108111 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (Lambda_6989586621679108479Sym4 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679108473 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym4 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679108473 :: IList s) = Lambda_6989586621679108479Sym5 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473
type Apply (Lambda_6989586621679108479Sym5 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679108474 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym5 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679108474 :: [(VSpace s n, IList s)]) = Lambda_6989586621679108479Sym6 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 ys6989586621679108474
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__6989586621680640167Sym0 :: 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_6989586621680640175Sym0 :: 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_6989586621679835458Sym0 :: 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_6989586621679835442Sym0 :: 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_6989586621679835426Sym0 :: 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_6989586621679835410Sym0 :: 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_6989586621679835394Sym0 :: 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_6989586621679835378Sym0 :: 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_6989586621679112442Sym0 :: 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_6989586621679112563 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_6989586621679112425Sym0 :: TyFun Nat (VSpace a1 b ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (VDimSym0 :: TyFun (VSpace a b) b -> Type) (a6989586621679108647 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (VIdSym0 :: TyFun (VSpace a b) a -> Type) (a6989586621679108651 :: VSpace a b) = VIdSym1 a6989586621679108651
type Apply (Compare_6989586621679112442Sym1 a6989586621679112447 :: TyFun (VSpace a b) Ordering -> Type) (a6989586621679112448 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679112442Sym1 a6989586621679112447 :: TyFun (VSpace a b) Ordering -> Type) (a6989586621679112448 :: VSpace a b) = Compare_6989586621679112442Sym2 a6989586621679112447 a6989586621679112448
type Apply (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679108211 :: 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) (a6989586621679108211 :: VSpace s n) = CanTransposeConSym1 a6989586621679108211
type Apply (CanTransposeCovSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679108156 :: 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) (a6989586621679108156 :: VSpace s n) = CanTransposeCovSym1 a6989586621679108156
type Apply (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679108129 :: 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) (a6989586621679108129 :: VSpace s n) = CanTransposeSym1 a6989586621679108129
type Apply (Lambda_6989586621679108479Sym0 :: 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) (xv6989586621679108469 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym0 :: 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) (xv6989586621679108469 :: VSpace s n) = Lambda_6989586621679108479Sym1 xv6989586621679108469
type Apply (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) (a6989586621679107830 :: 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) (a6989586621679107830 :: VSpace s n) = RelabelRSym1 a6989586621679107830
type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679108035 :: 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) (a6989586621679108035 :: VSpace s n) = TranspositionsSym1 a6989586621679108035
type Apply (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108081 :: 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) (a6989586621679108081 :: VSpace s n) = CanTransposeMultSym1 a6989586621679108081
type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679108084 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679108084 :: VSpace s n) = Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084
type Apply (Compare_6989586621679112442Sym0 :: TyFun (VSpace a b) (VSpace a b ~> Ordering) -> Type) (a6989586621679112447 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679112442Sym0 :: TyFun (VSpace a b) (VSpace a b ~> Ordering) -> Type) (a6989586621679112447 :: VSpace a b) = Compare_6989586621679112442Sym1 a6989586621679112447
type Apply (ShowsPrec_6989586621679112425Sym1 a6989586621679112433 :: TyFun (VSpace a b) (Symbol ~> Symbol) -> Type) (a6989586621679112434 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679112425Sym1 a6989586621679112433 :: TyFun (VSpace a b) (Symbol ~> Symbol) -> Type) (a6989586621679112434 :: VSpace a b) = ShowsPrec_6989586621679112425Sym2 a6989586621679112433 a6989586621679112434
type Apply (Lambda_6989586621679108479Sym3 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679108472 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym3 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679108472 :: VSpace s n) = Lambda_6989586621679108479Sym4 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472

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
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 #

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) #

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 a6989586621679568985 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym1 a6989586621679568728 :: 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_6989586621679112518Sym0 :: 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 (Let6989586621679108329Scrutinee_6989586621679101789Sym0 :: 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 (Let6989586621679108318Scrutinee_6989586621679101799Sym0 :: 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 (Let6989586621679107817Scrutinee_6989586621679101921Sym0 :: 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 (Let6989586621679107756Scrutinee_6989586621679101937Sym0 :: 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 (Let6989586621679108329Scrutinee_6989586621679101789Sym1 y'6989586621679108327 :: 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 (Let6989586621679108318Scrutinee_6989586621679101799Sym1 x'6989586621679108316 :: 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 a6989586621679568985 a6989586621679568986 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym2 a6989586621679568728 a6989586621679568729 :: 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_6989586621679108479Sym0 :: 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 (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: 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 a6989586621679108342 :: TyFun (IList a) (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679112518Sym1 a6989586621679112523 :: TyFun (IList a) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679568740RSym0 :: 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 (Let6989586621679568766RSym0 :: 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 (Let6989586621679568792RSym0 :: 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 (Let6989586621679568818RSym0 :: 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 (Let6989586621679568916RSym0 :: 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 (Let6989586621679568893RSym0 :: 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 a6989586621679568964 a6989586621679568965 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679107795Sym0 :: 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 a6989586621679107659 :: 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 a6989586621679108465 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679568916RSym1 vid6989586621679568911 :: 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 (Let6989586621679568893RSym1 vid6989586621679568888 :: 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 a6989586621679568985 a6989586621679568986 a6989586621679568987 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym3 a6989586621679568906 a6989586621679568907 a6989586621679568908 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym3 a6989586621679568883 a6989586621679568884 a6989586621679568885 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym3 a6989586621679568867 a6989586621679568868 a6989586621679568869 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym3 a6989586621679568841 a6989586621679568842 a6989586621679568843 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym3 a6989586621679568806 a6989586621679568807 a6989586621679568808 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym3 a6989586621679568780 a6989586621679568781 a6989586621679568782 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym3 a6989586621679568754 a6989586621679568755 a6989586621679568756 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym3 a6989586621679568728 a6989586621679568729 a6989586621679568730 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108110GoSym0 :: 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_6989586621679108479Sym1 xv6989586621679108469 :: 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 (Let6989586621679107786Scrutinee_6989586621679101933Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084 :: 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_6989586621679108429Sym0 :: 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_6989586621679108443Sym0 :: 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_6989586621679108454Sym0 :: 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 (Let6989586621679108494L'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 a6989586621679108211 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108329Scrutinee_6989586621679101789Sym2 y'6989586621679108327 ys'6989586621679108328 :: 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 (Let6989586621679108318Scrutinee_6989586621679101799Sym2 x'6989586621679108316 xs'6989586621679108317 :: 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_6989586621679108418Sym0 :: 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_6989586621679107795Sym1 rl6989586621679107792 :: 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_6989586621679107783Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679568740RSym1 vid6989586621679568734 :: 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 (Let6989586621679568766RSym1 vid6989586621679568760 :: 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 (Let6989586621679568792RSym1 vid6989586621679568786 :: 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 (Let6989586621679568818RSym1 vid6989586621679568812 :: 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 a6989586621679107830 :: 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_6989586621679108436Sym0 :: 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_6989586621679108479Sym2 xv6989586621679108469 xl6989586621679108470 :: 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 a6989586621679107830 a6989586621679107831 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108329Scrutinee_6989586621679101789Sym3 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108318Scrutinee_6989586621679101799Sym3 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjSym2ConRankSym4 a6989586621679568906 a6989586621679568907 a6989586621679568908 a6989586621679568909 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym4 a6989586621679568883 a6989586621679568884 a6989586621679568885 a6989586621679568886 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym4 a6989586621679568867 a6989586621679568868 a6989586621679568869 a6989586621679568870 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym4 a6989586621679568841 a6989586621679568842 a6989586621679568843 a6989586621679568844 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym4 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym4 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym4 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym4 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108443Sym1 xs6989586621679108440 :: 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 a6989586621679108211 a6989586621679108212 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108110GoSym1 i6989586621679108108 :: 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_6989586621679107783Sym1 rl6989586621679107781 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679568740RSym2 vid6989586621679568734 a6989586621679568735 :: 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 (Let6989586621679568766RSym2 vid6989586621679568760 a6989586621679568761 :: 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 (Let6989586621679568792RSym2 vid6989586621679568786 a6989586621679568787 :: 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 (Let6989586621679568818RSym2 vid6989586621679568812 a6989586621679568813 :: 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 (Let6989586621679568916RSym2 vid6989586621679568911 vdim6989586621679568912 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679107801L'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_6989586621679108429Sym1 xs6989586621679108426 :: 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_6989586621679108454Sym1 ys6989586621679108451 :: 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_6989586621679108418Sym1 xs6989586621679108414 :: 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_6989586621679107798Sym0 :: 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_6989586621679107795Sym2 rl6989586621679107792 is6989586621679107793 :: 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 a6989586621679108211 a6989586621679108212 a6989586621679108213 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym3 a6989586621679108156 a6989586621679108157 a6989586621679108158 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym3 a6989586621679108129 a6989586621679108130 a6989586621679108131 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjAreaConRankSym5 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 a6989586621679568810 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym5 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 a6989586621679568784 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym5 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 a6989586621679568758 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym5 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 a6989586621679568732 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679108479Sym3 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 :: 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 (Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: 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_6989586621679107783Sym2 rl6989586621679107781 is6989586621679107782 :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107772Sym2 rl6989586621679107770 is6989586621679107771 :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108429Sym2 xs6989586621679108426 ys6989586621679108427 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108436Sym2 xs6989586621679108433 ys6989586621679108434 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108454Sym2 ys6989586621679108451 xs6989586621679108452 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108494L'Sym2 v6989586621679108491 l6989586621679108492 :: TyFun k2 (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108373Scrutinee_6989586621679101781Sym2 v6989586621679108370 is6989586621679108371 :: TyFun k2 (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108329Scrutinee_6989586621679101789Sym4 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 xs6989586621679108292 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108318Scrutinee_6989586621679101799Sym4 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 xs6989586621679108292 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108418Sym2 xs6989586621679108414 ys6989586621679108415 :: 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_6989586621679107798Sym1 is'6989586621679107797 :: 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 (Let6989586621679568740RSym3 vid6989586621679568734 a6989586621679568735 b6989586621679568736 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679107795Sym3 rl6989586621679107792 is6989586621679107793 js6989586621679107794 :: TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107801L'Sym1 js'6989586621679107800 :: 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_6989586621679108421Sym0 :: 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_6989586621679108443Sym2 xs6989586621679108440 xs'6989586621679108441 :: 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 (Let6989586621679108110GoSym3 i6989586621679108108 r6989586621679108109 a6989586621679108111 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108329Scrutinee_6989586621679101789Sym5 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 xs6989586621679108292 y6989586621679108293 :: TyFun [a] (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108318Scrutinee_6989586621679101799Sym5 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 xs6989586621679108292 y6989586621679108293 :: TyFun [a] (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108479Sym4 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 :: 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 (Let6989586621679107801L'Sym2 js'6989586621679107800 is'6989586621679107797 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108421Sym1 xs''6989586621679108420 :: 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_6989586621679107798Sym2 is'6989586621679107797 rl6989586621679107792 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679568740RSym4 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568766RSym4 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568792RSym4 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568818RSym4 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568916RSym4 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 b6989586621679568914 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568893RSym4 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 b6989586621679568891 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679108429Sym3 xs6989586621679108426 ys6989586621679108427 xs'6989586621679108428 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108436Sym3 xs6989586621679108433 ys6989586621679108434 ys'6989586621679108435 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108443Sym3 xs6989586621679108440 xs'6989586621679108441 ys6989586621679108442 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108454Sym3 ys6989586621679108451 xs6989586621679108452 ys'6989586621679108453 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108418Sym3 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108479Sym5 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 :: 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 (Let6989586621679107801L'Sym3 js'6989586621679107800 is'6989586621679107797 rl6989586621679107792 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108421Sym2 xs''6989586621679108420 xs6989586621679108414 :: 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_6989586621679107798Sym3 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679568740RSym5 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 d6989586621679568738 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568766RSym5 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 d6989586621679568764 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568792RSym5 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 d6989586621679568790 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679568818RSym5 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 d6989586621679568816 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679108418Sym4 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 ys'6989586621679108417 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108479Sym6 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 ys6989586621679108474 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107801L'Sym4 js'6989586621679107800 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 :: TyFun k3 (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108421Sym3 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107798Sym4 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 js6989586621679107794 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108421Sym4 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679108421Sym5 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 ys'6989586621679108417 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (DeltaRankSym3 a6989586621679568985 a6989586621679568986 a6989586621679568987 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679568988 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym3 a6989586621679568985 a6989586621679568986 a6989586621679568987 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679568988 :: Symbol) = DeltaRankSym4 a6989586621679568985 a6989586621679568986 a6989586621679568987 a6989586621679568988
type Apply (InjSym2ConRankSym4 a6989586621679568906 a6989586621679568907 a6989586621679568908 a6989586621679568909 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568910 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym4 a6989586621679568906 a6989586621679568907 a6989586621679568908 a6989586621679568909 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568910 :: Symbol) = InjSym2ConRankSym5 a6989586621679568906 a6989586621679568907 a6989586621679568908 a6989586621679568909 a6989586621679568910
type Apply (InjSym2CovRankSym4 a6989586621679568883 a6989586621679568884 a6989586621679568885 a6989586621679568886 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568887 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym4 a6989586621679568883 a6989586621679568884 a6989586621679568885 a6989586621679568886 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568887 :: Symbol) = InjSym2CovRankSym5 a6989586621679568883 a6989586621679568884 a6989586621679568885 a6989586621679568886 a6989586621679568887
type Apply (SurjSym2ConRankSym4 a6989586621679568867 a6989586621679568868 a6989586621679568869 a6989586621679568870 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568871 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym4 a6989586621679568867 a6989586621679568868 a6989586621679568869 a6989586621679568870 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568871 :: Symbol) = SurjSym2ConRankSym5 a6989586621679568867 a6989586621679568868 a6989586621679568869 a6989586621679568870 a6989586621679568871
type Apply (SurjSym2CovRankSym4 a6989586621679568841 a6989586621679568842 a6989586621679568843 a6989586621679568844 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568845 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym4 a6989586621679568841 a6989586621679568842 a6989586621679568843 a6989586621679568844 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568845 :: Symbol) = SurjSym2CovRankSym5 a6989586621679568841 a6989586621679568842 a6989586621679568843 a6989586621679568844 a6989586621679568845
type Apply (InjAreaConRankSym5 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 a6989586621679568810 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568811 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym5 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 a6989586621679568810 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568811 :: Symbol) = InjAreaConRankSym6 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 a6989586621679568810 a6989586621679568811
type Apply (InjAreaCovRankSym5 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 a6989586621679568784 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568785 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym5 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 a6989586621679568784 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568785 :: Symbol) = InjAreaCovRankSym6 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 a6989586621679568784 a6989586621679568785
type Apply (SurjAreaConRankSym5 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 a6989586621679568758 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568759 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym5 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 a6989586621679568758 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568759 :: Symbol) = SurjAreaConRankSym6 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 a6989586621679568758 a6989586621679568759
type Apply (SurjAreaCovRankSym5 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 a6989586621679568732 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568733 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym5 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 a6989586621679568732 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568733 :: Symbol) = SurjAreaCovRankSym6 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 a6989586621679568732 a6989586621679568733
type Apply (Let6989586621679108494L'Sym2 v6989586621679108491 l6989586621679108492 :: TyFun k2 (Maybe (IList a)) -> Type) (ls6989586621679108493 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108494L'Sym2 v6989586621679108491 l6989586621679108492 :: TyFun k2 (Maybe (IList a)) -> Type) (ls6989586621679108493 :: k2) = Let6989586621679108494L'Sym3 v6989586621679108491 l6989586621679108492 ls6989586621679108493
type Apply (Let6989586621679108373Scrutinee_6989586621679101781Sym2 v6989586621679108370 is6989586621679108371 :: TyFun k2 (Maybe (IList a)) -> Type) (xs6989586621679108372 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108373Scrutinee_6989586621679101781Sym2 v6989586621679108370 is6989586621679108371 :: TyFun k2 (Maybe (IList a)) -> Type) (xs6989586621679108372 :: k2) = Let6989586621679108373Scrutinee_6989586621679101781Sym3 v6989586621679108370 is6989586621679108371 xs6989586621679108372
type Apply (Let6989586621679568916RSym4 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 b6989586621679568914 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568915 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568916RSym4 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 b6989586621679568914 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568915 :: a) = Let6989586621679568916RSym5 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 b6989586621679568914 i6989586621679568915
type Apply (Let6989586621679568893RSym4 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 b6989586621679568891 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568892 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568893RSym4 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 b6989586621679568891 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568892 :: a) = Let6989586621679568893RSym5 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 b6989586621679568891 i6989586621679568892
type Apply (Let6989586621679568740RSym5 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 d6989586621679568738 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568739 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym5 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 d6989586621679568738 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568739 :: a) = Let6989586621679568740RSym6 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 d6989586621679568738 i6989586621679568739
type Apply (Let6989586621679568766RSym5 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 d6989586621679568764 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568765 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym5 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 d6989586621679568764 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568765 :: a) = Let6989586621679568766RSym6 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 d6989586621679568764 i6989586621679568765
type Apply (Let6989586621679568792RSym5 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 d6989586621679568790 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568791 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym5 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 d6989586621679568790 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568791 :: a) = Let6989586621679568792RSym6 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 d6989586621679568790 i6989586621679568791
type Apply (Let6989586621679568818RSym5 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 d6989586621679568816 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568817 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym5 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 d6989586621679568816 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679568817 :: a) = Let6989586621679568818RSym6 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 d6989586621679568816 i6989586621679568817
type Apply (Let6989586621679107801L'Sym4 js'6989586621679107800 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 :: TyFun k3 (IList a) -> Type) (js6989586621679107794 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107801L'Sym4 js'6989586621679107800 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 :: TyFun k3 (IList a) -> Type) (js6989586621679107794 :: k3) = Let6989586621679107801L'Sym5 js'6989586621679107800 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 js6989586621679107794
type Apply DeltaRankSym0 (a6989586621679568985 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply DeltaRankSym0 (a6989586621679568985 :: Symbol) = DeltaRankSym1 a6989586621679568985
type Apply InjSym2ConRankSym0 (a6989586621679568906 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2ConRankSym0 (a6989586621679568906 :: Symbol) = InjSym2ConRankSym1 a6989586621679568906
type Apply InjSym2CovRankSym0 (a6989586621679568883 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2CovRankSym0 (a6989586621679568883 :: Symbol) = InjSym2CovRankSym1 a6989586621679568883
type Apply SurjSym2ConRankSym0 (a6989586621679568867 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2ConRankSym0 (a6989586621679568867 :: Symbol) = SurjSym2ConRankSym1 a6989586621679568867
type Apply SurjSym2CovRankSym0 (a6989586621679568841 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2CovRankSym0 (a6989586621679568841 :: Symbol) = SurjSym2CovRankSym1 a6989586621679568841
type Apply EpsilonRankSym0 (a6989586621679568964 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonRankSym0 (a6989586621679568964 :: Symbol) = EpsilonRankSym1 a6989586621679568964
type Apply EpsilonInvRankSym0 (a6989586621679568944 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonInvRankSym0 (a6989586621679568944 :: Symbol) = EpsilonInvRankSym1 a6989586621679568944
type Apply InjAreaConRankSym0 (a6989586621679568806 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaConRankSym0 (a6989586621679568806 :: Symbol) = InjAreaConRankSym1 a6989586621679568806
type Apply InjAreaCovRankSym0 (a6989586621679568780 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaCovRankSym0 (a6989586621679568780 :: Symbol) = InjAreaCovRankSym1 a6989586621679568780
type Apply SurjAreaConRankSym0 (a6989586621679568754 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjAreaConRankSym0 (a6989586621679568754 :: Symbol) = SurjAreaConRankSym1 a6989586621679568754
type Apply SurjAreaCovRankSym0 (a6989586621679568728 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym1 a6989586621679568985 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568986 :: Nat) = DeltaRankSym2 a6989586621679568985 a6989586621679568986
type Apply (InjSym2ConRankSym1 a6989586621679568906 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568907 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym1 a6989586621679568906 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568907 :: Nat) = InjSym2ConRankSym2 a6989586621679568906 a6989586621679568907
type Apply (InjSym2CovRankSym1 a6989586621679568883 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568884 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym1 a6989586621679568883 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568884 :: Nat) = InjSym2CovRankSym2 a6989586621679568883 a6989586621679568884
type Apply (SurjSym2ConRankSym1 a6989586621679568867 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568868 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym1 a6989586621679568867 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568868 :: Nat) = SurjSym2ConRankSym2 a6989586621679568867 a6989586621679568868
type Apply (SurjSym2CovRankSym1 a6989586621679568841 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568842 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym1 a6989586621679568841 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568842 :: Nat) = SurjSym2CovRankSym2 a6989586621679568841 a6989586621679568842
type Apply (ShowsPrec_6989586621679112491Sym0 :: TyFun Nat (IList a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679112503 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679112491Sym0 :: TyFun Nat (IList a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679112503 :: Nat) = ShowsPrec_6989586621679112491Sym1 a6989586621679112503 :: TyFun (IList a) (Symbol ~> Symbol) -> Type
type Apply (EpsilonRankSym1 a6989586621679568964 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568965 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym1 a6989586621679568964 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568965 :: Nat) = EpsilonRankSym2 a6989586621679568964 a6989586621679568965
type Apply (EpsilonInvRankSym1 a6989586621679568944 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568945 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym1 a6989586621679568944 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568945 :: Nat) = EpsilonInvRankSym2 a6989586621679568944 a6989586621679568945
type Apply (InjAreaConRankSym1 a6989586621679568806 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568807 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym1 a6989586621679568806 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568807 :: Symbol) = InjAreaConRankSym2 a6989586621679568806 a6989586621679568807
type Apply (InjAreaCovRankSym1 a6989586621679568780 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568781 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym1 a6989586621679568780 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568781 :: Symbol) = InjAreaCovRankSym2 a6989586621679568780 a6989586621679568781
type Apply (SurjAreaConRankSym1 a6989586621679568754 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568755 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym1 a6989586621679568754 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568755 :: Symbol) = SurjAreaConRankSym2 a6989586621679568754 a6989586621679568755
type Apply (SurjAreaCovRankSym1 a6989586621679568728 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568729 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym1 a6989586621679568728 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679568729 :: Symbol) = SurjAreaCovRankSym2 a6989586621679568728 a6989586621679568729
type Apply (PrepICovSym0 :: TyFun a (IList a ~> IList a) -> Type) (a6989586621679108342 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepICovSym0 :: TyFun a (IList a ~> IList a) -> Type) (a6989586621679108342 :: a) = PrepICovSym1 a6989586621679108342
type Apply (PrepIConSym0 :: TyFun a (IList a ~> IList a) -> Type) (a6989586621679108356 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepIConSym0 :: TyFun a (IList a ~> IList a) -> Type) (a6989586621679108356 :: a) = PrepIConSym1 a6989586621679108356
type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (y'6989586621679108327 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (y'6989586621679108327 :: a) = Let6989586621679108329Scrutinee_6989586621679101789Sym1 y'6989586621679108327
type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x'6989586621679108316 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x'6989586621679108316 :: a) = Let6989586621679108318Scrutinee_6989586621679101799Sym1 x'6989586621679108316
type Apply (DeltaRankSym2 a6989586621679568985 a6989586621679568986 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568987 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym2 a6989586621679568985 a6989586621679568986 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568987 :: Symbol) = DeltaRankSym3 a6989586621679568985 a6989586621679568986 a6989586621679568987
type Apply (InjSym2ConRankSym2 a6989586621679568906 a6989586621679568907 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568908 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym2 a6989586621679568906 a6989586621679568907 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568908 :: Symbol) = InjSym2ConRankSym3 a6989586621679568906 a6989586621679568907 a6989586621679568908
type Apply (InjSym2CovRankSym2 a6989586621679568883 a6989586621679568884 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568885 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym2 a6989586621679568883 a6989586621679568884 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568885 :: Symbol) = InjSym2CovRankSym3 a6989586621679568883 a6989586621679568884 a6989586621679568885
type Apply (SurjSym2ConRankSym2 a6989586621679568867 a6989586621679568868 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568869 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym2 a6989586621679568867 a6989586621679568868 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568869 :: Symbol) = SurjSym2ConRankSym3 a6989586621679568867 a6989586621679568868 a6989586621679568869
type Apply (SurjSym2CovRankSym2 a6989586621679568841 a6989586621679568842 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568843 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym2 a6989586621679568841 a6989586621679568842 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568843 :: Symbol) = SurjSym2CovRankSym3 a6989586621679568841 a6989586621679568842 a6989586621679568843
type Apply (InjAreaConRankSym2 a6989586621679568806 a6989586621679568807 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568808 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym2 a6989586621679568806 a6989586621679568807 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568808 :: Symbol) = InjAreaConRankSym3 a6989586621679568806 a6989586621679568807 a6989586621679568808
type Apply (InjAreaCovRankSym2 a6989586621679568780 a6989586621679568781 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568782 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym2 a6989586621679568780 a6989586621679568781 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568782 :: Symbol) = InjAreaCovRankSym3 a6989586621679568780 a6989586621679568781 a6989586621679568782
type Apply (SurjAreaConRankSym2 a6989586621679568754 a6989586621679568755 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568756 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym2 a6989586621679568754 a6989586621679568755 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568756 :: Symbol) = SurjAreaConRankSym3 a6989586621679568754 a6989586621679568755 a6989586621679568756
type Apply (SurjAreaCovRankSym2 a6989586621679568728 a6989586621679568729 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568730 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym2 a6989586621679568728 a6989586621679568729 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679568730 :: Symbol) = SurjAreaCovRankSym3 a6989586621679568728 a6989586621679568729 a6989586621679568730
type Apply (Let6989586621679568740RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568734 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568734 :: k1) = Let6989586621679568740RSym1 vid6989586621679568734 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568766RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568760 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568760 :: k1) = Let6989586621679568766RSym1 vid6989586621679568760 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568792RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568786 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568786 :: k1) = Let6989586621679568792RSym1 vid6989586621679568786 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568818RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568812 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568812 :: k1) = Let6989586621679568818RSym1 vid6989586621679568812 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568916RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568911 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568916RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568911 :: k1) = Let6989586621679568916RSym1 vid6989586621679568911 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568893RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568888 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568893RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679568888 :: k1) = Let6989586621679568893RSym1 vid6989586621679568888 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679568916RSym1 vid6989586621679568911 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679568912 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568916RSym1 vid6989586621679568911 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679568912 :: Nat) = Let6989586621679568916RSym2 vid6989586621679568911 vdim6989586621679568912 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (Let6989586621679568893RSym1 vid6989586621679568888 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679568889 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568893RSym1 vid6989586621679568888 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679568889 :: Nat) = Let6989586621679568893RSym2 vid6989586621679568888 vdim6989586621679568889 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (InjSym2ConRankSym3 a6989586621679568906 a6989586621679568907 a6989586621679568908 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568909 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym3 a6989586621679568906 a6989586621679568907 a6989586621679568908 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568909 :: Symbol) = InjSym2ConRankSym4 a6989586621679568906 a6989586621679568907 a6989586621679568908 a6989586621679568909
type Apply (InjSym2CovRankSym3 a6989586621679568883 a6989586621679568884 a6989586621679568885 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568886 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym3 a6989586621679568883 a6989586621679568884 a6989586621679568885 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568886 :: Symbol) = InjSym2CovRankSym4 a6989586621679568883 a6989586621679568884 a6989586621679568885 a6989586621679568886
type Apply (SurjSym2ConRankSym3 a6989586621679568867 a6989586621679568868 a6989586621679568869 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568870 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym3 a6989586621679568867 a6989586621679568868 a6989586621679568869 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568870 :: Symbol) = SurjSym2ConRankSym4 a6989586621679568867 a6989586621679568868 a6989586621679568869 a6989586621679568870
type Apply (SurjSym2CovRankSym3 a6989586621679568841 a6989586621679568842 a6989586621679568843 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568844 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym3 a6989586621679568841 a6989586621679568842 a6989586621679568843 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568844 :: Symbol) = SurjSym2CovRankSym4 a6989586621679568841 a6989586621679568842 a6989586621679568843 a6989586621679568844
type Apply (InjAreaConRankSym3 a6989586621679568806 a6989586621679568807 a6989586621679568808 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568809 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym3 a6989586621679568806 a6989586621679568807 a6989586621679568808 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568809 :: Symbol) = InjAreaConRankSym4 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809
type Apply (InjAreaCovRankSym3 a6989586621679568780 a6989586621679568781 a6989586621679568782 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568783 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym3 a6989586621679568780 a6989586621679568781 a6989586621679568782 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568783 :: Symbol) = InjAreaCovRankSym4 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783
type Apply (SurjAreaConRankSym3 a6989586621679568754 a6989586621679568755 a6989586621679568756 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568757 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym3 a6989586621679568754 a6989586621679568755 a6989586621679568756 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568757 :: Symbol) = SurjAreaConRankSym4 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757
type Apply (SurjAreaCovRankSym3 a6989586621679568728 a6989586621679568729 a6989586621679568730 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568731 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym3 a6989586621679568728 a6989586621679568729 a6989586621679568730 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679568731 :: Symbol) = SurjAreaCovRankSym4 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731
type Apply (Lambda_6989586621679108429Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679108426 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108429Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679108426 :: k1) = Lambda_6989586621679108429Sym1 xs6989586621679108426 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679108443Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679108440 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108443Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679108440 :: k1) = Lambda_6989586621679108443Sym1 xs6989586621679108440 :: TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679108454Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679108451 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108454Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679108451 :: k1) = Lambda_6989586621679108454Sym1 ys6989586621679108451 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Let6989586621679108494L'Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679108491 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108494L'Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679108491 :: k1) = Let6989586621679108494L'Sym1 v6989586621679108491 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type
type Apply (CanTransposeConSym1 a6989586621679108211 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108212 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym1 a6989586621679108211 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108212 :: s) = CanTransposeConSym2 a6989586621679108211 a6989586621679108212
type Apply (CanTransposeCovSym1 a6989586621679108156 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108157 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym1 a6989586621679108156 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108157 :: s) = CanTransposeCovSym2 a6989586621679108156 a6989586621679108157
type Apply (Let6989586621679108373Scrutinee_6989586621679101781Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679108370 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108373Scrutinee_6989586621679101781Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679108370 :: k1) = Let6989586621679108373Scrutinee_6989586621679101781Sym1 v6989586621679108370 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type
type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym2 y'6989586621679108327 ys'6989586621679108328 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679108291 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym2 y'6989586621679108327 ys'6989586621679108328 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679108291 :: a) = Let6989586621679108329Scrutinee_6989586621679101789Sym3 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291
type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym2 x'6989586621679108316 xs'6989586621679108317 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679108291 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym2 x'6989586621679108316 xs'6989586621679108317 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679108291 :: a) = Let6989586621679108318Scrutinee_6989586621679101799Sym3 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291
type Apply (Lambda_6989586621679108418Sym0 :: TyFun k2 (TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679108414 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108418Sym0 :: TyFun k2 (TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679108414 :: k2) = Lambda_6989586621679108418Sym1 xs6989586621679108414 :: TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679107795Sym1 rl6989586621679107792 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) (is6989586621679107793 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107795Sym1 rl6989586621679107792 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) (is6989586621679107793 :: k1) = Lambda_6989586621679107795Sym2 rl6989586621679107792 is6989586621679107793
type Apply (Lambda_6989586621679107783Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679107781 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107783Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679107781 :: k1) = Lambda_6989586621679107783Sym1 rl6989586621679107781 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679107772Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679107770 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107772Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679107770 :: k1) = Lambda_6989586621679107772Sym1 rl6989586621679107770 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type
type Apply (Let6989586621679568740RSym1 vid6989586621679568734 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568735 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym1 vid6989586621679568734 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568735 :: a) = Let6989586621679568740RSym2 vid6989586621679568734 a6989586621679568735
type Apply (Let6989586621679568766RSym1 vid6989586621679568760 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568761 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym1 vid6989586621679568760 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568761 :: a) = Let6989586621679568766RSym2 vid6989586621679568760 a6989586621679568761
type Apply (Let6989586621679568792RSym1 vid6989586621679568786 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568787 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym1 vid6989586621679568786 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568787 :: a) = Let6989586621679568792RSym2 vid6989586621679568786 a6989586621679568787
type Apply (Let6989586621679568818RSym1 vid6989586621679568812 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568813 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym1 vid6989586621679568812 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679568813 :: a) = Let6989586621679568818RSym2 vid6989586621679568812 a6989586621679568813
type Apply (InjAreaConRankSym4 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568810 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym4 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568810 :: Symbol) = InjAreaConRankSym5 a6989586621679568806 a6989586621679568807 a6989586621679568808 a6989586621679568809 a6989586621679568810
type Apply (InjAreaCovRankSym4 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568784 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym4 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568784 :: Symbol) = InjAreaCovRankSym5 a6989586621679568780 a6989586621679568781 a6989586621679568782 a6989586621679568783 a6989586621679568784
type Apply (SurjAreaConRankSym4 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568758 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym4 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568758 :: Symbol) = SurjAreaConRankSym5 a6989586621679568754 a6989586621679568755 a6989586621679568756 a6989586621679568757 a6989586621679568758
type Apply (SurjAreaCovRankSym4 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568732 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym4 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568732 :: Symbol) = SurjAreaCovRankSym5 a6989586621679568728 a6989586621679568729 a6989586621679568730 a6989586621679568731 a6989586621679568732
type Apply (Lambda_6989586621679108436Sym1 xs6989586621679108433 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679108434 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108436Sym1 xs6989586621679108433 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679108434 :: k1) = Lambda_6989586621679108436Sym2 xs6989586621679108433 ys6989586621679108434 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679108443Sym1 xs6989586621679108440 :: TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679108441 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108443Sym1 xs6989586621679108440 :: TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679108441 :: k2) = Lambda_6989586621679108443Sym2 xs6989586621679108440 xs'6989586621679108441 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (CanTransposeConSym2 a6989586621679108211 a6989586621679108212 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108213 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym2 a6989586621679108211 a6989586621679108212 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108213 :: s) = CanTransposeConSym3 a6989586621679108211 a6989586621679108212 a6989586621679108213
type Apply (CanTransposeCovSym2 a6989586621679108156 a6989586621679108157 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108158 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym2 a6989586621679108156 a6989586621679108157 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108158 :: s) = CanTransposeCovSym3 a6989586621679108156 a6989586621679108157 a6989586621679108158
type Apply (Let6989586621679108110GoSym1 i6989586621679108108 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679108109 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108110GoSym1 i6989586621679108108 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679108109 :: k) = Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type
type Apply (Lambda_6989586621679107783Sym1 rl6989586621679107781 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679107782 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107783Sym1 rl6989586621679107781 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679107782 :: k2) = Lambda_6989586621679107783Sym2 rl6989586621679107781 is6989586621679107782 :: TyFun (IList a) (Maybe (IList a)) -> Type
type Apply (Lambda_6989586621679107772Sym1 rl6989586621679107770 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679107771 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107772Sym1 rl6989586621679107770 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679107771 :: k2) = Lambda_6989586621679107772Sym2 rl6989586621679107770 is6989586621679107771 :: TyFun (IList a) (Maybe (IList a)) -> Type
type Apply (Let6989586621679568740RSym2 vid6989586621679568734 a6989586621679568735 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568736 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym2 vid6989586621679568734 a6989586621679568735 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568736 :: a) = Let6989586621679568740RSym3 vid6989586621679568734 a6989586621679568735 b6989586621679568736
type Apply (Let6989586621679568766RSym2 vid6989586621679568760 a6989586621679568761 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568762 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym2 vid6989586621679568760 a6989586621679568761 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568762 :: a) = Let6989586621679568766RSym3 vid6989586621679568760 a6989586621679568761 b6989586621679568762
type Apply (Let6989586621679568792RSym2 vid6989586621679568786 a6989586621679568787 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568788 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym2 vid6989586621679568786 a6989586621679568787 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568788 :: a) = Let6989586621679568792RSym3 vid6989586621679568786 a6989586621679568787 b6989586621679568788
type Apply (Let6989586621679568818RSym2 vid6989586621679568812 a6989586621679568813 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568814 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym2 vid6989586621679568812 a6989586621679568813 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679568814 :: a) = Let6989586621679568818RSym3 vid6989586621679568812 a6989586621679568813 b6989586621679568814
type Apply (Let6989586621679568916RSym2 vid6989586621679568911 vdim6989586621679568912 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679568913 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568916RSym2 vid6989586621679568911 vdim6989586621679568912 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679568913 :: a) = Let6989586621679568916RSym3 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913
type Apply (Let6989586621679568893RSym2 vid6989586621679568888 vdim6989586621679568889 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679568890 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568893RSym2 vid6989586621679568888 vdim6989586621679568889 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679568890 :: a) = Let6989586621679568893RSym3 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890
type Apply (Lambda_6989586621679108429Sym2 xs6989586621679108426 ys6989586621679108427 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (xs'6989586621679108428 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108429Sym2 xs6989586621679108426 ys6989586621679108427 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (xs'6989586621679108428 :: k2) = Lambda_6989586621679108429Sym3 xs6989586621679108426 ys6989586621679108427 xs'6989586621679108428
type Apply (Lambda_6989586621679108436Sym2 xs6989586621679108433 ys6989586621679108434 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679108435 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108436Sym2 xs6989586621679108433 ys6989586621679108434 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679108435 :: k2) = Lambda_6989586621679108436Sym3 xs6989586621679108433 ys6989586621679108434 ys'6989586621679108435
type Apply (Lambda_6989586621679108454Sym2 ys6989586621679108451 xs6989586621679108452 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679108453 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108454Sym2 ys6989586621679108451 xs6989586621679108452 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679108453 :: k2) = Lambda_6989586621679108454Sym3 ys6989586621679108451 xs6989586621679108452 ys'6989586621679108453
type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym4 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 xs6989586621679108292 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679108293 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym4 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 xs6989586621679108292 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679108293 :: a) = Let6989586621679108329Scrutinee_6989586621679101789Sym5 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 xs6989586621679108292 y6989586621679108293
type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym4 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 xs6989586621679108292 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679108293 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym4 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 xs6989586621679108292 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679108293 :: a) = Let6989586621679108318Scrutinee_6989586621679101799Sym5 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 xs6989586621679108292 y6989586621679108293
type Apply (Lambda_6989586621679108418Sym2 xs6989586621679108414 ys6989586621679108415 :: TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679108416 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108418Sym2 xs6989586621679108414 ys6989586621679108415 :: TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679108416 :: k3) = Lambda_6989586621679108418Sym3 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416
type Apply (Lambda_6989586621679107798Sym1 is'6989586621679107797 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (rl6989586621679107792 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107798Sym1 is'6989586621679107797 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (rl6989586621679107792 :: k1) = Lambda_6989586621679107798Sym2 is'6989586621679107797 rl6989586621679107792 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Let6989586621679568740RSym3 vid6989586621679568734 a6989586621679568735 b6989586621679568736 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568737 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym3 vid6989586621679568734 a6989586621679568735 b6989586621679568736 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568737 :: a) = Let6989586621679568740RSym4 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737
type Apply (Let6989586621679568766RSym3 vid6989586621679568760 a6989586621679568761 b6989586621679568762 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568763 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym3 vid6989586621679568760 a6989586621679568761 b6989586621679568762 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568763 :: a) = Let6989586621679568766RSym4 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763
type Apply (Let6989586621679568792RSym3 vid6989586621679568786 a6989586621679568787 b6989586621679568788 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568789 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym3 vid6989586621679568786 a6989586621679568787 b6989586621679568788 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568789 :: a) = Let6989586621679568792RSym4 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789
type Apply (Let6989586621679568818RSym3 vid6989586621679568812 a6989586621679568813 b6989586621679568814 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568815 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym3 vid6989586621679568812 a6989586621679568813 b6989586621679568814 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679568815 :: a) = Let6989586621679568818RSym4 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815
type Apply (Let6989586621679568916RSym3 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679568914 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568916RSym3 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679568914 :: a) = Let6989586621679568916RSym4 vid6989586621679568911 vdim6989586621679568912 a6989586621679568913 b6989586621679568914
type Apply (Let6989586621679568893RSym3 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679568891 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568893RSym3 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679568891 :: a) = Let6989586621679568893RSym4 vid6989586621679568888 vdim6989586621679568889 a6989586621679568890 b6989586621679568891
type Apply (Let6989586621679107801L'Sym2 js'6989586621679107800 is'6989586621679107797 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) (rl6989586621679107792 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107801L'Sym2 js'6989586621679107800 is'6989586621679107797 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) (rl6989586621679107792 :: k1) = Let6989586621679107801L'Sym3 js'6989586621679107800 is'6989586621679107797 rl6989586621679107792 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type
type Apply (Lambda_6989586621679108421Sym1 xs''6989586621679108420 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679108414 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108421Sym1 xs''6989586621679108420 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679108414 :: k1) = Lambda_6989586621679108421Sym2 xs''6989586621679108420 xs6989586621679108414 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679107798Sym2 is'6989586621679107797 rl6989586621679107792 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (is6989586621679107793 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107798Sym2 is'6989586621679107797 rl6989586621679107792 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (is6989586621679107793 :: k2) = Lambda_6989586621679107798Sym3 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Let6989586621679568740RSym4 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568738 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568740RSym4 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568738 :: a) = Let6989586621679568740RSym5 vid6989586621679568734 a6989586621679568735 b6989586621679568736 c6989586621679568737 d6989586621679568738
type Apply (Let6989586621679568766RSym4 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568764 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568766RSym4 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568764 :: a) = Let6989586621679568766RSym5 vid6989586621679568760 a6989586621679568761 b6989586621679568762 c6989586621679568763 d6989586621679568764
type Apply (Let6989586621679568792RSym4 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568790 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568792RSym4 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568790 :: a) = Let6989586621679568792RSym5 vid6989586621679568786 a6989586621679568787 b6989586621679568788 c6989586621679568789 d6989586621679568790
type Apply (Let6989586621679568818RSym4 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568816 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679568818RSym4 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679568816 :: a) = Let6989586621679568818RSym5 vid6989586621679568812 a6989586621679568813 b6989586621679568814 c6989586621679568815 d6989586621679568816
type Apply (Let6989586621679107801L'Sym3 js'6989586621679107800 is'6989586621679107797 rl6989586621679107792 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) (is6989586621679107793 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107801L'Sym3 js'6989586621679107800 is'6989586621679107797 rl6989586621679107792 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) (is6989586621679107793 :: k2) = Let6989586621679107801L'Sym4 js'6989586621679107800 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 :: TyFun k3 (IList a) -> Type
type Apply (Lambda_6989586621679108421Sym2 xs''6989586621679108420 xs6989586621679108414 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679108415 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108421Sym2 xs''6989586621679108420 xs6989586621679108414 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679108415 :: k2) = Lambda_6989586621679108421Sym3 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679107798Sym3 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (js6989586621679107794 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107798Sym3 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (js6989586621679107794 :: k3) = Lambda_6989586621679107798Sym4 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 js6989586621679107794
type Apply (Lambda_6989586621679108421Sym3 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679108416 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108421Sym3 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679108416 :: k3) = Lambda_6989586621679108421Sym4 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679108421Sym4 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679108417 :: k4) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108421Sym4 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679108417 :: k4) = Lambda_6989586621679108421Sym5 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 ys'6989586621679108417
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 Show_ (arg :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: IList a) = Apply (Show__6989586621680640167Sym0 :: 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_6989586621680640175Sym0 :: 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_6989586621679835458Sym0 :: 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_6989586621679835442Sym0 :: 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_6989586621679835426Sym0 :: 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_6989586621679835410Sym0 :: 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_6989586621679835394Sym0 :: 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_6989586621679835378Sym0 :: 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_6989586621679112518Sym0 :: 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_6989586621679112579 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_6989586621679112491Sym0 :: TyFun Nat (IList a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679108576 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679108576 :: IList a) = LengthILSym1 a6989586621679108576
type Apply (IsAscendingISym0 :: TyFun (IList a) Bool -> Type) (a6989586621679108597 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IsAscendingISym0 :: TyFun (IList a) Bool -> Type) (a6989586621679108597 :: IList a) = IsAscendingISym1 a6989586621679108597
type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679108571 :: [(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) (a6989586621679108571 :: [(VSpace s n, IList s)]) = LengthRSym1 a6989586621679108571
type Apply (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) (a6989586621679108562 :: [(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) (a6989586621679108562 :: [(VSpace a b, IList a)]) = SaneSym1 a6989586621679108562
type Apply (Compare_6989586621679112518Sym1 a6989586621679112523 :: TyFun (IList a) Ordering -> Type) (a6989586621679112524 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679112518Sym1 a6989586621679112523 :: TyFun (IList a) Ordering -> Type) (a6989586621679112524 :: IList a) = Compare_6989586621679112518Sym2 a6989586621679112523 a6989586621679112524
type Apply (CanTransposeMultSym2 a6989586621679108081 a6989586621679108082 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108083 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym2 a6989586621679108081 a6989586621679108082 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108083 :: [(VSpace s n, IList s)]) = CanTransposeMultSym3 a6989586621679108081 a6989586621679108082 a6989586621679108083
type Apply (CanTransposeConSym3 a6989586621679108211 a6989586621679108212 a6989586621679108213 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108214 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym3 a6989586621679108211 a6989586621679108212 a6989586621679108213 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108214 :: [(VSpace s n, IList s)]) = CanTransposeConSym4 a6989586621679108211 a6989586621679108212 a6989586621679108213 a6989586621679108214
type Apply (CanTransposeCovSym3 a6989586621679108156 a6989586621679108157 a6989586621679108158 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108159 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym3 a6989586621679108156 a6989586621679108157 a6989586621679108158 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108159 :: [(VSpace s n, IList s)]) = CanTransposeCovSym4 a6989586621679108156 a6989586621679108157 a6989586621679108158 a6989586621679108159
type Apply (CanTransposeSym3 a6989586621679108129 a6989586621679108130 a6989586621679108131 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108132 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym3 a6989586621679108129 a6989586621679108130 a6989586621679108131 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679108132 :: [(VSpace s n, IList s)]) = CanTransposeSym4 a6989586621679108129 a6989586621679108130 a6989586621679108131 a6989586621679108132
type Apply (ContractISym0 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679108290 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ContractISym0 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679108290 :: IList a) = ContractISym1 a6989586621679108290
type Apply (CovSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679107662 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CovSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679107662 :: NonEmpty a) = CovSym1 a6989586621679107662
type Apply (ConSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679107664 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ConSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679107664 :: NonEmpty a) = ConSym1 a6989586621679107664
type Apply (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108369 :: [(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) (a6989586621679108369 :: [(VSpace s n, IList s)]) = ContractRSym1 a6989586621679108369
type Apply (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108490 :: [(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) (a6989586621679108490 :: [(VSpace s n, IList s)]) = TailRSym1 a6989586621679108490
type Apply (PrepICovSym1 a6989586621679108342 :: TyFun (IList a) (IList a) -> Type) (a6989586621679108343 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepICovSym1 a6989586621679108342 :: TyFun (IList a) (IList a) -> Type) (a6989586621679108343 :: IList a) = PrepICovSym2 a6989586621679108342 a6989586621679108343
type Apply (PrepIConSym1 a6989586621679108356 :: TyFun (IList a) (IList a) -> Type) (a6989586621679108357 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepIConSym1 a6989586621679108356 :: TyFun (IList a) (IList a) -> Type) (a6989586621679108357 :: IList a) = PrepIConSym2 a6989586621679108356 a6989586621679108357
type Apply (MergeILSym1 a6989586621679108412 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679108413 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeILSym1 a6989586621679108412 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679108413 :: IList a) = MergeILSym2 a6989586621679108412 a6989586621679108413
type Apply (RelabelIL'Sym1 a6989586621679107768 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (a6989586621679107769 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelIL'Sym1 a6989586621679107768 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (a6989586621679107769 :: IList a) = RelabelIL'Sym2 a6989586621679107768 a6989586621679107769
type Apply (RelabelILSym1 a6989586621679107813 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679107814 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelILSym1 a6989586621679107813 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679107814 :: IList a) = RelabelILSym2 a6989586621679107813 a6989586621679107814
type Apply (Let6989586621679107817Scrutinee_6989586621679101921Sym1 rl6989586621679107815 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679107816 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107817Scrutinee_6989586621679101921Sym1 rl6989586621679107815 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679107816 :: IList a) = Let6989586621679107817Scrutinee_6989586621679101921Sym2 rl6989586621679107815 is6989586621679107816
type Apply (RelabelTranspositionsSym1 a6989586621679107752 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679107753 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym1 a6989586621679107752 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679107753 :: IList a) = RelabelTranspositionsSym2 a6989586621679107752 a6989586621679107753
type Apply (Let6989586621679107756Scrutinee_6989586621679101937Sym1 rl6989586621679107754 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679107755 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107756Scrutinee_6989586621679101937Sym1 rl6989586621679107754 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679107755 :: IList a) = Let6989586621679107756Scrutinee_6989586621679101937Sym2 rl6989586621679107754 is6989586621679107755
type Apply (EpsilonRankSym2 a6989586621679568964 a6989586621679568965 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568966 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym2 a6989586621679568964 a6989586621679568965 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568966 :: NonEmpty Symbol) = EpsilonRankSym3 a6989586621679568964 a6989586621679568965 a6989586621679568966
type Apply (EpsilonInvRankSym2 a6989586621679568944 a6989586621679568945 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568946 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym2 a6989586621679568944 a6989586621679568945 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679568946 :: NonEmpty Symbol) = EpsilonInvRankSym3 a6989586621679568944 a6989586621679568945 a6989586621679568946
type Apply (ConCovSym1 a6989586621679107659 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679107660 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ConCovSym1 a6989586621679107659 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679107660 :: NonEmpty a) = ConCovSym2 a6989586621679107659 a6989586621679107660
type Apply (MergeRSym1 a6989586621679108465 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679108466 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym1 a6989586621679108465 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679108466 :: [(VSpace s n, IList s)]) = MergeRSym2 a6989586621679108465 a6989586621679108466
type Apply (RemoveUntilSym1 a6989586621679108106 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108107 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym1 a6989586621679108106 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108107 :: [(VSpace s n, IList s)]) = RemoveUntilSym2 a6989586621679108106 a6989586621679108107
type Apply (RelabelRSym2 a6989586621679107830 a6989586621679107831 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679107832 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym2 a6989586621679107830 a6989586621679107831 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679107832 :: [(VSpace s n, IList s)]) = RelabelRSym3 a6989586621679107830 a6989586621679107831 a6989586621679107832
type Apply (TranspositionsSym2 a6989586621679108035 a6989586621679108036 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679108037 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679108035 a6989586621679108036 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679108037 :: [(VSpace s n, IList s)]) = TranspositionsSym3 a6989586621679108035 a6989586621679108036 a6989586621679108037
type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym2 vs6989586621679108084 tl6989586621679108085 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679108086 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym2 vs6989586621679108084 tl6989586621679108085 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679108086 :: [(VSpace s n, IList s)]) = Let6989586621679108087Scrutinee_6989586621679101859Sym3 vs6989586621679108084 tl6989586621679108085 r6989586621679108086
type Apply (Lambda_6989586621679107783Sym2 rl6989586621679107781 is6989586621679107782 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679107785 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107783Sym2 rl6989586621679107781 is6989586621679107782 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679107785 :: IList a) = Lambda_6989586621679107783Sym3 rl6989586621679107781 is6989586621679107782 is'6989586621679107785
type Apply (Lambda_6989586621679107772Sym2 rl6989586621679107770 is6989586621679107771 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679107774 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107772Sym2 rl6989586621679107770 is6989586621679107771 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679107774 :: IList a) = Lambda_6989586621679107772Sym3 rl6989586621679107770 is6989586621679107771 is'6989586621679107774
type Apply (Lambda_6989586621679107795Sym3 rl6989586621679107792 is6989586621679107793 js6989586621679107794 :: TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) (is'6989586621679107797 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107795Sym3 rl6989586621679107792 is6989586621679107793 js6989586621679107794 :: TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) (is'6989586621679107797 :: NonEmpty (a, a)) = Lambda_6989586621679107795Sym4 rl6989586621679107792 is6989586621679107793 js6989586621679107794 is'6989586621679107797
type Apply (Let6989586621679108110GoSym3 i6989586621679108108 r6989586621679108109 a6989586621679108111 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108112 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108110GoSym3 i6989586621679108108 r6989586621679108109 a6989586621679108111 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679108112 :: [(VSpace s n, IList s)]) = Let6989586621679108110GoSym4 i6989586621679108108 r6989586621679108109 a6989586621679108111 a6989586621679108112
type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym5 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 xs6989586621679108292 y6989586621679108293 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679108294 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym5 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 xs6989586621679108292 y6989586621679108293 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679108294 :: [a]) = Let6989586621679108329Scrutinee_6989586621679101789Sym6 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 xs6989586621679108292 y6989586621679108293 ys6989586621679108294
type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym5 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 xs6989586621679108292 y6989586621679108293 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679108294 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym5 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 xs6989586621679108292 y6989586621679108293 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679108294 :: [a]) = Let6989586621679108318Scrutinee_6989586621679101799Sym6 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 xs6989586621679108292 y6989586621679108293 ys6989586621679108294
type Apply (Lambda_6989586621679108429Sym3 xs6989586621679108426 ys6989586621679108427 xs'6989586621679108428 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679108431 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108429Sym3 xs6989586621679108426 ys6989586621679108427 xs'6989586621679108428 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679108431 :: NonEmpty a) = Lambda_6989586621679108429Sym4 xs6989586621679108426 ys6989586621679108427 xs'6989586621679108428 xs''6989586621679108431
type Apply (Lambda_6989586621679108436Sym3 xs6989586621679108433 ys6989586621679108434 ys'6989586621679108435 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679108438 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108436Sym3 xs6989586621679108433 ys6989586621679108434 ys'6989586621679108435 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679108438 :: NonEmpty a) = Lambda_6989586621679108436Sym4 xs6989586621679108433 ys6989586621679108434 ys'6989586621679108435 ys''6989586621679108438
type Apply (Lambda_6989586621679108443Sym3 xs6989586621679108440 xs'6989586621679108441 ys6989586621679108442 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679108445 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108443Sym3 xs6989586621679108440 xs'6989586621679108441 ys6989586621679108442 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679108445 :: NonEmpty a) = Lambda_6989586621679108443Sym4 xs6989586621679108440 xs'6989586621679108441 ys6989586621679108442 xs''6989586621679108445
type Apply (Lambda_6989586621679108454Sym3 ys6989586621679108451 xs6989586621679108452 ys'6989586621679108453 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679108456 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108454Sym3 ys6989586621679108451 xs6989586621679108452 ys'6989586621679108453 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679108456 :: NonEmpty a) = Lambda_6989586621679108454Sym4 ys6989586621679108451 xs6989586621679108452 ys'6989586621679108453 ys''6989586621679108456
type Apply (Lambda_6989586621679108418Sym4 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 ys'6989586621679108417 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679108420 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108418Sym4 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 ys'6989586621679108417 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679108420 :: NonEmpty a) = Lambda_6989586621679108418Sym5 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 ys'6989586621679108417 xs''6989586621679108420
type Apply (Lambda_6989586621679108479Sym6 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 ys6989586621679108474 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679108481 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym6 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 ys6989586621679108474 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679108481 :: IList s) = Lambda_6989586621679108479Sym7 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 ys6989586621679108474 xl'6989586621679108481
type Apply (Lambda_6989586621679107798Sym4 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 js6989586621679107794 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (js'6989586621679107800 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107798Sym4 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 js6989586621679107794 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (js'6989586621679107800 :: NonEmpty a) = Lambda_6989586621679107798Sym5 is'6989586621679107797 rl6989586621679107792 is6989586621679107793 js6989586621679107794 js'6989586621679107800
type Apply (Lambda_6989586621679108421Sym5 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 ys'6989586621679108417 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679108423 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108421Sym5 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 ys'6989586621679108417 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679108423 :: NonEmpty a) = Lambda_6989586621679108421Sym6 xs''6989586621679108420 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 ys'6989586621679108417 ys''6989586621679108423
type Apply (MergeILSym0 :: TyFun (IList a) (IList a ~> Maybe (IList a)) -> Type) (a6989586621679108412 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeILSym0 :: TyFun (IList a) (IList a ~> Maybe (IList a)) -> Type) (a6989586621679108412 :: IList a) = MergeILSym1 a6989586621679108412
type Apply (Compare_6989586621679112518Sym0 :: TyFun (IList a) (IList a ~> Ordering) -> Type) (a6989586621679112523 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679112518Sym0 :: TyFun (IList a) (IList a ~> Ordering) -> Type) (a6989586621679112523 :: IList a) = Compare_6989586621679112518Sym1 a6989586621679112523
type Apply (RelabelIL'Sym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList (a, a))) -> Type) (a6989586621679107768 :: 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) (a6989586621679107768 :: NonEmpty (a, a)) = RelabelIL'Sym1 a6989586621679107768
type Apply (RelabelILSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList a)) -> Type) (a6989586621679107813 :: 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) (a6989586621679107813 :: NonEmpty (a, a)) = RelabelILSym1 a6989586621679107813
type Apply (Let6989586621679107817Scrutinee_6989586621679101921Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679107815 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107817Scrutinee_6989586621679101921Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679107815 :: NonEmpty (a, a)) = Let6989586621679107817Scrutinee_6989586621679101921Sym1 rl6989586621679107815
type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) (a6989586621679107752 :: 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) (a6989586621679107752 :: NonEmpty (a, a)) = RelabelTranspositionsSym1 a6989586621679107752
type Apply (Let6989586621679107756Scrutinee_6989586621679101937Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679107754 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107756Scrutinee_6989586621679101937Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679107754 :: NonEmpty (a, a)) = Let6989586621679107756Scrutinee_6989586621679101937Sym1 rl6989586621679107754
type Apply (ConCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> IList a) -> Type) (a6989586621679107659 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ConCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> IList a) -> Type) (a6989586621679107659 :: NonEmpty a) = ConCovSym1 a6989586621679107659
type Apply (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679108465 :: [(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) (a6989586621679108465 :: [(VSpace s n, IList s)]) = MergeRSym1 a6989586621679108465
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679108545 :: [(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) (a6989586621679108545 :: [(VSpace s n, IList s)]) = HeadRSym1 a6989586621679108545
type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym1 y'6989586621679108327 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (ys'6989586621679108328 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym1 y'6989586621679108327 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (ys'6989586621679108328 :: [a]) = Let6989586621679108329Scrutinee_6989586621679101789Sym2 y'6989586621679108327 ys'6989586621679108328
type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym1 x'6989586621679108316 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs'6989586621679108317 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym1 x'6989586621679108316 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs'6989586621679108317 :: [a]) = Let6989586621679108318Scrutinee_6989586621679101799Sym2 x'6989586621679108316 xs'6989586621679108317
type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679108106 :: 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) (a6989586621679108106 :: Ix s) = RemoveUntilSym1 a6989586621679108106 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (ShowsPrec_6989586621679112491Sym1 a6989586621679112503 :: TyFun (IList a) (Symbol ~> Symbol) -> Type) (a6989586621679112504 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679112491Sym1 a6989586621679112503 :: TyFun (IList a) (Symbol ~> Symbol) -> Type) (a6989586621679112504 :: IList a) = ShowsPrec_6989586621679112491Sym2 a6989586621679112503 a6989586621679112504
type Apply (Lambda_6989586621679107795Sym0 :: TyFun (NonEmpty (a, a)) (TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) -> Type) (rl6989586621679107792 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107795Sym0 :: TyFun (NonEmpty (a, a)) (TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) -> Type) (rl6989586621679107792 :: NonEmpty (a, a)) = Lambda_6989586621679107795Sym1 rl6989586621679107792 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type
type Apply (CanTransposeSym1 a6989586621679108129 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108130 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679108129 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108130 :: Ix s) = CanTransposeSym2 a6989586621679108129 a6989586621679108130
type Apply (Let6989586621679108110GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679108108 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108110GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679108108 :: Ix s) = Let6989586621679108110GoSym1 i6989586621679108108 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type
type Apply (Lambda_6989586621679108479Sym1 xv6989586621679108469 :: 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) (xl6989586621679108470 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym1 xv6989586621679108469 :: 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) (xl6989586621679108470 :: IList s) = Lambda_6989586621679108479Sym2 xv6989586621679108469 xl6989586621679108470
type Apply (Let6989586621679107786Scrutinee_6989586621679101933Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679107785 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107786Scrutinee_6989586621679101933Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679107785 :: IList a) = Let6989586621679107786Scrutinee_6989586621679101933Sym1 is'6989586621679107785 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type
type Apply (Let6989586621679107775Scrutinee_6989586621679101935Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679107774 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107775Scrutinee_6989586621679101935Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679107774 :: IList a) = Let6989586621679107775Scrutinee_6989586621679101935Sym1 is'6989586621679107774 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type
type Apply (TranspositionsSym1 a6989586621679108035 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679108036 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679108035 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679108036 :: TransRule s) = TranspositionsSym2 a6989586621679108035 a6989586621679108036
type Apply (CanTransposeMultSym1 a6989586621679108081 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108082 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679108081 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108082 :: TransRule s) = CanTransposeMultSym2 a6989586621679108081 a6989586621679108082
type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679108085 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679108085 :: TransRule s) = Let6989586621679108087Scrutinee_6989586621679101859Sym2 vs6989586621679108084 tl6989586621679108085
type Apply (RelabelRSym1 a6989586621679107830 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679107831 :: NonEmpty (s, s)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym1 a6989586621679107830 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679107831 :: NonEmpty (s, s)) = RelabelRSym2 a6989586621679107830 a6989586621679107831
type Apply (Lambda_6989586621679108436Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679108433 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108436Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679108433 :: NonEmpty a) = Lambda_6989586621679108436Sym1 xs6989586621679108433 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679108479Sym2 xv6989586621679108469 xl6989586621679108470 :: 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) (xs6989586621679108471 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym2 xv6989586621679108469 xl6989586621679108470 :: 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) (xs6989586621679108471 :: [(VSpace s n, IList s)]) = Lambda_6989586621679108479Sym3 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471
type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym3 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679108292 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108329Scrutinee_6989586621679101789Sym3 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679108292 :: [a]) = Let6989586621679108329Scrutinee_6989586621679101789Sym4 y'6989586621679108327 ys'6989586621679108328 x6989586621679108291 xs6989586621679108292
type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym3 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679108292 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108318Scrutinee_6989586621679101799Sym3 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679108292 :: [a]) = Let6989586621679108318Scrutinee_6989586621679101799Sym4 x'6989586621679108316 xs'6989586621679108317 x6989586621679108291 xs6989586621679108292
type Apply (CanTransposeSym2 a6989586621679108129 a6989586621679108130 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108131 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679108129 a6989586621679108130 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108131 :: Ix s) = CanTransposeSym3 a6989586621679108129 a6989586621679108130 a6989586621679108131
type Apply (Let6989586621679108494L'Sym1 v6989586621679108491 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (l6989586621679108492 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108494L'Sym1 v6989586621679108491 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (l6989586621679108492 :: IList a) = Let6989586621679108494L'Sym2 v6989586621679108491 l6989586621679108492 :: TyFun k2 (Maybe (IList a)) -> Type
type Apply (Let6989586621679108373Scrutinee_6989586621679101781Sym1 v6989586621679108370 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (is6989586621679108371 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108373Scrutinee_6989586621679101781Sym1 v6989586621679108370 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (is6989586621679108371 :: IList a) = Let6989586621679108373Scrutinee_6989586621679101781Sym2 v6989586621679108370 is6989586621679108371 :: TyFun k2 (Maybe (IList a)) -> Type
type Apply (Let6989586621679107801L'Sym0 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) -> Type) (js'6989586621679107800 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107801L'Sym0 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) -> Type) (js'6989586621679107800 :: NonEmpty a) = Let6989586621679107801L'Sym1 js'6989586621679107800 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679108429Sym1 xs6989586621679108426 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679108427 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108429Sym1 xs6989586621679108426 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679108427 :: NonEmpty a) = Lambda_6989586621679108429Sym2 xs6989586621679108426 ys6989586621679108427 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679108454Sym1 ys6989586621679108451 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679108452 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108454Sym1 ys6989586621679108451 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679108452 :: NonEmpty a) = Lambda_6989586621679108454Sym2 ys6989586621679108451 xs6989586621679108452 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679108418Sym1 xs6989586621679108414 :: TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679108415 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108418Sym1 xs6989586621679108414 :: TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679108415 :: NonEmpty a) = Lambda_6989586621679108418Sym2 xs6989586621679108414 ys6989586621679108415 :: TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679107798Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (is'6989586621679107797 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107798Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (is'6989586621679107797 :: NonEmpty a) = Lambda_6989586621679107798Sym1 is'6989586621679107797 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679107795Sym2 rl6989586621679107792 is6989586621679107793 :: TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) (js6989586621679107794 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107795Sym2 rl6989586621679107792 is6989586621679107793 :: TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) (js6989586621679107794 :: NonEmpty a) = Lambda_6989586621679107795Sym3 rl6989586621679107792 is6989586621679107793 js6989586621679107794
type Apply (Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679108111 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679108111 :: Ix s) = Let6989586621679108110GoSym3 i6989586621679108108 r6989586621679108109 a6989586621679108111 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (Let6989586621679107801L'Sym1 js'6989586621679107800 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) (is'6989586621679107797 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107801L'Sym1 js'6989586621679107800 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) (is'6989586621679107797 :: NonEmpty a) = Let6989586621679107801L'Sym2 js'6989586621679107800 is'6989586621679107797 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679108421Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (xs''6989586621679108420 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108421Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (xs''6989586621679108420 :: NonEmpty a) = Lambda_6989586621679108421Sym1 xs''6989586621679108420 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679108443Sym2 xs6989586621679108440 xs'6989586621679108441 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys6989586621679108442 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108443Sym2 xs6989586621679108440 xs'6989586621679108441 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys6989586621679108442 :: NonEmpty a) = Lambda_6989586621679108443Sym3 xs6989586621679108440 xs'6989586621679108441 ys6989586621679108442
type Apply (Lambda_6989586621679108479Sym4 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679108473 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym4 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679108473 :: IList s) = Lambda_6989586621679108479Sym5 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473
type Apply (Lambda_6989586621679108418Sym3 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679108417 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108418Sym3 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679108417 :: NonEmpty a) = Lambda_6989586621679108418Sym4 xs6989586621679108414 ys6989586621679108415 xs'6989586621679108416 ys'6989586621679108417
type Apply (Lambda_6989586621679108479Sym5 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679108474 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym5 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679108474 :: [(VSpace s n, IList s)]) = Lambda_6989586621679108479Sym6 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472 yl6989586621679108473 ys6989586621679108474
type Apply (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679108211 :: 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) (a6989586621679108211 :: VSpace s n) = CanTransposeConSym1 a6989586621679108211
type Apply (CanTransposeCovSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679108156 :: 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) (a6989586621679108156 :: VSpace s n) = CanTransposeCovSym1 a6989586621679108156
type Apply (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679108129 :: 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) (a6989586621679108129 :: VSpace s n) = CanTransposeSym1 a6989586621679108129
type Apply (Lambda_6989586621679108479Sym0 :: 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) (xv6989586621679108469 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym0 :: 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) (xv6989586621679108469 :: VSpace s n) = Lambda_6989586621679108479Sym1 xv6989586621679108469
type Apply (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) (a6989586621679107830 :: 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) (a6989586621679107830 :: VSpace s n) = RelabelRSym1 a6989586621679107830
type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679108035 :: 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) (a6989586621679108035 :: VSpace s n) = TranspositionsSym1 a6989586621679108035
type Apply (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108081 :: 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) (a6989586621679108081 :: VSpace s n) = CanTransposeMultSym1 a6989586621679108081
type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679108084 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679108084 :: VSpace s n) = Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084
type Apply (Lambda_6989586621679108479Sym3 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679108472 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679108479Sym3 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679108472 :: VSpace s n) = Lambda_6989586621679108479Sym4 xv6989586621679108469 xl6989586621679108470 xs6989586621679108471 yv6989586621679108472

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
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 #

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) #

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_6989586621679112456Sym0 :: 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_6989586621679112477Sym0 :: 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 a6989586621679108616 :: TyFun (Ix a) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679112456Sym1 a6989586621679112466 :: TyFun (Ix a) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679112477Sym1 a6989586621679112482 :: 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 a6989586621679108129 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108110GoSym0 :: 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 a6989586621679108129 a6989586621679108130 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108110GoSym1 i6989586621679108108 :: 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 (Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: 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) (a6989586621679107655 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IConSym0 :: TyFun a (Ix a) -> Type) (a6989586621679107655 :: a) = IConSym1 a6989586621679107655
type Apply (ICovSym0 :: TyFun a (Ix a) -> Type) (a6989586621679107657 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ICovSym0 :: TyFun a (Ix a) -> Type) (a6989586621679107657 :: a) = ICovSym1 a6989586621679107657
type Apply (ShowsPrec_6989586621679112456Sym0 :: TyFun Nat (Ix a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679112466 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679112456Sym0 :: TyFun Nat (Ix a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679112466 :: Nat) = ShowsPrec_6989586621679112456Sym1 a6989586621679112466 :: TyFun (Ix a) (Symbol ~> Symbol) -> Type
type Apply (Let6989586621679108110GoSym1 i6989586621679108108 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679108109 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108110GoSym1 i6989586621679108108 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679108109 :: k) = Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type
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 Show_ (arg :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: Ix a) = Apply (Show__6989586621680640167Sym0 :: 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_6989586621680640175Sym0 :: 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_6989586621679835458Sym0 :: 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_6989586621679835442Sym0 :: 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_6989586621679835426Sym0 :: 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_6989586621679835410Sym0 :: 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_6989586621679835394Sym0 :: 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_6989586621679835378Sym0 :: 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_6989586621679112477Sym0 :: 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_6989586621679112571 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_6989586621679112456Sym0 :: TyFun Nat (Ix a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (IxCompareSym1 a6989586621679108616 :: TyFun (Ix a) Ordering -> Type) (a6989586621679108617 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IxCompareSym1 a6989586621679108616 :: TyFun (Ix a) Ordering -> Type) (a6989586621679108617 :: Ix a) = IxCompareSym2 a6989586621679108616 a6989586621679108617
type Apply (Compare_6989586621679112477Sym1 a6989586621679112482 :: TyFun (Ix a) Ordering -> Type) (a6989586621679112483 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679112477Sym1 a6989586621679112482 :: TyFun (Ix a) Ordering -> Type) (a6989586621679112483 :: Ix a) = Compare_6989586621679112477Sym2 a6989586621679112482 a6989586621679112483
type Apply (IxCompareSym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679108616 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IxCompareSym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679108616 :: Ix a) = IxCompareSym1 a6989586621679108616
type Apply (Compare_6989586621679112477Sym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679112482 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679112477Sym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679112482 :: Ix a) = Compare_6989586621679112477Sym1 a6989586621679112482
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679108545 :: [(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) (a6989586621679108545 :: [(VSpace s n, IList s)]) = HeadRSym1 a6989586621679108545
type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679108106 :: 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) (a6989586621679108106 :: Ix s) = RemoveUntilSym1 a6989586621679108106 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (ShowsPrec_6989586621679112456Sym1 a6989586621679112466 :: TyFun (Ix a) (Symbol ~> Symbol) -> Type) (a6989586621679112467 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679112456Sym1 a6989586621679112466 :: TyFun (Ix a) (Symbol ~> Symbol) -> Type) (a6989586621679112467 :: Ix a) = ShowsPrec_6989586621679112456Sym2 a6989586621679112466 a6989586621679112467
type Apply (CanTransposeSym1 a6989586621679108129 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108130 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679108129 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108130 :: Ix s) = CanTransposeSym2 a6989586621679108129 a6989586621679108130
type Apply (Let6989586621679108110GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679108108 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108110GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679108108 :: Ix s) = Let6989586621679108110GoSym1 i6989586621679108108 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type
type Apply (CanTransposeSym2 a6989586621679108129 a6989586621679108130 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108131 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679108129 a6989586621679108130 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108131 :: Ix s) = CanTransposeSym3 a6989586621679108129 a6989586621679108130 a6989586621679108131
type Apply (Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679108111 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108110GoSym2 i6989586621679108108 r6989586621679108109 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679108111 :: Ix s) = Let6989586621679108110GoSym3 i6989586621679108108 r6989586621679108109 a6989586621679108111 :: 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) (a6989586621679108129 :: 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) (a6989586621679108129 :: VSpace s n) = CanTransposeSym1 a6989586621679108129

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

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) #

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_6989586621679112536Sym0 :: 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 (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: 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_6989586621679112536Sym1 a6989586621679112546 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransConSym1 a6989586621679107666 :: TyFun (NonEmpty a) (TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransCovSym1 a6989586621679107669 :: 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 a6989586621679108035 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084 :: 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 (Let6989586621679108043Scrutinee_6989586621679101865Sym0 :: 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 (Let6989586621679108043Scrutinee_6989586621679101865Sym1 vs6989586621679108038 :: 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_6989586621679112536Sym0 :: TyFun Nat (TransRule a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679112546 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679112536Sym0 :: TyFun Nat (TransRule a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679112546 :: Nat) = ShowsPrec_6989586621679112536Sym1 a6989586621679112546 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type
type Apply (Let6989586621679108043Scrutinee_6989586621679101865Sym0 :: TyFun k1 (TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (vs6989586621679108038 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108043Scrutinee_6989586621679101865Sym0 :: TyFun k1 (TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (vs6989586621679108038 :: k1) = Let6989586621679108043Scrutinee_6989586621679101865Sym1 vs6989586621679108038 :: TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type
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 Show_ (arg :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: TransRule a) = Apply (Show__6989586621680640167Sym0 :: 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_6989586621680640175Sym0 :: 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_6989586621679112591 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) (a6989586621679108094 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (SaneTransRuleSym0 :: TyFun (TransRule a) Bool -> Type) (a6989586621679108094 :: TransRule a) = SaneTransRuleSym1 a6989586621679108094
type Apply (TransConSym1 a6989586621679107666 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679107667 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransConSym1 a6989586621679107666 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679107667 :: NonEmpty a) = TransConSym2 a6989586621679107666 a6989586621679107667
type Apply (TransCovSym1 a6989586621679107669 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679107670 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransCovSym1 a6989586621679107669 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679107670 :: NonEmpty a) = TransCovSym2 a6989586621679107669 a6989586621679107670
type Apply (TransConSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) (a6989586621679107666 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransConSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) (a6989586621679107666 :: NonEmpty a) = TransConSym1 a6989586621679107666
type Apply (TransCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) (a6989586621679107669 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) (a6989586621679107669 :: NonEmpty a) = TransCovSym1 a6989586621679107669
type Apply (ShowsPrec_6989586621679112536Sym1 a6989586621679112546 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type) (a6989586621679112547 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679112536Sym1 a6989586621679112546 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type) (a6989586621679112547 :: TransRule a) = ShowsPrec_6989586621679112536Sym2 a6989586621679112546 a6989586621679112547
type Apply (TranspositionsSym1 a6989586621679108035 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679108036 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679108035 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679108036 :: TransRule s) = TranspositionsSym2 a6989586621679108035 a6989586621679108036
type Apply (CanTransposeMultSym1 a6989586621679108081 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108082 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679108081 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679108082 :: TransRule s) = CanTransposeMultSym2 a6989586621679108081 a6989586621679108082
type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679108085 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679108085 :: TransRule s) = Let6989586621679108087Scrutinee_6989586621679101859Sym2 vs6989586621679108084 tl6989586621679108085
type Apply (Let6989586621679108043Scrutinee_6989586621679101865Sym1 vs6989586621679108038 :: TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (tl6989586621679108039 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108043Scrutinee_6989586621679101865Sym1 vs6989586621679108038 :: TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (tl6989586621679108039 :: TransRule a) = Let6989586621679108043Scrutinee_6989586621679101865Sym2 vs6989586621679108038 tl6989586621679108039 :: 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) (a6989586621679108035 :: 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) (a6989586621679108035 :: VSpace s n) = TranspositionsSym1 a6989586621679108035
type Apply (CanTransposeMultSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679108081 :: 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) (a6989586621679108081 :: VSpace s n) = CanTransposeMultSym1 a6989586621679108081
type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679108084 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679108084 :: VSpace s n) = Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084

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 #

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 #

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_6989586621679112409Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings FromNatSym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings ShowsPrec_6989586621679110643Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Signum_6989586621679112402Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Abs_6989586621679112395Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Negate_6989586621679112378Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings SSym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679111944Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679112385Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679112367Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679112355Sym0 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_6989586621679111944Sym1 a6989586621679111949 :: TyFun N Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679112385Sym1 a6989586621679112390 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679112367Sym1 a6989586621679112372 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679112355Sym1 a6989586621679112360 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679110643Sym1 a6989586621679110653 :: 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 (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: 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 a6989586621679107752 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107675Is'''Sym0 :: TyFun (NonEmpty (a6989586621679101722, b6989586621679101725)) (NonEmpty (N, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107675Is''Sym0 :: TyFun (NonEmpty (a6989586621679101722, k1)) (NonEmpty (N, k1)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107675Is'Sym0 :: TyFun (NonEmpty (a6989586621679101722, b6989586621679101723)) (NonEmpty (N, b6989586621679101723)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Transpositions'Sym1 a6989586621679107919 :: 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 a6989586621679108035 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107675Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679101724, b6989586621679101725) ~> NonEmpty (a6989586621679101724, N)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107675GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679101722, b6989586621679101723) ~> NonEmpty (N, b6989586621679101723)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925Xs'Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107967Sym0 :: 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_6989586621679107971Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Transpositions'Sym2 a6989586621679107919 a6989586621679107920 :: 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 a6989586621679108035 a6989586621679108036 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107675Go'Sym1 is6989586621679107674 :: TyFun N (NonEmpty (a6989586621679101724, b6989586621679101725) ~> NonEmpty (a6989586621679101724, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107675GoSym1 is6989586621679107674 :: TyFun N (NonEmpty (a6989586621679101722, b6989586621679101723) ~> NonEmpty (N, b6989586621679101723)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925FindSym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925Go'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925Xs'Sym1 sources6989586621679107922 :: TyFun k2 (TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107967Sym1 sources6989586621679107922 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107974Sym0 :: 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_6989586621679107971Sym1 sources6989586621679107922 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, 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 (Let6989586621679107925FindSym1 sources6989586621679107922 :: TyFun k2 (TyFun k3 (TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925Go'Sym1 sources6989586621679107922 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107974Sym1 ss6989586621679107973 :: 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_6989586621679107967Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107971Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107675Go'Sym2 is6989586621679107674 a6989586621679107684 :: TyFun (NonEmpty (a6989586621679101724, b6989586621679101725)) (NonEmpty (a6989586621679101724, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107675GoSym2 is6989586621679107674 a6989586621679107693 :: TyFun (NonEmpty (a6989586621679101722, b6989586621679101723)) (NonEmpty (N, b6989586621679101723)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925Xs'Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925FindSym2 sources6989586621679107922 targets6989586621679107923 :: TyFun k3 (TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925Go'Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun k3 (TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107967Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun k3 (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107974Sym2 ss6989586621679107973 sources6989586621679107922 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107971Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925Go'Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925FindSym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107974Sym3 ss6989586621679107973 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679107974Sym4 ss6989586621679107973 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun k4 (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925FindSym4 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 a6989586621679107937 :: TyFun (NonEmpty (N, Maybe a6989586621679101625)) (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679107925Go'Sym4 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 a6989586621679107957 :: TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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__6989586621680640167Sym0 :: 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_6989586621680640175Sym0 :: 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_6989586621679112385Sym0 a1) a2
type (a1 :: N) - (a2 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (a1 :: N) - (a2 :: N) = Apply (Apply TFHelper_6989586621679112367Sym0 a1) a2
type (a1 :: N) + (a2 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (a1 :: N) + (a2 :: N) = Apply (Apply TFHelper_6989586621679112355Sym0 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_6989586621679835458Sym0 :: 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_6989586621679835442Sym0 :: 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_6989586621679835426Sym0 :: 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_6989586621679835410Sym0 :: 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_6989586621679111944Sym0 a1) a2
type (arg :: N) < (arg1 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: N) < (arg1 :: N) = Apply (Apply (TFHelper_6989586621679835378Sym0 :: 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_6989586621679835357Sym0 :: 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_6989586621679112557 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_6989586621679110643Sym0 a1) a2) a3
type Apply FromInteger_6989586621679112409Sym0 (a6989586621679112413 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply FromInteger_6989586621679112409Sym0 (a6989586621679112413 :: Nat) = FromInteger_6989586621679112409Sym1 a6989586621679112413
type Apply FromNatSym0 (a6989586621679108638 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply FromNatSym0 (a6989586621679108638 :: Nat) = FromNatSym1 a6989586621679108638
type Apply Signum_6989586621679112402Sym0 (a6989586621679112406 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Signum_6989586621679112402Sym0 (a6989586621679112406 :: N) = Signum_6989586621679112402Sym1 a6989586621679112406
type Apply Abs_6989586621679112395Sym0 (a6989586621679112399 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Abs_6989586621679112395Sym0 (a6989586621679112399 :: N) = Abs_6989586621679112395Sym1 a6989586621679112399
type Apply Negate_6989586621679112378Sym0 (a6989586621679112382 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Negate_6989586621679112378Sym0 (a6989586621679112382 :: N) = Negate_6989586621679112378Sym1 a6989586621679112382
type Apply SSym0 (a6989586621679107649 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply SSym0 (a6989586621679107649 :: N) = SSym1 a6989586621679107649
type Apply (TFHelper_6989586621679111944Sym1 a6989586621679111949 :: TyFun N Bool -> Type) (a6989586621679111950 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679111944Sym1 a6989586621679111949 :: TyFun N Bool -> Type) (a6989586621679111950 :: N) = TFHelper_6989586621679111944Sym2 a6989586621679111949 a6989586621679111950
type Apply (TFHelper_6989586621679112385Sym1 a6989586621679112390 :: TyFun N N -> Type) (a6989586621679112391 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679112385Sym1 a6989586621679112390 :: TyFun N N -> Type) (a6989586621679112391 :: N) = TFHelper_6989586621679112385Sym2 a6989586621679112390 a6989586621679112391
type Apply (TFHelper_6989586621679112367Sym1 a6989586621679112372 :: TyFun N N -> Type) (a6989586621679112373 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679112367Sym1 a6989586621679112372 :: TyFun N N -> Type) (a6989586621679112373 :: N) = TFHelper_6989586621679112367Sym2 a6989586621679112372 a6989586621679112373
type Apply (TFHelper_6989586621679112355Sym1 a6989586621679112360 :: TyFun N N -> Type) (a6989586621679112361 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679112355Sym1 a6989586621679112360 :: TyFun N N -> Type) (a6989586621679112361 :: N) = TFHelper_6989586621679112355Sym2 a6989586621679112360 a6989586621679112361
type Apply (Lambda_6989586621679107967Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun k3 (Maybe N) -> Type) (lhs_69895866216791018916989586621679107969 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107967Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun k3 (Maybe N) -> Type) (lhs_69895866216791018916989586621679107969 :: k3) = Lambda_6989586621679107967Sym4 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 lhs_69895866216791018916989586621679107969
type Apply (Lambda_6989586621679107974Sym4 ss6989586621679107973 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun k4 (Maybe N) -> Type) (lhs_69895866216791018896989586621679107976 :: k4) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107974Sym4 ss6989586621679107973 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun k4 (Maybe N) -> Type) (lhs_69895866216791018896989586621679107976 :: k4) = Lambda_6989586621679107974Sym5 ss6989586621679107973 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 lhs_69895866216791018896989586621679107976
type Apply ShowsPrec_6989586621679110643Sym0 (a6989586621679110653 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply ShowsPrec_6989586621679110643Sym0 (a6989586621679110653 :: Nat) = ShowsPrec_6989586621679110643Sym1 a6989586621679110653
type Apply TFHelper_6989586621679111944Sym0 (a6989586621679111949 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679111944Sym0 (a6989586621679111949 :: N) = TFHelper_6989586621679111944Sym1 a6989586621679111949
type Apply TFHelper_6989586621679112385Sym0 (a6989586621679112390 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679112385Sym0 (a6989586621679112390 :: N) = TFHelper_6989586621679112385Sym1 a6989586621679112390
type Apply TFHelper_6989586621679112367Sym0 (a6989586621679112372 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679112367Sym0 (a6989586621679112372 :: N) = TFHelper_6989586621679112367Sym1 a6989586621679112372
type Apply TFHelper_6989586621679112355Sym0 (a6989586621679112360 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679112355Sym0 (a6989586621679112360 :: N) = TFHelper_6989586621679112355Sym1 a6989586621679112360
type Apply (ShowsPrec_6989586621679110643Sym1 a6989586621679110653 :: TyFun N (Symbol ~> Symbol) -> Type) (a6989586621679110654 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679110643Sym1 a6989586621679110653 :: TyFun N (Symbol ~> Symbol) -> Type) (a6989586621679110654 :: N) = ShowsPrec_6989586621679110643Sym2 a6989586621679110653 a6989586621679110654
type Apply (Let6989586621679107675Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679101724, b6989586621679101725) ~> NonEmpty (a6989586621679101724, N)) -> Type) -> Type) (is6989586621679107674 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107675Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679101724, b6989586621679101725) ~> NonEmpty (a6989586621679101724, N)) -> Type) -> Type) (is6989586621679107674 :: k) = Let6989586621679107675Go'Sym1 is6989586621679107674 :: TyFun N (NonEmpty (a6989586621679101724, b6989586621679101725) ~> NonEmpty (a6989586621679101724, N)) -> Type
type Apply (Let6989586621679107675GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679101722, b6989586621679101723) ~> NonEmpty (N, b6989586621679101723)) -> Type) -> Type) (is6989586621679107674 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107675GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679101722, b6989586621679101723) ~> NonEmpty (N, b6989586621679101723)) -> Type) -> Type) (is6989586621679107674 :: k) = Let6989586621679107675GoSym1 is6989586621679107674 :: TyFun N (NonEmpty (a6989586621679101722, b6989586621679101723) ~> NonEmpty (N, b6989586621679101723)) -> Type
type Apply (Let6989586621679107925Xs'Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925Xs'Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k1) = Let6989586621679107925Xs'Sym1 sources6989586621679107922 :: TyFun k2 (TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) -> Type
type Apply (Lambda_6989586621679107967Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107967Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k1) = Lambda_6989586621679107967Sym1 sources6989586621679107922 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679107971Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107971Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k1) = Lambda_6989586621679107971Sym1 sources6989586621679107922 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) -> Type) -> Type
type Apply (Let6989586621679107675Go'Sym1 is6989586621679107674 :: TyFun N (NonEmpty (a6989586621679101724, b6989586621679101725) ~> NonEmpty (a6989586621679101724, N)) -> Type) (a6989586621679107684 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107675Go'Sym1 is6989586621679107674 :: TyFun N (NonEmpty (a6989586621679101724, b6989586621679101725) ~> NonEmpty (a6989586621679101724, N)) -> Type) (a6989586621679107684 :: N) = Let6989586621679107675Go'Sym2 is6989586621679107674 a6989586621679107684 :: TyFun (NonEmpty (a6989586621679101724, b6989586621679101725)) (NonEmpty (a6989586621679101724, N)) -> Type
type Apply (Let6989586621679107675GoSym1 is6989586621679107674 :: TyFun N (NonEmpty (a6989586621679101722, b6989586621679101723) ~> NonEmpty (N, b6989586621679101723)) -> Type) (a6989586621679107693 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107675GoSym1 is6989586621679107674 :: TyFun N (NonEmpty (a6989586621679101722, b6989586621679101723) ~> NonEmpty (N, b6989586621679101723)) -> Type) (a6989586621679107693 :: N) = Let6989586621679107675GoSym2 is6989586621679107674 a6989586621679107693 :: TyFun (NonEmpty (a6989586621679101722, b6989586621679101723)) (NonEmpty (N, b6989586621679101723)) -> Type
type Apply (Let6989586621679107925FindSym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925FindSym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k1) = Let6989586621679107925FindSym1 sources6989586621679107922 :: TyFun k2 (TyFun k3 (TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) -> Type) -> Type
type Apply (Let6989586621679107925Go'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925Go'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k1) = Let6989586621679107925Go'Sym1 sources6989586621679107922 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) -> Type) -> Type
type Apply (Let6989586621679107925Xs'Sym1 sources6989586621679107922 :: TyFun k2 (TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) -> Type) (targets6989586621679107923 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925Xs'Sym1 sources6989586621679107922 :: TyFun k2 (TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) -> Type) (targets6989586621679107923 :: k2) = Let6989586621679107925Xs'Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type
type Apply (Lambda_6989586621679107967Sym1 sources6989586621679107922 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679107923 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107967Sym1 sources6989586621679107922 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679107923 :: k2) = Lambda_6989586621679107967Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type
type Apply (Lambda_6989586621679107974Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) -> Type) (ss6989586621679107973 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107974Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) -> Type) (ss6989586621679107973 :: k1) = Lambda_6989586621679107974Sym1 ss6989586621679107973 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679107925FindSym1 sources6989586621679107922 :: TyFun k2 (TyFun k3 (TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) -> Type) -> Type) (targets6989586621679107923 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925FindSym1 sources6989586621679107922 :: TyFun k2 (TyFun k3 (TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) -> Type) -> Type) (targets6989586621679107923 :: k2) = Let6989586621679107925FindSym2 sources6989586621679107922 targets6989586621679107923 :: TyFun k3 (TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) -> Type
type Apply (Let6989586621679107925Go'Sym1 sources6989586621679107922 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) -> Type) -> Type) (targets6989586621679107923 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925Go'Sym1 sources6989586621679107922 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) -> Type) -> Type) (targets6989586621679107923 :: k2) = Let6989586621679107925Go'Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun k3 (TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) -> Type
type Apply (Lambda_6989586621679107974Sym1 ss6989586621679107973 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107974Sym1 ss6989586621679107973 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679107922 :: k2) = Lambda_6989586621679107974Sym2 ss6989586621679107973 sources6989586621679107922 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type
type Apply (Let6989586621679107925FindSym2 sources6989586621679107922 targets6989586621679107923 :: TyFun k3 (TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) -> Type) (xs6989586621679107924 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925FindSym2 sources6989586621679107922 targets6989586621679107923 :: TyFun k3 (TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) -> Type) (xs6989586621679107924 :: k3) = Let6989586621679107925FindSym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type
type Apply (Let6989586621679107925Go'Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun k3 (TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) -> Type) (xs6989586621679107924 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925Go'Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun k3 (TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) -> Type) (xs6989586621679107924 :: k3) = Let6989586621679107925Go'Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type
type Apply (Lambda_6989586621679107974Sym2 ss6989586621679107973 sources6989586621679107922 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679107923 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107974Sym2 ss6989586621679107973 sources6989586621679107922 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679107923 :: k3) = Lambda_6989586621679107974Sym3 ss6989586621679107973 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type
type Apply (Let6989586621679107925Go'Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) (a6989586621679107957 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925Go'Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun N (NonEmpty a6989586621679101624 ~> NonEmpty (N, a6989586621679101624)) -> Type) (a6989586621679107957 :: N) = Let6989586621679107925Go'Sym4 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 a6989586621679107957 :: TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type
type Apply (Let6989586621679107925FindSym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) (a6989586621679107937 :: a6989586621679101625) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925FindSym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun a6989586621679101625 (NonEmpty (N, Maybe a6989586621679101625) ~> Maybe N) -> Type) (a6989586621679107937 :: a6989586621679101625) = Let6989586621679107925FindSym4 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 a6989586621679107937
type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679108576 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679108576 :: IList a) = LengthILSym1 a6989586621679108576
type Apply (LengthNESym0 :: TyFun (NonEmpty a) N -> Type) (a6989586621679108583 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthNESym0 :: TyFun (NonEmpty a) N -> Type) (a6989586621679108583 :: NonEmpty a) = LengthNESym1 a6989586621679108583
type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679108571 :: [(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) (a6989586621679108571 :: [(VSpace s n, IList s)]) = LengthRSym1 a6989586621679108571
type Apply (RelabelTranspositions'Sym0 :: TyFun (NonEmpty (a, a)) [(N, N)] -> Type) (a6989586621679107673 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositions'Sym0 :: TyFun (NonEmpty (a, a)) [(N, N)] -> Type) (a6989586621679107673 :: NonEmpty (a, a)) = RelabelTranspositions'Sym1 a6989586621679107673
type Apply (RelabelTranspositionsSym1 a6989586621679107752 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679107753 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym1 a6989586621679107752 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679107753 :: IList a) = RelabelTranspositionsSym2 a6989586621679107752 a6989586621679107753
type Apply (Let6989586621679107675Is'''Sym0 :: TyFun (NonEmpty (a6989586621679101722, b6989586621679101725)) (NonEmpty (N, N)) -> Type) (is6989586621679107674 :: NonEmpty (a6989586621679101722, b6989586621679101725)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107675Is'''Sym0 :: TyFun (NonEmpty (a6989586621679101722, b6989586621679101725)) (NonEmpty (N, N)) -> Type) (is6989586621679107674 :: NonEmpty (a6989586621679101722, b6989586621679101725)) = Let6989586621679107675Is'''Sym1 is6989586621679107674
type Apply (Let6989586621679107675Is''Sym0 :: TyFun (NonEmpty (a6989586621679101722, k1)) (NonEmpty (N, k1)) -> Type) (is6989586621679107674 :: NonEmpty (a6989586621679101722, k1)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107675Is''Sym0 :: TyFun (NonEmpty (a6989586621679101722, k1)) (NonEmpty (N, k1)) -> Type) (is6989586621679107674 :: NonEmpty (a6989586621679101722, k1)) = Let6989586621679107675Is''Sym1 is6989586621679107674
type Apply (Let6989586621679107675Is'Sym0 :: TyFun (NonEmpty (a6989586621679101722, b6989586621679101723)) (NonEmpty (N, b6989586621679101723)) -> Type) (is6989586621679107674 :: NonEmpty (a6989586621679101722, b6989586621679101723)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107675Is'Sym0 :: TyFun (NonEmpty (a6989586621679101722, b6989586621679101723)) (NonEmpty (N, b6989586621679101723)) -> Type) (is6989586621679107674 :: NonEmpty (a6989586621679101722, b6989586621679101723)) = Let6989586621679107675Is'Sym1 is6989586621679107674
type Apply (Transpositions'Sym2 a6989586621679107919 a6989586621679107920 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) (a6989586621679107921 :: NonEmpty (Maybe a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Transpositions'Sym2 a6989586621679107919 a6989586621679107920 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) (a6989586621679107921 :: NonEmpty (Maybe a)) = Transpositions'Sym3 a6989586621679107919 a6989586621679107920 a6989586621679107921
type Apply (TranspositionsSym2 a6989586621679108035 a6989586621679108036 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679108037 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679108035 a6989586621679108036 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679108037 :: [(VSpace s n, IList s)]) = TranspositionsSym3 a6989586621679108035 a6989586621679108036 a6989586621679108037
type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym2 vs6989586621679108084 tl6989586621679108085 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679108086 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym2 vs6989586621679108084 tl6989586621679108085 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679108086 :: [(VSpace s n, IList s)]) = Let6989586621679108087Scrutinee_6989586621679101859Sym3 vs6989586621679108084 tl6989586621679108085 r6989586621679108086
type Apply (Let6989586621679107675Go'Sym2 is6989586621679107674 a6989586621679107684 :: TyFun (NonEmpty (a6989586621679101724, b6989586621679101725)) (NonEmpty (a6989586621679101724, N)) -> Type) (a6989586621679107685 :: NonEmpty (a6989586621679101724, b6989586621679101725)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107675Go'Sym2 is6989586621679107674 a6989586621679107684 :: TyFun (NonEmpty (a6989586621679101724, b6989586621679101725)) (NonEmpty (a6989586621679101724, N)) -> Type) (a6989586621679107685 :: NonEmpty (a6989586621679101724, b6989586621679101725)) = Let6989586621679107675Go'Sym3 is6989586621679107674 a6989586621679107684 a6989586621679107685
type Apply (Let6989586621679107675GoSym2 is6989586621679107674 a6989586621679107693 :: TyFun (NonEmpty (a6989586621679101722, b6989586621679101723)) (NonEmpty (N, b6989586621679101723)) -> Type) (a6989586621679107694 :: NonEmpty (a6989586621679101722, b6989586621679101723)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107675GoSym2 is6989586621679107674 a6989586621679107693 :: TyFun (NonEmpty (a6989586621679101722, b6989586621679101723)) (NonEmpty (N, b6989586621679101723)) -> Type) (a6989586621679107694 :: NonEmpty (a6989586621679101722, b6989586621679101723)) = Let6989586621679107675GoSym3 is6989586621679107674 a6989586621679107693 a6989586621679107694
type Apply (Let6989586621679107925Xs'Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) (xs6989586621679107924 :: NonEmpty a6989586621679101624) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925Xs'Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) (xs6989586621679107924 :: NonEmpty a6989586621679101624) = Let6989586621679107925Xs'Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924
type Apply (Lambda_6989586621679107971Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) (ss6989586621679107973 :: NonEmpty a6989586621679101626) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107971Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) (ss6989586621679107973 :: NonEmpty a6989586621679101626) = Lambda_6989586621679107971Sym4 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 ss6989586621679107973
type Apply (Let6989586621679107925FindSym4 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 a6989586621679107937 :: TyFun (NonEmpty (N, Maybe a6989586621679101625)) (Maybe N) -> Type) (a6989586621679107938 :: NonEmpty (N, Maybe a6989586621679101625)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925FindSym4 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 a6989586621679107937 :: TyFun (NonEmpty (N, Maybe a6989586621679101625)) (Maybe N) -> Type) (a6989586621679107938 :: NonEmpty (N, Maybe a6989586621679101625)) = Let6989586621679107925FindSym5 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 a6989586621679107937 a6989586621679107938
type Apply (Let6989586621679107925Go'Sym4 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 a6989586621679107957 :: TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) (a6989586621679107958 :: NonEmpty a6989586621679101624) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679107925Go'Sym4 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 a6989586621679107957 :: TyFun (NonEmpty a6989586621679101624) (NonEmpty (N, a6989586621679101624)) -> Type) (a6989586621679107958 :: NonEmpty a6989586621679101624) = Let6989586621679107925Go'Sym5 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 a6989586621679107957 a6989586621679107958
type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) (a6989586621679107752 :: 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) (a6989586621679107752 :: NonEmpty (a, a)) = RelabelTranspositionsSym1 a6989586621679107752
type Apply (Transpositions'Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> (NonEmpty (Maybe a) ~> Maybe [(N, N)])) -> Type) (a6989586621679107919 :: 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) (a6989586621679107919 :: NonEmpty a) = Transpositions'Sym1 a6989586621679107919
type Apply (Transpositions'Sym1 a6989586621679107919 :: TyFun (NonEmpty a) (NonEmpty (Maybe a) ~> Maybe [(N, N)]) -> Type) (a6989586621679107920 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Transpositions'Sym1 a6989586621679107919 :: TyFun (NonEmpty a) (NonEmpty (Maybe a) ~> Maybe [(N, N)]) -> Type) (a6989586621679107920 :: NonEmpty a) = Transpositions'Sym2 a6989586621679107919 a6989586621679107920
type Apply (TranspositionsSym1 a6989586621679108035 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679108036 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679108035 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679108036 :: TransRule s) = TranspositionsSym2 a6989586621679108035 a6989586621679108036
type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679108085 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679108085 :: TransRule s) = Let6989586621679108087Scrutinee_6989586621679101859Sym2 vs6989586621679108084 tl6989586621679108085
type Apply (Lambda_6989586621679107971Sym1 sources6989586621679107922 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) -> Type) -> Type) (targets6989586621679107923 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107971Sym1 sources6989586621679107922 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) -> Type) -> Type) (targets6989586621679107923 :: NonEmpty a) = Lambda_6989586621679107971Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) -> Type
type Apply (Lambda_6989586621679107967Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) (xs6989586621679107924 :: NonEmpty (Maybe k3)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107967Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) (xs6989586621679107924 :: NonEmpty (Maybe k3)) = Lambda_6989586621679107967Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924
type Apply (Lambda_6989586621679107971Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) -> Type) (xs6989586621679107924 :: NonEmpty (Maybe a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107971Sym2 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type) -> Type) (xs6989586621679107924 :: NonEmpty (Maybe a)) = Lambda_6989586621679107971Sym3 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924 :: TyFun (NonEmpty a6989586621679101626) (Maybe [(a6989586621679101626, N)]) -> Type
type Apply (Lambda_6989586621679107974Sym3 ss6989586621679107973 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) (xs6989586621679107924 :: NonEmpty (Maybe k4)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679107974Sym3 ss6989586621679107973 sources6989586621679107922 targets6989586621679107923 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) (xs6989586621679107924 :: NonEmpty (Maybe k4)) = Lambda_6989586621679107974Sym4 ss6989586621679107973 sources6989586621679107922 targets6989586621679107923 xs6989586621679107924
type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679108035 :: 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) (a6989586621679108035 :: VSpace s n) = TranspositionsSym1 a6989586621679108035
type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679108084 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679108087Scrutinee_6989586621679101859Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679108084 :: VSpace s n) = Let6989586621679108087Scrutinee_6989586621679101859Sym1 vs6989586621679108084

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 #

vecFromListUnsafe :: forall (n :: N) a. Sing n -> [a] -> Vec n a Source #