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

Contents

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

(ShowSing a, ShowSing b) => Show (Sing z) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> 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 :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: 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 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

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

(%==) :: Sing a0 -> Sing b0 -> Sing (a0 == b0) #

(%/=) :: 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

(%~) :: 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 :: 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 SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2ConRankSym0 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 SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym1 a6989586621679606233 :: 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 (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 (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 (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 (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 (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

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679136367Sym0 :: TyFun Nat (VSpace a6989586621679120380 b6989586621679120381 ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (VIdSym0 :: TyFun (VSpace a6989586621679120380 b6989586621679120381) a6989586621679120380 -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (VDimSym0 :: TyFun (VSpace a6989586621679120380 b6989586621679120381) b6989586621679120381 -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym0 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679136382Sym0 :: TyFun (VSpace a6989586621679120380 b6989586621679120381) (VSpace a6989586621679120380 b6989586621679120381 ~> Ordering) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (VSpaceSym0 :: TyFun a6989586621679120380 (b6989586621679120381 ~> VSpace a6989586621679120380 b6989586621679120381) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (EpsilonInvRankSym2 a6989586621679606504 a6989586621679606503 :: 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 (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 (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 (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 (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 (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

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 a6989586621679131011 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RemoveUntilSym1 a6989586621679131155 n6989586621679120272 :: TyFun [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606463RSym1 vid6989586621679606458 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606408RSym1 vid6989586621679606403 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (DeltaRankSym3 a6989586621679606551 a6989586621679606550 a6989586621679606549 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym3 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym3 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym3 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym3 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym3 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym3 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym3 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym3 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679136367Sym1 a6989586621679136364 a6989586621679120380 b6989586621679120381 :: TyFun (VSpace a6989586621679120380 b6989586621679120381) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679136382Sym1 a6989586621679136380 :: TyFun (VSpace a6989586621679120380 b6989586621679120381) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym1 a6989586621679130754 :: TyFun (Ix s6989586621679120273) (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131161GoSym0 :: TyFun (Ix s6989586621679120291) (TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym1 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym1 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym1 a6989586621679131511 :: TyFun (TransRule s6989586621679120268) ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (VSpaceSym1 t6989586621679130247 b6989586621679120381 :: TyFun b6989586621679120381 (VSpace a6989586621679120380 b6989586621679120381) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeConSym1 a6989586621679130564 :: TyFun s6989586621679120277 (s6989586621679120277 ~> ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym1 a6989586621679130659 :: TyFun s6989586621679120275 (s6989586621679120275 ~> ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606251RSym1 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606286RSym1 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606321RSym1 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606356RSym1 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (RelabelRSym1 a6989586621679131310 :: TyFun (NonEmpty (s6989586621679120259, s6989586621679120259)) ([(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] ~> Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

(SOrd s, SingI d) => SingI (RemoveUntilSym1 d n :: 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 n) #

(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 (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 (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 (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 (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 (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 (TyCon1 (VSpace d :: b -> VSpace a b) :: b ~> VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon1 (VSpace d)) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (VSpaceSym1 d b) #

(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_6989586621679131032Sym2 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelRSym2 a6989586621679131311 a6989586621679131310 :: TyFun [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] (Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym2 a6989586621679131459 a6989586621679131458 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131520Scrutinee_6989586621679120863Sym2 tl6989586621679131518 vs6989586621679131517 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym2 a6989586621679131512 a6989586621679131511 :: TyFun [(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (SurjSym2ConRankSym4 a6989586621679606491 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym4 a6989586621679606451 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym4 a6989586621679606436 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym4 a6989586621679606396 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym4 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym4 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym4 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym4 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (CanTransposeSym2 a6989586621679130755 a6989586621679130754 :: TyFun (Ix s6989586621679120273) ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeConSym2 a6989586621679130565 a6989586621679130564 :: TyFun s6989586621679120277 ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym2 a6989586621679130660 a6989586621679130659 :: TyFun s6989586621679120275 ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606251RSym2 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606286RSym2 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606321RSym2 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606356RSym2 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606463RSym2 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606408RSym2 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> 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 (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 (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 (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 (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 (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) #

SingI (TyCon2 (VSpace :: a -> b -> VSpace a b) :: a ~> (b ~> VSpace a b)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon2 VSpace) #

SuppressUnusedWarnings (CanTransposeConSym3 a6989586621679130566 a6989586621679130565 a6989586621679130564 :: TyFun [(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym3 a6989586621679130661 a6989586621679130660 a6989586621679130659 :: TyFun [(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym3 a6989586621679130756 a6989586621679130755 a6989586621679130754 :: TyFun [(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjAreaConRankSym5 a6989586621679606342 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym5 a6989586621679606307 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym5 a6989586621679606272 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym5 a6989586621679606237 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym3 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131161GoSym2 r6989586621679131160 i6989586621679131159 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606251RSym3 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606286RSym3 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606321RSym3 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606356RSym3 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606463RSym3 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606408RSym3 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> 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 (Let6989586621679131161GoSym3 a6989586621679131162 r6989586621679131160 i6989586621679131159 :: TyFun [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym4 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606251RSym4 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606286RSym4 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606321RSym4 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606356RSym4 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606463RSym4 b6989586621679606461 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606408RSym4 b6989586621679606406 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym5 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606251RSym5 d6989586621679606249 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606286RSym5 d6989586621679606284 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606321RSym5 d6989586621679606319 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606356RSym5 d6989586621679606354 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym6 ys6989586621679131022 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) (Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) (a6989586621679131215 :: [(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) (a6989586621679131215 :: [(VSpace a b, IList a)]) = Sane a6989586621679131215
type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679131188 :: [(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) (a6989586621679131188 :: [(VSpace s n, IList s)]) = LengthR a6989586621679131188
type Apply (CanTransposeMultSym2 a6989586621679131512 a6989586621679131511 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679131513 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym2 a6989586621679131512 a6989586621679131511 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679131513 :: [(VSpace s n, IList s)]) = CanTransposeMult a6989586621679131512 a6989586621679131511 a6989586621679131513
type Apply (CanTransposeConSym3 a6989586621679130566 a6989586621679130565 a6989586621679130564 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130567 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym3 a6989586621679130566 a6989586621679130565 a6989586621679130564 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130567 :: [(VSpace s n, IList s)]) = CanTransposeCon a6989586621679130566 a6989586621679130565 a6989586621679130564 a6989586621679130567
type Apply (CanTransposeCovSym3 a6989586621679130661 a6989586621679130660 a6989586621679130659 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130662 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym3 a6989586621679130661 a6989586621679130660 a6989586621679130659 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130662 :: [(VSpace s n, IList s)]) = CanTransposeCov a6989586621679130661 a6989586621679130660 a6989586621679130659 a6989586621679130662
type Apply (CanTransposeSym3 a6989586621679130756 a6989586621679130755 a6989586621679130754 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130757 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym3 a6989586621679130756 a6989586621679130755 a6989586621679130754 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130757 :: [(VSpace s n, IList s)]) = CanTranspose a6989586621679130756 a6989586621679130755 a6989586621679130754 a6989586621679130757
type Apply (VIdSym0 :: TyFun (VSpace a b) a -> Type) (a6989586621679130239 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (VIdSym0 :: TyFun (VSpace a b) a -> Type) (a6989586621679130239 :: VSpace a b) = VId a6989586621679130239
type Apply (VDimSym0 :: TyFun (VSpace a b) b -> Type) (a6989586621679130242 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (VDimSym0 :: TyFun (VSpace a b) b -> Type) (a6989586621679130242 :: VSpace a b) = VDim a6989586621679130242
type Apply (Compare_6989586621679136382Sym1 a6989586621679136380 :: TyFun (VSpace a b) Ordering -> Type) (a6989586621679136381 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679136382Sym1 a6989586621679136380 :: TyFun (VSpace a b) Ordering -> Type) (a6989586621679136381 :: VSpace a b) = Compare_6989586621679136382 a6989586621679136380 a6989586621679136381
type Apply (DeltaRankSym3 a6989586621679606551 a6989586621679606550 a6989586621679606549 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679606552 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym3 a6989586621679606551 a6989586621679606550 a6989586621679606549 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679606552 :: Symbol) = DeltaRank a6989586621679606551 a6989586621679606550 a6989586621679606549 a6989586621679606552
type Apply (SurjSym2ConRankSym4 a6989586621679606491 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606492 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym4 a6989586621679606491 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606492 :: Symbol) = SurjSym2ConRank a6989586621679606491 a6989586621679606490 a6989586621679606489 a6989586621679606488 a6989586621679606492
type Apply (InjSym2CovRankSym4 a6989586621679606451 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606452 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym4 a6989586621679606451 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606452 :: Symbol) = InjSym2CovRank a6989586621679606451 a6989586621679606450 a6989586621679606449 a6989586621679606448 a6989586621679606452
type Apply (SurjSym2CovRankSym4 a6989586621679606436 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606437 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym4 a6989586621679606436 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606437 :: Symbol) = SurjSym2CovRank a6989586621679606436 a6989586621679606435 a6989586621679606434 a6989586621679606433 a6989586621679606437
type Apply (InjSym2ConRankSym4 a6989586621679606396 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606397 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym4 a6989586621679606396 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606397 :: Symbol) = InjSym2ConRank a6989586621679606396 a6989586621679606395 a6989586621679606394 a6989586621679606393 a6989586621679606397
type Apply (InjAreaConRankSym5 a6989586621679606342 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606343 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym5 a6989586621679606342 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606343 :: Symbol) = InjAreaConRank a6989586621679606342 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 a6989586621679606343
type Apply (InjAreaCovRankSym5 a6989586621679606307 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606308 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym5 a6989586621679606307 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606308 :: Symbol) = InjAreaCovRank a6989586621679606307 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 a6989586621679606308
type Apply (SurjAreaConRankSym5 a6989586621679606272 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606273 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym5 a6989586621679606272 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606273 :: Symbol) = SurjAreaConRank a6989586621679606272 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 a6989586621679606273
type Apply (SurjAreaCovRankSym5 a6989586621679606237 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606238 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym5 a6989586621679606237 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606238 :: Symbol) = SurjAreaCovRank a6989586621679606237 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 a6989586621679606238
type Apply (Let6989586621679606463RSym4 b6989586621679606461 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606462 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606463RSym4 b6989586621679606461 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606462 :: a6989586621679120391) = Let6989586621679606463R b6989586621679606461 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 i6989586621679606462
type Apply (Let6989586621679606408RSym4 b6989586621679606406 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606407 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606408RSym4 b6989586621679606406 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606407 :: a6989586621679120391) = Let6989586621679606408R b6989586621679606406 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 i6989586621679606407
type Apply (Let6989586621679606251RSym5 d6989586621679606249 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606250 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym5 d6989586621679606249 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606250 :: a6989586621679120391) = Let6989586621679606251R d6989586621679606249 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 i6989586621679606250
type Apply (Let6989586621679606286RSym5 d6989586621679606284 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606285 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym5 d6989586621679606284 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606285 :: a6989586621679120391) = Let6989586621679606286R d6989586621679606284 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 i6989586621679606285
type Apply (Let6989586621679606321RSym5 d6989586621679606319 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606320 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym5 d6989586621679606319 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606320 :: a6989586621679120391) = Let6989586621679606321R d6989586621679606319 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 i6989586621679606320
type Apply (Let6989586621679606356RSym5 d6989586621679606354 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606355 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym5 d6989586621679606354 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606355 :: a6989586621679120391) = Let6989586621679606356R d6989586621679606354 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 i6989586621679606355
type Apply (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679130885 :: [(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) (a6989586621679130885 :: [(VSpace s n, IList s)]) = ContractR a6989586621679130885
type Apply (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679131056 :: [(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) (a6989586621679131056 :: [(VSpace s n, IList s)]) = TailR a6989586621679131056
type Apply (EpsilonRankSym2 a6989586621679606527 a6989586621679606526 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606528 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym2 a6989586621679606527 a6989586621679606526 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606528 :: NonEmpty Symbol) = EpsilonRank a6989586621679606527 a6989586621679606526 a6989586621679606528
type Apply (EpsilonInvRankSym2 a6989586621679606504 a6989586621679606503 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606505 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym2 a6989586621679606504 a6989586621679606503 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606505 :: NonEmpty Symbol) = EpsilonInvRank a6989586621679606504 a6989586621679606503 a6989586621679606505
type Apply (RemoveUntilSym1 a6989586621679131155 n :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679131156 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym1 a6989586621679131155 n :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679131156 :: [(VSpace s n, IList s)]) = RemoveUntil a6989586621679131155 a6989586621679131156
type Apply (MergeRSym1 a6989586621679131011 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679131012 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym1 a6989586621679131011 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679131012 :: [(VSpace s n, IList s)]) = MergeR a6989586621679131011 a6989586621679131012
type Apply (TranspositionsSym2 a6989586621679131459 a6989586621679131458 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679131460 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679131459 a6989586621679131458 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679131460 :: [(VSpace s n, IList s)]) = Transpositions a6989586621679131459 a6989586621679131458 a6989586621679131460
type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym2 tl6989586621679131518 vs6989586621679131517 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) (r6989586621679131519 :: [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym2 tl6989586621679131518 vs6989586621679131517 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) (r6989586621679131519 :: [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)]) = Let6989586621679131520Scrutinee_6989586621679120863 tl6989586621679131518 vs6989586621679131517 r6989586621679131519
type Apply (RelabelRSym2 a6989586621679131311 a6989586621679131310 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679131312 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym2 a6989586621679131311 a6989586621679131310 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679131312 :: [(VSpace s n, IList s)]) = RelabelR a6989586621679131311 a6989586621679131310 a6989586621679131312
type Apply (Let6989586621679131161GoSym3 a6989586621679131162 r6989586621679131160 i6989586621679131159 :: TyFun [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] -> Type) (a6989586621679131163 :: [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131161GoSym3 a6989586621679131162 r6989586621679131160 i6989586621679131159 :: TyFun [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] -> Type) (a6989586621679131163 :: [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) = Let6989586621679131161Go a6989586621679131162 r6989586621679131160 i6989586621679131159 a6989586621679131163
type Apply (Lambda_6989586621679131032Sym6 ys6989586621679131022 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) (Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (t6989586621679131047 :: IList s6989586621679120289) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym6 ys6989586621679131022 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) (Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (t6989586621679131047 :: IList s6989586621679120289) = Lambda_6989586621679131032 ys6989586621679131022 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 t6989586621679131047
data Sing (c :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

data Sing (c :: VSpace a b) where
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__6989586621680262835Sym0 :: 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_6989586621680262846Sym0 :: 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_6989586621679380340Sym0 :: 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_6989586621679380322Sym0 :: 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_6989586621679380304Sym0 :: 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_6989586621679380286Sym0 :: 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_6989586621679380268Sym0 :: 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_6989586621679380250Sym0 :: 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_6989586621679136382Sym0 :: 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_6989586621679136504 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_6989586621679136367Sym0 :: TyFun Nat (VSpace a1 b ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply DeltaRankSym0 (a6989586621679606549 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply DeltaRankSym0 (a6989586621679606549 :: Symbol) = DeltaRankSym1 a6989586621679606549
type Apply SurjSym2ConRankSym0 (a6989586621679606488 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2ConRankSym0 (a6989586621679606488 :: Symbol) = SurjSym2ConRankSym1 a6989586621679606488
type Apply InjSym2CovRankSym0 (a6989586621679606448 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2CovRankSym0 (a6989586621679606448 :: Symbol) = InjSym2CovRankSym1 a6989586621679606448
type Apply SurjSym2CovRankSym0 (a6989586621679606433 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2CovRankSym0 (a6989586621679606433 :: Symbol) = SurjSym2CovRankSym1 a6989586621679606433
type Apply InjSym2ConRankSym0 (a6989586621679606393 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2ConRankSym0 (a6989586621679606393 :: Symbol) = InjSym2ConRankSym1 a6989586621679606393
type Apply EpsilonRankSym0 (a6989586621679606526 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonRankSym0 (a6989586621679606526 :: Symbol) = EpsilonRankSym1 a6989586621679606526
type Apply EpsilonInvRankSym0 (a6989586621679606503 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonInvRankSym0 (a6989586621679606503 :: Symbol) = EpsilonInvRankSym1 a6989586621679606503
type Apply InjAreaConRankSym0 (a6989586621679606338 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaConRankSym0 (a6989586621679606338 :: Symbol) = InjAreaConRankSym1 a6989586621679606338
type Apply InjAreaCovRankSym0 (a6989586621679606303 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaCovRankSym0 (a6989586621679606303 :: Symbol) = InjAreaCovRankSym1 a6989586621679606303
type Apply SurjAreaConRankSym0 (a6989586621679606268 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjAreaConRankSym0 (a6989586621679606268 :: Symbol) = SurjAreaConRankSym1 a6989586621679606268
type Apply SurjAreaCovRankSym0 (a6989586621679606233 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym1 a6989586621679606549 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606550 :: Nat) = DeltaRankSym2 a6989586621679606549 a6989586621679606550
type Apply (SurjSym2ConRankSym1 a6989586621679606488 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606489 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym1 a6989586621679606488 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606489 :: Nat) = SurjSym2ConRankSym2 a6989586621679606488 a6989586621679606489
type Apply (InjSym2CovRankSym1 a6989586621679606448 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606449 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym1 a6989586621679606448 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606449 :: Nat) = InjSym2CovRankSym2 a6989586621679606448 a6989586621679606449
type Apply (SurjSym2CovRankSym1 a6989586621679606433 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606434 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym1 a6989586621679606433 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606434 :: Nat) = SurjSym2CovRankSym2 a6989586621679606433 a6989586621679606434
type Apply (InjSym2ConRankSym1 a6989586621679606393 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606394 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym1 a6989586621679606393 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606394 :: Nat) = InjSym2ConRankSym2 a6989586621679606393 a6989586621679606394
type Apply (InjAreaConRankSym1 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606339 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym1 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606339 :: Symbol) = InjAreaConRankSym2 a6989586621679606338 a6989586621679606339
type Apply (InjAreaCovRankSym1 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606304 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym1 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606304 :: Symbol) = InjAreaCovRankSym2 a6989586621679606303 a6989586621679606304
type Apply (SurjAreaConRankSym1 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606269 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym1 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606269 :: Symbol) = SurjAreaConRankSym2 a6989586621679606268 a6989586621679606269
type Apply (SurjAreaCovRankSym1 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606234 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym1 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606234 :: Symbol) = SurjAreaCovRankSym2 a6989586621679606233 a6989586621679606234
type Apply (EpsilonRankSym1 a6989586621679606526 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606527 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym1 a6989586621679606526 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606527 :: Nat) = EpsilonRankSym2 a6989586621679606526 a6989586621679606527
type Apply (EpsilonInvRankSym1 a6989586621679606503 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606504 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym1 a6989586621679606503 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606504 :: Nat) = EpsilonInvRankSym2 a6989586621679606503 a6989586621679606504
type Apply (Let6989586621679606463RSym0 :: TyFun k1 (TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606458 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606463RSym0 :: TyFun k1 (TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606458 :: k1) = (Let6989586621679606463RSym1 vid6989586621679606458 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606408RSym0 :: TyFun k1 (TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606403 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606408RSym0 :: TyFun k1 (TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606403 :: k1) = (Let6989586621679606408RSym1 vid6989586621679606403 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606251RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606245 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606245 :: k1) = (Let6989586621679606251RSym1 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606286RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606280 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606280 :: k1) = (Let6989586621679606286RSym1 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606321RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606315 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606315 :: k1) = (Let6989586621679606321RSym1 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606356RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606350 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606350 :: k1) = (Let6989586621679606356RSym1 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (DeltaRankSym2 a6989586621679606550 a6989586621679606549 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606551 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym2 a6989586621679606550 a6989586621679606549 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606551 :: Symbol) = DeltaRankSym3 a6989586621679606550 a6989586621679606549 a6989586621679606551
type Apply (SurjSym2ConRankSym2 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606490 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym2 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606490 :: Symbol) = SurjSym2ConRankSym3 a6989586621679606489 a6989586621679606488 a6989586621679606490
type Apply (InjSym2CovRankSym2 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606450 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym2 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606450 :: Symbol) = InjSym2CovRankSym3 a6989586621679606449 a6989586621679606448 a6989586621679606450
type Apply (SurjSym2CovRankSym2 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606435 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym2 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606435 :: Symbol) = SurjSym2CovRankSym3 a6989586621679606434 a6989586621679606433 a6989586621679606435
type Apply (InjSym2ConRankSym2 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606395 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym2 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606395 :: Symbol) = InjSym2ConRankSym3 a6989586621679606394 a6989586621679606393 a6989586621679606395
type Apply (InjAreaConRankSym2 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606340 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym2 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606340 :: Symbol) = InjAreaConRankSym3 a6989586621679606339 a6989586621679606338 a6989586621679606340
type Apply (InjAreaCovRankSym2 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606305 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym2 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606305 :: Symbol) = InjAreaCovRankSym3 a6989586621679606304 a6989586621679606303 a6989586621679606305
type Apply (SurjAreaConRankSym2 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606270 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym2 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606270 :: Symbol) = SurjAreaConRankSym3 a6989586621679606269 a6989586621679606268 a6989586621679606270
type Apply (SurjAreaCovRankSym2 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606235 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym2 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606235 :: Symbol) = SurjAreaCovRankSym3 a6989586621679606234 a6989586621679606233 a6989586621679606235
type Apply (ShowsPrec_6989586621679136367Sym0 :: TyFun Nat (VSpace a6989586621679120380 b6989586621679120381 ~> (Symbol ~> Symbol)) -> Type) (a6989586621679136364 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679136367Sym0 :: TyFun Nat (VSpace a6989586621679120380 b6989586621679120381 ~> (Symbol ~> Symbol)) -> Type) (a6989586621679136364 :: Nat) = (ShowsPrec_6989586621679136367Sym1 a6989586621679136364 a6989586621679120380 b6989586621679120381 :: TyFun (VSpace a6989586621679120380 b6989586621679120381) (Symbol ~> Symbol) -> Type)
type Apply (VSpaceSym0 :: TyFun a6989586621679120380 (b6989586621679120381 ~> VSpace a6989586621679120380 b6989586621679120381) -> Type) (t6989586621679130247 :: a6989586621679120380) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (VSpaceSym0 :: TyFun a6989586621679120380 (b6989586621679120381 ~> VSpace a6989586621679120380 b6989586621679120381) -> Type) (t6989586621679130247 :: a6989586621679120380) = (VSpaceSym1 t6989586621679130247 b6989586621679120381 :: TyFun b6989586621679120381 (VSpace a6989586621679120380 b6989586621679120381) -> Type)
type Apply (Let6989586621679606251RSym1 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606246 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym1 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606246 :: a6989586621679120391) = Let6989586621679606251RSym2 vid6989586621679606245 a6989586621679606246
type Apply (Let6989586621679606286RSym1 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606281 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym1 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606281 :: a6989586621679120391) = Let6989586621679606286RSym2 vid6989586621679606280 a6989586621679606281
type Apply (Let6989586621679606321RSym1 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606316 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym1 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606316 :: a6989586621679120391) = Let6989586621679606321RSym2 vid6989586621679606315 a6989586621679606316
type Apply (Let6989586621679606356RSym1 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606351 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym1 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606351 :: a6989586621679120391) = Let6989586621679606356RSym2 vid6989586621679606350 a6989586621679606351
type Apply (Let6989586621679606463RSym1 vid6989586621679606458 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679606459 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606463RSym1 vid6989586621679606458 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679606459 :: Nat) = (Let6989586621679606463RSym2 vid6989586621679606458 vdim6989586621679606459 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type)
type Apply (Let6989586621679606408RSym1 vid6989586621679606403 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679606404 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606408RSym1 vid6989586621679606403 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679606404 :: Nat) = (Let6989586621679606408RSym2 vid6989586621679606403 vdim6989586621679606404 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type)
type Apply (VSpaceSym1 t6989586621679130247 b :: TyFun b (VSpace a b) -> Type) (t6989586621679130248 :: b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (VSpaceSym1 t6989586621679130247 b :: TyFun b (VSpace a b) -> Type) (t6989586621679130248 :: b) = VSpace t6989586621679130247 t6989586621679130248
type Apply (SurjSym2ConRankSym3 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606491 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym3 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606491 :: Symbol) = SurjSym2ConRankSym4 a6989586621679606490 a6989586621679606489 a6989586621679606488 a6989586621679606491
type Apply (InjSym2CovRankSym3 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606451 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym3 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606451 :: Symbol) = InjSym2CovRankSym4 a6989586621679606450 a6989586621679606449 a6989586621679606448 a6989586621679606451
type Apply (SurjSym2CovRankSym3 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606436 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym3 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606436 :: Symbol) = SurjSym2CovRankSym4 a6989586621679606435 a6989586621679606434 a6989586621679606433 a6989586621679606436
type Apply (InjSym2ConRankSym3 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606396 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym3 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606396 :: Symbol) = InjSym2ConRankSym4 a6989586621679606395 a6989586621679606394 a6989586621679606393 a6989586621679606396
type Apply (InjAreaConRankSym3 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606341 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym3 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606341 :: Symbol) = InjAreaConRankSym4 a6989586621679606340 a6989586621679606339 a6989586621679606338 a6989586621679606341
type Apply (InjAreaCovRankSym3 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606306 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym3 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606306 :: Symbol) = InjAreaCovRankSym4 a6989586621679606305 a6989586621679606304 a6989586621679606303 a6989586621679606306
type Apply (SurjAreaConRankSym3 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606271 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym3 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606271 :: Symbol) = SurjAreaConRankSym4 a6989586621679606270 a6989586621679606269 a6989586621679606268 a6989586621679606271
type Apply (SurjAreaCovRankSym3 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606236 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym3 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606236 :: Symbol) = SurjAreaCovRankSym4 a6989586621679606235 a6989586621679606234 a6989586621679606233 a6989586621679606236
type Apply (CanTransposeConSym1 a6989586621679130564 :: TyFun s6989586621679120277 (s6989586621679120277 ~> ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool)) -> Type) (a6989586621679130565 :: s6989586621679120277) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym1 a6989586621679130564 :: TyFun s6989586621679120277 (s6989586621679120277 ~> ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool)) -> Type) (a6989586621679130565 :: s6989586621679120277) = CanTransposeConSym2 a6989586621679130564 a6989586621679130565
type Apply (CanTransposeCovSym1 a6989586621679130659 :: TyFun s6989586621679120275 (s6989586621679120275 ~> ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool)) -> Type) (a6989586621679130660 :: s6989586621679120275) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym1 a6989586621679130659 :: TyFun s6989586621679120275 (s6989586621679120275 ~> ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool)) -> Type) (a6989586621679130660 :: s6989586621679120275) = CanTransposeCovSym2 a6989586621679130659 a6989586621679130660
type Apply (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) (r6989586621679131160 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) (r6989586621679131160 :: k) = (Let6989586621679131161GoSym2 i6989586621679131159 r6989586621679131160 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type)
type Apply (Let6989586621679606251RSym2 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606247 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym2 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606247 :: a6989586621679120391) = Let6989586621679606251RSym3 a6989586621679606246 vid6989586621679606245 b6989586621679606247
type Apply (Let6989586621679606286RSym2 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606282 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym2 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606282 :: a6989586621679120391) = Let6989586621679606286RSym3 a6989586621679606281 vid6989586621679606280 b6989586621679606282
type Apply (Let6989586621679606321RSym2 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606317 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym2 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606317 :: a6989586621679120391) = Let6989586621679606321RSym3 a6989586621679606316 vid6989586621679606315 b6989586621679606317
type Apply (Let6989586621679606356RSym2 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606352 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym2 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606352 :: a6989586621679120391) = Let6989586621679606356RSym3 a6989586621679606351 vid6989586621679606350 b6989586621679606352
type Apply (Let6989586621679606463RSym2 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (a6989586621679606460 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606463RSym2 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (a6989586621679606460 :: a6989586621679120391) = Let6989586621679606463RSym3 vdim6989586621679606459 vid6989586621679606458 a6989586621679606460
type Apply (Let6989586621679606408RSym2 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (a6989586621679606405 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606408RSym2 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (a6989586621679606405 :: a6989586621679120391) = Let6989586621679606408RSym3 vdim6989586621679606404 vid6989586621679606403 a6989586621679606405
type Apply (CanTransposeConSym2 a6989586621679130565 a6989586621679130564 :: TyFun s6989586621679120277 ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool) -> Type) (a6989586621679130566 :: s6989586621679120277) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym2 a6989586621679130565 a6989586621679130564 :: TyFun s6989586621679120277 ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool) -> Type) (a6989586621679130566 :: s6989586621679120277) = CanTransposeConSym3 a6989586621679130565 a6989586621679130564 a6989586621679130566
type Apply (CanTransposeCovSym2 a6989586621679130660 a6989586621679130659 :: TyFun s6989586621679120275 ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool) -> Type) (a6989586621679130661 :: s6989586621679120275) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym2 a6989586621679130660 a6989586621679130659 :: TyFun s6989586621679120275 ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool) -> Type) (a6989586621679130661 :: s6989586621679120275) = CanTransposeCovSym3 a6989586621679130660 a6989586621679130659 a6989586621679130661
type Apply (InjAreaConRankSym4 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606342 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym4 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606342 :: Symbol) = InjAreaConRankSym5 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 a6989586621679606342
type Apply (InjAreaCovRankSym4 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606307 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym4 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606307 :: Symbol) = InjAreaCovRankSym5 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 a6989586621679606307
type Apply (SurjAreaConRankSym4 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606272 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym4 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606272 :: Symbol) = SurjAreaConRankSym5 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 a6989586621679606272
type Apply (SurjAreaCovRankSym4 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606237 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym4 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606237 :: Symbol) = SurjAreaCovRankSym5 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 a6989586621679606237
type Apply (Let6989586621679606251RSym3 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606248 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym3 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606248 :: a6989586621679120391) = Let6989586621679606251RSym4 b6989586621679606247 a6989586621679606246 vid6989586621679606245 c6989586621679606248
type Apply (Let6989586621679606286RSym3 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606283 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym3 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606283 :: a6989586621679120391) = Let6989586621679606286RSym4 b6989586621679606282 a6989586621679606281 vid6989586621679606280 c6989586621679606283
type Apply (Let6989586621679606321RSym3 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606318 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym3 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606318 :: a6989586621679120391) = Let6989586621679606321RSym4 b6989586621679606317 a6989586621679606316 vid6989586621679606315 c6989586621679606318
type Apply (Let6989586621679606356RSym3 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606353 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym3 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606353 :: a6989586621679120391) = Let6989586621679606356RSym4 b6989586621679606352 a6989586621679606351 vid6989586621679606350 c6989586621679606353
type Apply (Let6989586621679606463RSym3 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (b6989586621679606461 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606463RSym3 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (b6989586621679606461 :: a6989586621679120391) = Let6989586621679606463RSym4 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 b6989586621679606461
type Apply (Let6989586621679606408RSym3 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (b6989586621679606406 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606408RSym3 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (b6989586621679606406 :: a6989586621679120391) = Let6989586621679606408RSym4 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 b6989586621679606406
type Apply (Let6989586621679606251RSym4 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606249 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym4 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606249 :: a6989586621679120391) = Let6989586621679606251RSym5 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 d6989586621679606249
type Apply (Let6989586621679606286RSym4 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606284 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym4 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606284 :: a6989586621679120391) = Let6989586621679606286RSym5 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 d6989586621679606284
type Apply (Let6989586621679606321RSym4 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606319 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym4 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606319 :: a6989586621679120391) = Let6989586621679606321RSym5 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 d6989586621679606319
type Apply (Let6989586621679606356RSym4 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606354 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym4 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606354 :: a6989586621679120391) = Let6989586621679606356RSym5 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 d6989586621679606354
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679131136 :: [(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) (a6989586621679131136 :: [(VSpace s n, IList s)]) = HeadR a6989586621679131136
type Apply (MergeRSym0 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (a6989586621679131011 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym0 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (a6989586621679131011 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) = MergeRSym1 a6989586621679131011
type Apply (RemoveUntilSym0 :: TyFun (Ix s6989586621679120271) ([(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] ~> [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)]) -> Type) (a6989586621679131155 :: Ix s6989586621679120271) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym0 :: TyFun (Ix s6989586621679120271) ([(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] ~> [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)]) -> Type) (a6989586621679131155 :: Ix s6989586621679120271) = (RemoveUntilSym1 a6989586621679131155 n6989586621679120272 :: TyFun [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] -> Type)
type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679131518 :: TransRule s6989586621679120266) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679131518 :: TransRule s6989586621679120266) = Let6989586621679131520Scrutinee_6989586621679120863Sym2 vs6989586621679131517 tl6989586621679131518
type Apply (Let6989586621679131161GoSym0 :: TyFun (Ix s6989586621679120291) (TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) -> Type) (i6989586621679131159 :: Ix s6989586621679120291) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131161GoSym0 :: TyFun (Ix s6989586621679120291) (TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) -> Type) (i6989586621679131159 :: Ix s6989586621679120291) = (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type)
type Apply (Lambda_6989586621679131032Sym1 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))))) -> Type) (xl6989586621679131018 :: IList s6989586621679120289) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym1 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))))) -> Type) (xl6989586621679131018 :: IList s6989586621679120289) = Lambda_6989586621679131032Sym2 xv6989586621679131017 xl6989586621679131018
type Apply (RelabelRSym1 a6989586621679131310 :: TyFun (NonEmpty (s6989586621679120259, s6989586621679120259)) ([(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] ~> Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)]) -> Type) (a6989586621679131311 :: NonEmpty (s6989586621679120259, s6989586621679120259)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym1 a6989586621679131310 :: TyFun (NonEmpty (s6989586621679120259, s6989586621679120259)) ([(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] ~> Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)]) -> Type) (a6989586621679131311 :: NonEmpty (s6989586621679120259, s6989586621679120259)) = RelabelRSym2 a6989586621679131310 a6989586621679131311
type Apply (TranspositionsSym1 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) (a6989586621679131459 :: TransRule s6989586621679120266) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) (a6989586621679131459 :: TransRule s6989586621679120266) = TranspositionsSym2 a6989586621679131458 a6989586621679131459
type Apply (CanTransposeMultSym1 a6989586621679131511 :: TyFun (TransRule s6989586621679120268) ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool) -> Type) (a6989586621679131512 :: TransRule s6989586621679120268) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679131511 :: TyFun (TransRule s6989586621679120268) ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool) -> Type) (a6989586621679131512 :: TransRule s6989586621679120268) = CanTransposeMultSym2 a6989586621679131511 a6989586621679131512
type Apply (CanTransposeSym1 a6989586621679130754 :: TyFun (Ix s6989586621679120273) (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool)) -> Type) (a6989586621679130755 :: Ix s6989586621679120273) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679130754 :: TyFun (Ix s6989586621679120273) (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool)) -> Type) (a6989586621679130755 :: Ix s6989586621679120273) = CanTransposeSym2 a6989586621679130754 a6989586621679130755
type Apply (CanTransposeSym2 a6989586621679130755 a6989586621679130754 :: TyFun (Ix s6989586621679120273) ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool) -> Type) (a6989586621679130756 :: Ix s6989586621679120273) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679130755 a6989586621679130754 :: TyFun (Ix s6989586621679120273) ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool) -> Type) (a6989586621679130756 :: Ix s6989586621679120273) = CanTransposeSym3 a6989586621679130755 a6989586621679130754 a6989586621679130756
type Apply (Lambda_6989586621679131032Sym2 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))) -> Type) (xs6989586621679131019 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym2 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))) -> Type) (xs6989586621679131019 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) = Lambda_6989586621679131032Sym3 xl6989586621679131018 xv6989586621679131017 xs6989586621679131019
type Apply (Let6989586621679131161GoSym2 r6989586621679131160 i6989586621679131159 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) (a6989586621679131162 :: Ix s6989586621679120291) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131161GoSym2 r6989586621679131160 i6989586621679131159 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) (a6989586621679131162 :: Ix s6989586621679120291) = (Let6989586621679131161GoSym3 r6989586621679131160 i6989586621679131159 a6989586621679131162 :: TyFun [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] -> Type)
type Apply (Lambda_6989586621679131032Sym4 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])) -> Type) (yl6989586621679131021 :: IList s6989586621679120289) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym4 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])) -> Type) (yl6989586621679131021 :: IList s6989586621679120289) = Lambda_6989586621679131032Sym5 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 yl6989586621679131021
type Apply (Lambda_6989586621679131032Sym5 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (ys6989586621679131022 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym5 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (ys6989586621679131022 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) = Lambda_6989586621679131032Sym6 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 ys6989586621679131022
type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679131517 :: VSpace s6989586621679120266 n6989586621679120267) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679131517 :: VSpace s6989586621679120266 n6989586621679120267) = Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517
type Apply (Compare_6989586621679136382Sym0 :: TyFun (VSpace a6989586621679120380 b6989586621679120381) (VSpace a6989586621679120380 b6989586621679120381 ~> Ordering) -> Type) (a6989586621679136380 :: VSpace a6989586621679120380 b6989586621679120381) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679136382Sym0 :: TyFun (VSpace a6989586621679120380 b6989586621679120381) (VSpace a6989586621679120380 b6989586621679120381 ~> Ordering) -> Type) (a6989586621679136380 :: VSpace a6989586621679120380 b6989586621679120381) = Compare_6989586621679136382Sym1 a6989586621679136380
type Apply (CanTransposeSym0 :: TyFun (VSpace s6989586621679120273 n6989586621679120274) (Ix s6989586621679120273 ~> (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool))) -> Type) (a6989586621679130754 :: VSpace s6989586621679120273 n6989586621679120274) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym0 :: TyFun (VSpace s6989586621679120273 n6989586621679120274) (Ix s6989586621679120273 ~> (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool))) -> Type) (a6989586621679130754 :: VSpace s6989586621679120273 n6989586621679120274) = CanTransposeSym1 a6989586621679130754
type Apply (Lambda_6989586621679131032Sym0 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))))) -> Type) (xv6989586621679131017 :: VSpace s6989586621679120289 n6989586621679120290) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym0 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))))) -> Type) (xv6989586621679131017 :: VSpace s6989586621679120289 n6989586621679120290) = Lambda_6989586621679131032Sym1 xv6989586621679131017
type Apply (TranspositionsSym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TransRule s6989586621679120266 ~> ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)])) -> Type) (a6989586621679131458 :: VSpace s6989586621679120266 n6989586621679120267) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TransRule s6989586621679120266 ~> ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)])) -> Type) (a6989586621679131458 :: VSpace s6989586621679120266 n6989586621679120267) = TranspositionsSym1 a6989586621679131458
type Apply (CanTransposeMultSym0 :: TyFun (VSpace s6989586621679120268 n6989586621679120269) (TransRule s6989586621679120268 ~> ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool)) -> Type) (a6989586621679131511 :: VSpace s6989586621679120268 n6989586621679120269) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym0 :: TyFun (VSpace s6989586621679120268 n6989586621679120269) (TransRule s6989586621679120268 ~> ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool)) -> Type) (a6989586621679131511 :: VSpace s6989586621679120268 n6989586621679120269) = CanTransposeMultSym1 a6989586621679131511
type Apply (CanTransposeConSym0 :: TyFun (VSpace s6989586621679120277 n6989586621679120278) (s6989586621679120277 ~> (s6989586621679120277 ~> ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool))) -> Type) (a6989586621679130564 :: VSpace s6989586621679120277 n6989586621679120278) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym0 :: TyFun (VSpace s6989586621679120277 n6989586621679120278) (s6989586621679120277 ~> (s6989586621679120277 ~> ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool))) -> Type) (a6989586621679130564 :: VSpace s6989586621679120277 n6989586621679120278) = CanTransposeConSym1 a6989586621679130564
type Apply (CanTransposeCovSym0 :: TyFun (VSpace s6989586621679120275 n6989586621679120276) (s6989586621679120275 ~> (s6989586621679120275 ~> ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool))) -> Type) (a6989586621679130659 :: VSpace s6989586621679120275 n6989586621679120276) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym0 :: TyFun (VSpace s6989586621679120275 n6989586621679120276) (s6989586621679120275 ~> (s6989586621679120275 ~> ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool))) -> Type) (a6989586621679130659 :: VSpace s6989586621679120275 n6989586621679120276) = CanTransposeCovSym1 a6989586621679130659
type Apply (RelabelRSym0 :: TyFun (VSpace s6989586621679120259 n6989586621679120260) (NonEmpty (s6989586621679120259, s6989586621679120259) ~> ([(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] ~> Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)])) -> Type) (a6989586621679131310 :: VSpace s6989586621679120259 n6989586621679120260) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym0 :: TyFun (VSpace s6989586621679120259 n6989586621679120260) (NonEmpty (s6989586621679120259, s6989586621679120259) ~> ([(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] ~> Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)])) -> Type) (a6989586621679131310 :: VSpace s6989586621679120259 n6989586621679120260) = RelabelRSym1 a6989586621679131310
type Apply (ShowsPrec_6989586621679136367Sym1 a6989586621679136364 a6989586621679120380 b6989586621679120381 :: TyFun (VSpace a6989586621679120380 b6989586621679120381) (Symbol ~> Symbol) -> Type) (a6989586621679136365 :: VSpace a6989586621679120380 b6989586621679120381) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679136367Sym1 a6989586621679136364 a6989586621679120380 b6989586621679120381 :: TyFun (VSpace a6989586621679120380 b6989586621679120381) (Symbol ~> Symbol) -> Type) (a6989586621679136365 :: VSpace a6989586621679120380 b6989586621679120381) = ShowsPrec_6989586621679136367Sym2 a6989586621679136364 a6989586621679136365
type Apply (Lambda_6989586621679131032Sym3 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))) -> Type) (yv6989586621679131020 :: VSpace s6989586621679120289 n6989586621679120290) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym3 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))) -> Type) (yv6989586621679131020 :: VSpace s6989586621679120289 n6989586621679120290) = Lambda_6989586621679131032Sym4 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 yv6989586621679131020

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
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 :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: 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 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

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

(%==) :: Sing a0 -> Sing b -> Sing (a0 == b) #

(%/=) :: 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

(%~) :: 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 :: Sing a0 -> Demote (IList a) #

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

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

ShowSing (NonEmpty a) => Show (Sing z) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

SuppressUnusedWarnings DeltaRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2ConRankSym0 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 SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym1 a6989586621679606233 :: 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 a6989586621679120281) (Maybe (IList a6989586621679120281)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679136468Sym0 :: TyFun (IList a6989586621679120391) (IList a6989586621679120391 ~> Ordering) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ConSym0 :: TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> 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 (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 (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 (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 (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 (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 s6989586621679120284 n6989586621679120285, IList s6989586621679120284)] [(VSpace s6989586621679120284 n6989586621679120285, IList s6989586621679120284)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130870Scrutinee_6989586621679120793Sym1 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130854Scrutinee_6989586621679120803Sym1 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym2 a6989586621679606234 a6989586621679606233 :: 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 s6989586621679120277 n6989586621679120278) (s6989586621679120277 ~> (s6989586621679120277 ~> ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym0 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (PrepICovSym1 a6989586621679130796 :: TyFun (IList a6989586621679120282) (IList a6989586621679120282) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (PrepIConSym1 a6989586621679130809 :: TyFun (IList a6989586621679120283) (IList a6989586621679120283) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (MergeILSym1 a6989586621679130932 :: TyFun (IList a6989586621679120288) (Maybe (IList a6989586621679120288)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131346Scrutinee_6989586621679120941Sym1 rl6989586621679131344 :: TyFun (IList a6989586621679120257) (Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131300Scrutinee_6989586621679120925Sym1 rl6989586621679131298 :: TyFun (IList a6989586621679120257) (Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelILSym1 a6989586621679131294 :: TyFun (IList a6989586621679120258) (Maybe (IList a6989586621679120258)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679136449Sym1 a6989586621679136446 a6989586621679120391 :: TyFun (IList a6989586621679120391) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679136468Sym1 a6989586621679136466 :: TyFun (IList a6989586621679120391) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ConCovSym1 t6989586621679130255 :: TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> 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 (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 (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 (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 (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 (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 a6989586621679131011 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RemoveUntilSym1 a6989586621679131155 n6989586621679120272 :: TyFun [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606463RSym1 vid6989586621679606458 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606408RSym1 vid6989586621679606403 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (DeltaRankSym3 a6989586621679606551 a6989586621679606550 a6989586621679606549 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym3 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym3 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym3 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym3 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym3 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym3 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym3 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym3 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (CanTransposeSym1 a6989586621679130754 :: TyFun (Ix s6989586621679120273) (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131161GoSym0 :: TyFun (Ix s6989586621679120291) (TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym1 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym1 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym1 a6989586621679131511 :: TyFun (TransRule s6989586621679120268) ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeConSym1 a6989586621679130564 :: TyFun s6989586621679120277 (s6989586621679120277 ~> ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym1 a6989586621679130659 :: TyFun s6989586621679120275 (s6989586621679120275 ~> ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130870Scrutinee_6989586621679120793Sym2 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130854Scrutinee_6989586621679120803Sym2 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131262Sym1 rl6989586621679131259 :: TyFun k1 (TyFun (NonEmpty a6989586621679120261) (TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606251RSym1 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606286RSym1 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606321RSym1 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606356RSym1 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (RelabelRSym1 a6989586621679131310 :: TyFun (NonEmpty (s6989586621679120259, s6989586621679120259)) ([(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] ~> Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

(SOrd s, SingI d) => SingI (RemoveUntilSym1 d n :: 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 n) #

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

SingI d => SingI (TyCon1 (ConCov d) :: NonEmpty a ~> IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon1 (ConCov d)) #

SingI (TyCon1 (Cov :: NonEmpty a -> IList a) :: NonEmpty a ~> IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon1 Cov) #

SingI (TyCon1 (Con :: NonEmpty a -> IList a) :: NonEmpty a ~> IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon1 Con) #

SuppressUnusedWarnings (Lambda_6989586621679131032Sym2 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelRSym2 a6989586621679131311 a6989586621679131310 :: TyFun [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] (Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TranspositionsSym2 a6989586621679131459 a6989586621679131458 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131520Scrutinee_6989586621679120863Sym2 tl6989586621679131518 vs6989586621679131517 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym2 a6989586621679131512 a6989586621679131511 :: TyFun [(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130870Scrutinee_6989586621679120793Sym3 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130854Scrutinee_6989586621679120803Sym3 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (SurjSym2ConRankSym4 a6989586621679606491 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym4 a6989586621679606451 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym4 a6989586621679606436 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym4 a6989586621679606396 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym4 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym4 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym4 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym4 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (CanTransposeSym2 a6989586621679130755 a6989586621679130754 :: TyFun (Ix s6989586621679120273) ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131061L'Sym1 v6989586621679131058 :: TyFun (IList a6989586621679120391) (TyFun k1 (Maybe (IList a6989586621679120391)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130890Scrutinee_6989586621679120785Sym1 v6989586621679130887 :: TyFun (IList a6989586621679120281) (TyFun k1 (Maybe (IList a6989586621679120281)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130973Sym1 xs6989586621679130970 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130984Sym1 xs6989586621679130981 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeConSym2 a6989586621679130565 a6989586621679130564 :: TyFun s6989586621679120277 ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym2 a6989586621679130660 a6989586621679130659 :: TyFun s6989586621679120275 ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131245Sym1 rl6989586621679131243 :: TyFun k1 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131248Scrutinee_6989586621679120937Sym1 rl6989586621679131243 :: TyFun k1 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131229Sym1 rl6989586621679131227 :: TyFun k1 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131232Scrutinee_6989586621679120939Sym1 rl6989586621679131227 :: TyFun k1 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606251RSym2 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606286RSym2 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606321RSym2 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606356RSym2 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606463RSym2 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606408RSym2 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679130962Sym1 xs6989586621679130959 :: TyFun (NonEmpty a6989586621679120391) (TyFun k1 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130999Sym1 ys6989586621679130996 :: TyFun (NonEmpty a6989586621679120391) (TyFun k1 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130940Sym1 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120286) (TyFun k2 (TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131262Sym2 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120261) (TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> 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 (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 (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 (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 (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 (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) #

SingI (TyCon2 (ConCov :: NonEmpty a -> NonEmpty a -> IList a) :: NonEmpty a ~> (NonEmpty a ~> IList a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon2 ConCov) #

SuppressUnusedWarnings (CanTransposeConSym3 a6989586621679130566 a6989586621679130565 a6989586621679130564 :: TyFun [(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym3 a6989586621679130661 a6989586621679130660 a6989586621679130659 :: TyFun [(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym3 a6989586621679130756 a6989586621679130755 a6989586621679130754 :: TyFun [(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjAreaConRankSym5 a6989586621679606342 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym5 a6989586621679606307 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym5 a6989586621679606272 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym5 a6989586621679606237 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym3 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131161GoSym2 r6989586621679131160 i6989586621679131159 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131245Sym2 is6989586621679131244 rl6989586621679131243 :: TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131248Scrutinee_6989586621679120937Sym2 is6989586621679131244 rl6989586621679131243 :: TyFun (IList a6989586621679120302) Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131229Sym2 is6989586621679131228 rl6989586621679131227 :: TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131232Scrutinee_6989586621679120939Sym2 is6989586621679131228 rl6989586621679131227 :: TyFun (IList a6989586621679120302) Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130962Sym2 ys6989586621679130960 xs6989586621679130959 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130973Sym2 ys6989586621679130971 xs6989586621679130970 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130999Sym2 xs6989586621679130997 ys6989586621679130996 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131061L'Sym2 l6989586621679131059 v6989586621679131058 :: TyFun k1 (Maybe (IList a6989586621679120391)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131268L'Sym1 rl6989586621679131259 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130890Scrutinee_6989586621679120785Sym2 is6989586621679130888 v6989586621679130887 :: TyFun k1 (Maybe (IList a6989586621679120281)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130870Scrutinee_6989586621679120793Sym4 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130854Scrutinee_6989586621679120803Sym4 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130940Sym2 ys6989586621679130937 xs6989586621679130936 :: TyFun k2 (TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131265Sym1 rl6989586621679131259 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606251RSym3 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606286RSym3 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606321RSym3 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606356RSym3 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606463RSym3 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606408RSym3 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679131262Sym3 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130984Sym2 xs'6989586621679130982 xs6989586621679130981 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> 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 (Let6989586621679131161GoSym3 a6989586621679131162 r6989586621679131160 i6989586621679131159 :: TyFun [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130870Scrutinee_6989586621679120793Sym5 y'6989586621679130868 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130854Scrutinee_6989586621679120803Sym5 x'6989586621679130852 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym4 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130943Sym1 xs6989586621679130936 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131268L'Sym2 is6989586621679131260 rl6989586621679131259 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131265Sym2 is6989586621679131260 rl6989586621679131259 :: TyFun k1 (TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606251RSym4 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606286RSym4 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606321RSym4 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606356RSym4 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606463RSym4 b6989586621679606461 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606408RSym4 b6989586621679606406 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679130962Sym3 xs'6989586621679130961 ys6989586621679130960 xs6989586621679130959 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130973Sym3 ys'6989586621679130972 ys6989586621679130971 xs6989586621679130970 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130984Sym3 ys6989586621679130983 xs'6989586621679130982 xs6989586621679130981 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130999Sym3 ys'6989586621679130998 xs6989586621679130997 ys6989586621679130996 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130940Sym3 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym5 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130943Sym2 ys6989586621679130937 xs6989586621679130936 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679606251RSym5 d6989586621679606249 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606286RSym5 d6989586621679606284 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606321RSym5 d6989586621679606319 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679606356RSym5 d6989586621679606354 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679131268L'Sym3 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130940Sym4 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131265Sym3 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131032Sym6 ys6989586621679131022 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) (Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130943Sym3 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131268L'Sym4 is'6989586621679131264 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679131265Sym4 is'6989586621679131264 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130943Sym4 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130943Sym5 xs''6989586621679130942 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IsAscendingISym0 :: TyFun (IList a) Bool -> Type) (a6989586621679131209 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IsAscendingISym0 :: TyFun (IList a) Bool -> Type) (a6989586621679131209 :: IList a) = IsAscendingI a6989586621679131209
type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679131182 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679131182 :: IList a) = LengthIL a6989586621679131182
type Apply (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) (a6989586621679131215 :: [(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) (a6989586621679131215 :: [(VSpace a b, IList a)]) = Sane a6989586621679131215
type Apply (Compare_6989586621679136468Sym1 a6989586621679136466 :: TyFun (IList a) Ordering -> Type) (a6989586621679136467 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679136468Sym1 a6989586621679136466 :: TyFun (IList a) Ordering -> Type) (a6989586621679136467 :: IList a) = Compare_6989586621679136468 a6989586621679136466 a6989586621679136467
type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679131188 :: [(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) (a6989586621679131188 :: [(VSpace s n, IList s)]) = LengthR a6989586621679131188
type Apply (CanTransposeMultSym2 a6989586621679131512 a6989586621679131511 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679131513 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym2 a6989586621679131512 a6989586621679131511 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679131513 :: [(VSpace s n, IList s)]) = CanTransposeMult a6989586621679131512 a6989586621679131511 a6989586621679131513
type Apply (CanTransposeConSym3 a6989586621679130566 a6989586621679130565 a6989586621679130564 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130567 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym3 a6989586621679130566 a6989586621679130565 a6989586621679130564 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130567 :: [(VSpace s n, IList s)]) = CanTransposeCon a6989586621679130566 a6989586621679130565 a6989586621679130564 a6989586621679130567
type Apply (CanTransposeCovSym3 a6989586621679130661 a6989586621679130660 a6989586621679130659 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130662 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym3 a6989586621679130661 a6989586621679130660 a6989586621679130659 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130662 :: [(VSpace s n, IList s)]) = CanTransposeCov a6989586621679130661 a6989586621679130660 a6989586621679130659 a6989586621679130662
type Apply (CanTransposeSym3 a6989586621679130756 a6989586621679130755 a6989586621679130754 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130757 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym3 a6989586621679130756 a6989586621679130755 a6989586621679130754 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679130757 :: [(VSpace s n, IList s)]) = CanTranspose a6989586621679130756 a6989586621679130755 a6989586621679130754 a6989586621679130757
type Apply (Let6989586621679131248Scrutinee_6989586621679120937Sym2 is6989586621679131244 rl6989586621679131243 :: TyFun (IList a6989586621679120302) Bool -> Type) (is'6989586621679131247 :: IList a6989586621679120302) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131248Scrutinee_6989586621679120937Sym2 is6989586621679131244 rl6989586621679131243 :: TyFun (IList a6989586621679120302) Bool -> Type) (is'6989586621679131247 :: IList a6989586621679120302) = Let6989586621679131248Scrutinee_6989586621679120937 is6989586621679131244 rl6989586621679131243 is'6989586621679131247
type Apply (Let6989586621679131232Scrutinee_6989586621679120939Sym2 is6989586621679131228 rl6989586621679131227 :: TyFun (IList a6989586621679120302) Bool -> Type) (is'6989586621679131231 :: IList a6989586621679120302) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131232Scrutinee_6989586621679120939Sym2 is6989586621679131228 rl6989586621679131227 :: TyFun (IList a6989586621679120302) Bool -> Type) (is'6989586621679131231 :: IList a6989586621679120302) = Let6989586621679131232Scrutinee_6989586621679120939 is6989586621679131228 rl6989586621679131227 is'6989586621679131231
data Sing (b :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

data Sing (b :: IList a) where
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__6989586621680262835Sym0 :: 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_6989586621680262846Sym0 :: 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_6989586621679380340Sym0 :: 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_6989586621679380322Sym0 :: 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_6989586621679380304Sym0 :: 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_6989586621679380286Sym0 :: 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_6989586621679380268Sym0 :: 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_6989586621679380250Sym0 :: 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_6989586621679136468Sym0 :: 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_6989586621679136520 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_6989586621679136449Sym0 :: TyFun Nat (IList a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (DeltaRankSym3 a6989586621679606551 a6989586621679606550 a6989586621679606549 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679606552 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym3 a6989586621679606551 a6989586621679606550 a6989586621679606549 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679606552 :: Symbol) = DeltaRank a6989586621679606551 a6989586621679606550 a6989586621679606549 a6989586621679606552
type Apply (SurjSym2ConRankSym4 a6989586621679606491 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606492 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym4 a6989586621679606491 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606492 :: Symbol) = SurjSym2ConRank a6989586621679606491 a6989586621679606490 a6989586621679606489 a6989586621679606488 a6989586621679606492
type Apply (InjSym2CovRankSym4 a6989586621679606451 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606452 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym4 a6989586621679606451 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606452 :: Symbol) = InjSym2CovRank a6989586621679606451 a6989586621679606450 a6989586621679606449 a6989586621679606448 a6989586621679606452
type Apply (SurjSym2CovRankSym4 a6989586621679606436 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606437 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym4 a6989586621679606436 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606437 :: Symbol) = SurjSym2CovRank a6989586621679606436 a6989586621679606435 a6989586621679606434 a6989586621679606433 a6989586621679606437
type Apply (InjSym2ConRankSym4 a6989586621679606396 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606397 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym4 a6989586621679606396 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606397 :: Symbol) = InjSym2ConRank a6989586621679606396 a6989586621679606395 a6989586621679606394 a6989586621679606393 a6989586621679606397
type Apply (InjAreaConRankSym5 a6989586621679606342 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606343 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym5 a6989586621679606342 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606343 :: Symbol) = InjAreaConRank a6989586621679606342 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 a6989586621679606343
type Apply (InjAreaCovRankSym5 a6989586621679606307 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606308 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym5 a6989586621679606307 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606308 :: Symbol) = InjAreaCovRank a6989586621679606307 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 a6989586621679606308
type Apply (SurjAreaConRankSym5 a6989586621679606272 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606273 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym5 a6989586621679606272 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606273 :: Symbol) = SurjAreaConRank a6989586621679606272 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 a6989586621679606273
type Apply (SurjAreaCovRankSym5 a6989586621679606237 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606238 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym5 a6989586621679606237 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606238 :: Symbol) = SurjAreaCovRank a6989586621679606237 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 a6989586621679606238
type Apply (Let6989586621679131061L'Sym2 l6989586621679131059 v6989586621679131058 :: TyFun k2 (Maybe (IList a6989586621679120391)) -> Type) (ls6989586621679131060 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131061L'Sym2 l6989586621679131059 v6989586621679131058 :: TyFun k2 (Maybe (IList a6989586621679120391)) -> Type) (ls6989586621679131060 :: k2) = Let6989586621679131061L' l6989586621679131059 v6989586621679131058 ls6989586621679131060
type Apply (Let6989586621679130890Scrutinee_6989586621679120785Sym2 is6989586621679130888 v6989586621679130887 :: TyFun k2 (Maybe (IList a6989586621679120281)) -> Type) (xs6989586621679130889 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130890Scrutinee_6989586621679120785Sym2 is6989586621679130888 v6989586621679130887 :: TyFun k2 (Maybe (IList a6989586621679120281)) -> Type) (xs6989586621679130889 :: k2) = Let6989586621679130890Scrutinee_6989586621679120785 is6989586621679130888 v6989586621679130887 xs6989586621679130889
type Apply (Let6989586621679606463RSym4 b6989586621679606461 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606462 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606463RSym4 b6989586621679606461 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606462 :: a6989586621679120391) = Let6989586621679606463R b6989586621679606461 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 i6989586621679606462
type Apply (Let6989586621679606408RSym4 b6989586621679606406 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606407 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606408RSym4 b6989586621679606406 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606407 :: a6989586621679120391) = Let6989586621679606408R b6989586621679606406 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 i6989586621679606407
type Apply (Let6989586621679606251RSym5 d6989586621679606249 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606250 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym5 d6989586621679606249 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606250 :: a6989586621679120391) = Let6989586621679606251R d6989586621679606249 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 i6989586621679606250
type Apply (Let6989586621679606286RSym5 d6989586621679606284 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606285 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym5 d6989586621679606284 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606285 :: a6989586621679120391) = Let6989586621679606286R d6989586621679606284 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 i6989586621679606285
type Apply (Let6989586621679606321RSym5 d6989586621679606319 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606320 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym5 d6989586621679606319 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606320 :: a6989586621679120391) = Let6989586621679606321R d6989586621679606319 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 i6989586621679606320
type Apply (Let6989586621679606356RSym5 d6989586621679606354 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606355 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym5 d6989586621679606354 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) (i6989586621679606355 :: a6989586621679120391) = Let6989586621679606356R d6989586621679606354 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 i6989586621679606355
type Apply (ContractISym0 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679130822 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ContractISym0 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679130822 :: IList a) = ContractI a6989586621679130822
type Apply (CovSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (t6989586621679130259 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CovSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (t6989586621679130259 :: NonEmpty a) = Cov t6989586621679130259
type Apply (ConSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (t6989586621679130261 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ConSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (t6989586621679130261 :: NonEmpty a) = Con t6989586621679130261
type Apply (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679130885 :: [(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) (a6989586621679130885 :: [(VSpace s n, IList s)]) = ContractR a6989586621679130885
type Apply (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679131056 :: [(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) (a6989586621679131056 :: [(VSpace s n, IList s)]) = TailR a6989586621679131056
type Apply (RelabelTranspositionsSym1 a6989586621679131340 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679131341 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym1 a6989586621679131340 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679131341 :: IList a) = RelabelTranspositions a6989586621679131340 a6989586621679131341
type Apply (EpsilonRankSym2 a6989586621679606527 a6989586621679606526 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606528 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym2 a6989586621679606527 a6989586621679606526 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606528 :: NonEmpty Symbol) = EpsilonRank a6989586621679606527 a6989586621679606526 a6989586621679606528
type Apply (EpsilonInvRankSym2 a6989586621679606504 a6989586621679606503 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606505 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym2 a6989586621679606504 a6989586621679606503 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606505 :: NonEmpty Symbol) = EpsilonInvRank a6989586621679606504 a6989586621679606503 a6989586621679606505
type Apply (RelabelIL'Sym1 a6989586621679131223 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (a6989586621679131224 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelIL'Sym1 a6989586621679131223 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (a6989586621679131224 :: IList a) = RelabelIL' a6989586621679131223 a6989586621679131224
type Apply (Let6989586621679131346Scrutinee_6989586621679120941Sym1 rl6989586621679131344 :: TyFun (IList a6989586621679120257) (Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) (is6989586621679131345 :: IList a6989586621679120257) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131346Scrutinee_6989586621679120941Sym1 rl6989586621679131344 :: TyFun (IList a6989586621679120257) (Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) (is6989586621679131345 :: IList a6989586621679120257) = Let6989586621679131346Scrutinee_6989586621679120941 rl6989586621679131344 is6989586621679131345
type Apply (Let6989586621679131300Scrutinee_6989586621679120925Sym1 rl6989586621679131298 :: TyFun (IList a6989586621679120257) (Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) (is6989586621679131299 :: IList a6989586621679120257) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131300Scrutinee_6989586621679120925Sym1 rl6989586621679131298 :: TyFun (IList a6989586621679120257) (Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) (is6989586621679131299 :: IList a6989586621679120257) = Let6989586621679131300Scrutinee_6989586621679120925 rl6989586621679131298 is6989586621679131299
type Apply (MergeILSym1 a6989586621679130932 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679130933 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeILSym1 a6989586621679130932 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679130933 :: IList a) = MergeIL a6989586621679130932 a6989586621679130933
type Apply (RelabelILSym1 a6989586621679131294 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679131295 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelILSym1 a6989586621679131294 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679131295 :: IList a) = RelabelIL a6989586621679131294 a6989586621679131295
type Apply (ConCovSym1 t6989586621679130255 :: TyFun (NonEmpty a) (IList a) -> Type) (t6989586621679130256 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ConCovSym1 t6989586621679130255 :: TyFun (NonEmpty a) (IList a) -> Type) (t6989586621679130256 :: NonEmpty a) = ConCov t6989586621679130255 t6989586621679130256
type Apply (PrepICovSym1 a6989586621679130796 :: TyFun (IList a) (IList a) -> Type) (a6989586621679130797 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepICovSym1 a6989586621679130796 :: TyFun (IList a) (IList a) -> Type) (a6989586621679130797 :: IList a) = PrepICov a6989586621679130796 a6989586621679130797
type Apply (PrepIConSym1 a6989586621679130809 :: TyFun (IList a) (IList a) -> Type) (a6989586621679130810 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepIConSym1 a6989586621679130809 :: TyFun (IList a) (IList a) -> Type) (a6989586621679130810 :: IList a) = PrepICon a6989586621679130809 a6989586621679130810
type Apply (RemoveUntilSym1 a6989586621679131155 n :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679131156 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym1 a6989586621679131155 n :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679131156 :: [(VSpace s n, IList s)]) = RemoveUntil a6989586621679131155 a6989586621679131156
type Apply (MergeRSym1 a6989586621679131011 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679131012 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym1 a6989586621679131011 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679131012 :: [(VSpace s n, IList s)]) = MergeR a6989586621679131011 a6989586621679131012
type Apply (TranspositionsSym2 a6989586621679131459 a6989586621679131458 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679131460 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679131459 a6989586621679131458 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679131460 :: [(VSpace s n, IList s)]) = Transpositions a6989586621679131459 a6989586621679131458 a6989586621679131460
type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym2 tl6989586621679131518 vs6989586621679131517 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) (r6989586621679131519 :: [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym2 tl6989586621679131518 vs6989586621679131517 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) (r6989586621679131519 :: [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)]) = Let6989586621679131520Scrutinee_6989586621679120863 tl6989586621679131518 vs6989586621679131517 r6989586621679131519
type Apply (RelabelRSym2 a6989586621679131311 a6989586621679131310 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679131312 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym2 a6989586621679131311 a6989586621679131310 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679131312 :: [(VSpace s n, IList s)]) = RelabelR a6989586621679131311 a6989586621679131310 a6989586621679131312
type Apply (Lambda_6989586621679131262Sym3 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> Type) (t6989586621679131289 :: NonEmpty (a6989586621679120261, a6989586621679120261)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131262Sym3 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> Type) (t6989586621679131289 :: NonEmpty (a6989586621679120261, a6989586621679120261)) = Lambda_6989586621679131262 js6989586621679131261 is6989586621679131260 rl6989586621679131259 t6989586621679131289
type Apply (Lambda_6989586621679131245Sym2 is6989586621679131244 rl6989586621679131243 :: TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) (t6989586621679131255 :: IList a6989586621679120302) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131245Sym2 is6989586621679131244 rl6989586621679131243 :: TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) (t6989586621679131255 :: IList a6989586621679120302) = Lambda_6989586621679131245 is6989586621679131244 rl6989586621679131243 t6989586621679131255
type Apply (Lambda_6989586621679131229Sym2 is6989586621679131228 rl6989586621679131227 :: TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) (t6989586621679131239 :: IList a6989586621679120302) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131229Sym2 is6989586621679131228 rl6989586621679131227 :: TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) (t6989586621679131239 :: IList a6989586621679120302) = Lambda_6989586621679131229 is6989586621679131228 rl6989586621679131227 t6989586621679131239
type Apply (Let6989586621679131161GoSym3 a6989586621679131162 r6989586621679131160 i6989586621679131159 :: TyFun [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] -> Type) (a6989586621679131163 :: [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131161GoSym3 a6989586621679131162 r6989586621679131160 i6989586621679131159 :: TyFun [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] -> Type) (a6989586621679131163 :: [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) = Let6989586621679131161Go a6989586621679131162 r6989586621679131160 i6989586621679131159 a6989586621679131163
type Apply (Lambda_6989586621679130962Sym3 xs'6989586621679130961 ys6989586621679130960 xs6989586621679130959 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) (t6989586621679130965 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130962Sym3 xs'6989586621679130961 ys6989586621679130960 xs6989586621679130959 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) (t6989586621679130965 :: NonEmpty a6989586621679120391) = Lambda_6989586621679130962 xs'6989586621679130961 ys6989586621679130960 xs6989586621679130959 t6989586621679130965
type Apply (Lambda_6989586621679130973Sym3 ys'6989586621679130972 ys6989586621679130971 xs6989586621679130970 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) (t6989586621679130976 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130973Sym3 ys'6989586621679130972 ys6989586621679130971 xs6989586621679130970 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) (t6989586621679130976 :: NonEmpty a6989586621679120391) = Lambda_6989586621679130973 ys'6989586621679130972 ys6989586621679130971 xs6989586621679130970 t6989586621679130976
type Apply (Lambda_6989586621679130984Sym3 ys6989586621679130983 xs'6989586621679130982 xs6989586621679130981 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) (t6989586621679130987 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130984Sym3 ys6989586621679130983 xs'6989586621679130982 xs6989586621679130981 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) (t6989586621679130987 :: NonEmpty a6989586621679120391) = Lambda_6989586621679130984 ys6989586621679130983 xs'6989586621679130982 xs6989586621679130981 t6989586621679130987
type Apply (Lambda_6989586621679130999Sym3 ys'6989586621679130998 xs6989586621679130997 ys6989586621679130996 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) (t6989586621679131002 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130999Sym3 ys'6989586621679130998 xs6989586621679130997 ys6989586621679130996 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) (t6989586621679131002 :: NonEmpty a6989586621679120391) = Lambda_6989586621679130999 ys'6989586621679130998 xs6989586621679130997 ys6989586621679130996 t6989586621679131002
type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym5 y'6989586621679130868 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) (ys'6989586621679130869 :: [a6989586621679120281]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym5 y'6989586621679130868 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) (ys'6989586621679130869 :: [a6989586621679120281]) = Let6989586621679130870Scrutinee_6989586621679120793 y'6989586621679130868 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 ys'6989586621679130869
type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym5 x'6989586621679130852 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) (xs'6989586621679130853 :: [a6989586621679120281]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym5 x'6989586621679130852 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) (xs'6989586621679130853 :: [a6989586621679120281]) = Let6989586621679130854Scrutinee_6989586621679120803 x'6989586621679130852 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 xs'6989586621679130853
type Apply (Lambda_6989586621679130940Sym4 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) (t6989586621679130953 :: NonEmpty a6989586621679120286) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130940Sym4 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) (t6989586621679130953 :: NonEmpty a6989586621679120286) = Lambda_6989586621679130940 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 t6989586621679130953
type Apply (Lambda_6989586621679131032Sym6 ys6989586621679131022 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) (Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (t6989586621679131047 :: IList s6989586621679120289) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym6 ys6989586621679131022 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) (Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (t6989586621679131047 :: IList s6989586621679120289) = Lambda_6989586621679131032 ys6989586621679131022 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 t6989586621679131047
type Apply (Lambda_6989586621679131265Sym4 is'6989586621679131264 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) (t6989586621679131283 :: NonEmpty a6989586621679120302) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131265Sym4 is'6989586621679131264 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) (t6989586621679131283 :: NonEmpty a6989586621679120302) = Lambda_6989586621679131265 is'6989586621679131264 js6989586621679131261 is6989586621679131260 rl6989586621679131259 t6989586621679131283
type Apply (Let6989586621679131268L'Sym4 is'6989586621679131264 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) (js'6989586621679131267 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131268L'Sym4 is'6989586621679131264 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) (js'6989586621679131267 :: NonEmpty a6989586621679120391) = Let6989586621679131268L' is'6989586621679131264 js6989586621679131261 is6989586621679131260 rl6989586621679131259 js'6989586621679131267
type Apply (Lambda_6989586621679130943Sym5 xs''6989586621679130942 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) (t6989586621679130946 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130943Sym5 xs''6989586621679130942 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) (t6989586621679130946 :: NonEmpty a6989586621679120391) = Lambda_6989586621679130943 xs''6989586621679130942 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 t6989586621679130946
type Apply DeltaRankSym0 (a6989586621679606549 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply DeltaRankSym0 (a6989586621679606549 :: Symbol) = DeltaRankSym1 a6989586621679606549
type Apply SurjSym2ConRankSym0 (a6989586621679606488 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2ConRankSym0 (a6989586621679606488 :: Symbol) = SurjSym2ConRankSym1 a6989586621679606488
type Apply InjSym2CovRankSym0 (a6989586621679606448 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2CovRankSym0 (a6989586621679606448 :: Symbol) = InjSym2CovRankSym1 a6989586621679606448
type Apply SurjSym2CovRankSym0 (a6989586621679606433 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2CovRankSym0 (a6989586621679606433 :: Symbol) = SurjSym2CovRankSym1 a6989586621679606433
type Apply InjSym2ConRankSym0 (a6989586621679606393 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2ConRankSym0 (a6989586621679606393 :: Symbol) = InjSym2ConRankSym1 a6989586621679606393
type Apply EpsilonRankSym0 (a6989586621679606526 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonRankSym0 (a6989586621679606526 :: Symbol) = EpsilonRankSym1 a6989586621679606526
type Apply EpsilonInvRankSym0 (a6989586621679606503 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonInvRankSym0 (a6989586621679606503 :: Symbol) = EpsilonInvRankSym1 a6989586621679606503
type Apply InjAreaConRankSym0 (a6989586621679606338 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaConRankSym0 (a6989586621679606338 :: Symbol) = InjAreaConRankSym1 a6989586621679606338
type Apply InjAreaCovRankSym0 (a6989586621679606303 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaCovRankSym0 (a6989586621679606303 :: Symbol) = InjAreaCovRankSym1 a6989586621679606303
type Apply SurjAreaConRankSym0 (a6989586621679606268 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjAreaConRankSym0 (a6989586621679606268 :: Symbol) = SurjAreaConRankSym1 a6989586621679606268
type Apply SurjAreaCovRankSym0 (a6989586621679606233 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjAreaCovRankSym0 (a6989586621679606233 :: Symbol) = SurjAreaCovRankSym1 a6989586621679606233
type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym0 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621679130824 :: a6989586621679120281) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym0 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621679130824 :: a6989586621679120281) = Let6989586621679130870Scrutinee_6989586621679120793Sym1 x6989586621679130824
type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym0 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621679130824 :: a6989586621679120281) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym0 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x6989586621679130824 :: a6989586621679120281) = Let6989586621679130854Scrutinee_6989586621679120803Sym1 x6989586621679130824
type Apply (DeltaRankSym1 a6989586621679606549 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606550 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym1 a6989586621679606549 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606550 :: Nat) = DeltaRankSym2 a6989586621679606549 a6989586621679606550
type Apply (SurjSym2ConRankSym1 a6989586621679606488 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606489 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym1 a6989586621679606488 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606489 :: Nat) = SurjSym2ConRankSym2 a6989586621679606488 a6989586621679606489
type Apply (InjSym2CovRankSym1 a6989586621679606448 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606449 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym1 a6989586621679606448 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606449 :: Nat) = InjSym2CovRankSym2 a6989586621679606448 a6989586621679606449
type Apply (SurjSym2CovRankSym1 a6989586621679606433 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606434 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym1 a6989586621679606433 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606434 :: Nat) = SurjSym2CovRankSym2 a6989586621679606433 a6989586621679606434
type Apply (InjSym2ConRankSym1 a6989586621679606393 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606394 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym1 a6989586621679606393 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606394 :: Nat) = InjSym2ConRankSym2 a6989586621679606393 a6989586621679606394
type Apply (InjAreaConRankSym1 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606339 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym1 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606339 :: Symbol) = InjAreaConRankSym2 a6989586621679606338 a6989586621679606339
type Apply (InjAreaCovRankSym1 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606304 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym1 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606304 :: Symbol) = InjAreaCovRankSym2 a6989586621679606303 a6989586621679606304
type Apply (SurjAreaConRankSym1 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606269 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym1 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606269 :: Symbol) = SurjAreaConRankSym2 a6989586621679606268 a6989586621679606269
type Apply (SurjAreaCovRankSym1 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606234 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym1 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679606234 :: Symbol) = SurjAreaCovRankSym2 a6989586621679606233 a6989586621679606234
type Apply (PrepICovSym0 :: TyFun a6989586621679120282 (IList a6989586621679120282 ~> IList a6989586621679120282) -> Type) (a6989586621679130796 :: a6989586621679120282) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepICovSym0 :: TyFun a6989586621679120282 (IList a6989586621679120282 ~> IList a6989586621679120282) -> Type) (a6989586621679130796 :: a6989586621679120282) = PrepICovSym1 a6989586621679130796
type Apply (PrepIConSym0 :: TyFun a6989586621679120283 (IList a6989586621679120283 ~> IList a6989586621679120283) -> Type) (a6989586621679130809 :: a6989586621679120283) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepIConSym0 :: TyFun a6989586621679120283 (IList a6989586621679120283 ~> IList a6989586621679120283) -> Type) (a6989586621679130809 :: a6989586621679120283) = PrepIConSym1 a6989586621679130809
type Apply (ShowsPrec_6989586621679136449Sym0 :: TyFun Nat (IList a6989586621679120391 ~> (Symbol ~> Symbol)) -> Type) (a6989586621679136446 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679136449Sym0 :: TyFun Nat (IList a6989586621679120391 ~> (Symbol ~> Symbol)) -> Type) (a6989586621679136446 :: Nat) = (ShowsPrec_6989586621679136449Sym1 a6989586621679136446 a6989586621679120391 :: TyFun (IList a6989586621679120391) (Symbol ~> Symbol) -> Type)
type Apply (EpsilonRankSym1 a6989586621679606526 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606527 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym1 a6989586621679606526 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606527 :: Nat) = EpsilonRankSym2 a6989586621679606526 a6989586621679606527
type Apply (EpsilonInvRankSym1 a6989586621679606503 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606504 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym1 a6989586621679606503 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606504 :: Nat) = EpsilonInvRankSym2 a6989586621679606503 a6989586621679606504
type Apply (Let6989586621679606463RSym0 :: TyFun k1 (TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606458 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606463RSym0 :: TyFun k1 (TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606458 :: k1) = (Let6989586621679606463RSym1 vid6989586621679606458 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606408RSym0 :: TyFun k1 (TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606403 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606408RSym0 :: TyFun k1 (TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606403 :: k1) = (Let6989586621679606408RSym1 vid6989586621679606403 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606251RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606245 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606245 :: k1) = (Let6989586621679606251RSym1 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606286RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606280 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606280 :: k1) = (Let6989586621679606286RSym1 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606321RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606315 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606315 :: k1) = (Let6989586621679606321RSym1 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606356RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606350 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym0 :: TyFun k1 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679606350 :: k1) = (Let6989586621679606356RSym1 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (DeltaRankSym2 a6989586621679606550 a6989586621679606549 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606551 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym2 a6989586621679606550 a6989586621679606549 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606551 :: Symbol) = DeltaRankSym3 a6989586621679606550 a6989586621679606549 a6989586621679606551
type Apply (SurjSym2ConRankSym2 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606490 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym2 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606490 :: Symbol) = SurjSym2ConRankSym3 a6989586621679606489 a6989586621679606488 a6989586621679606490
type Apply (InjSym2CovRankSym2 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606450 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym2 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606450 :: Symbol) = InjSym2CovRankSym3 a6989586621679606449 a6989586621679606448 a6989586621679606450
type Apply (SurjSym2CovRankSym2 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606435 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym2 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606435 :: Symbol) = SurjSym2CovRankSym3 a6989586621679606434 a6989586621679606433 a6989586621679606435
type Apply (InjSym2ConRankSym2 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606395 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym2 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606395 :: Symbol) = InjSym2ConRankSym3 a6989586621679606394 a6989586621679606393 a6989586621679606395
type Apply (InjAreaConRankSym2 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606340 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym2 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606340 :: Symbol) = InjAreaConRankSym3 a6989586621679606339 a6989586621679606338 a6989586621679606340
type Apply (InjAreaCovRankSym2 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606305 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym2 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606305 :: Symbol) = InjAreaCovRankSym3 a6989586621679606304 a6989586621679606303 a6989586621679606305
type Apply (SurjAreaConRankSym2 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606270 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym2 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606270 :: Symbol) = SurjAreaConRankSym3 a6989586621679606269 a6989586621679606268 a6989586621679606270
type Apply (SurjAreaCovRankSym2 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606235 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym2 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679606235 :: Symbol) = SurjAreaCovRankSym3 a6989586621679606234 a6989586621679606233 a6989586621679606235
type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym2 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) (y6989586621679130826 :: a6989586621679120281) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym2 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) (y6989586621679130826 :: a6989586621679120281) = Let6989586621679130870Scrutinee_6989586621679120793Sym3 xs6989586621679130825 x6989586621679130824 y6989586621679130826
type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym2 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) (y6989586621679130826 :: a6989586621679120281) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym2 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) (y6989586621679130826 :: a6989586621679120281) = Let6989586621679130854Scrutinee_6989586621679120803Sym3 xs6989586621679130825 x6989586621679130824 y6989586621679130826
type Apply (Let6989586621679131061L'Sym0 :: TyFun k1 (TyFun (IList a6989586621679120391) (TyFun k2 (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (v6989586621679131058 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131061L'Sym0 :: TyFun k1 (TyFun (IList a6989586621679120391) (TyFun k2 (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (v6989586621679131058 :: k1) = (Let6989586621679131061L'Sym1 v6989586621679131058 :: TyFun (IList a6989586621679120391) (TyFun k2 (Maybe (IList a6989586621679120391)) -> Type) -> Type)
type Apply (Let6989586621679130890Scrutinee_6989586621679120785Sym0 :: TyFun k1 (TyFun (IList a6989586621679120281) (TyFun k2 (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) (v6989586621679130887 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130890Scrutinee_6989586621679120785Sym0 :: TyFun k1 (TyFun (IList a6989586621679120281) (TyFun k2 (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) (v6989586621679130887 :: k1) = (Let6989586621679130890Scrutinee_6989586621679120785Sym1 v6989586621679130887 :: TyFun (IList a6989586621679120281) (TyFun k2 (Maybe (IList a6989586621679120281)) -> Type) -> Type)
type Apply (Lambda_6989586621679130984Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130981 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130984Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130981 :: k1) = (Lambda_6989586621679130984Sym1 xs6989586621679130981 :: TyFun k2 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679131245Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) (rl6989586621679131243 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131245Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) (rl6989586621679131243 :: k1) = (Lambda_6989586621679131245Sym1 rl6989586621679131243 :: TyFun k2 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type)
type Apply (Let6989586621679131248Scrutinee_6989586621679120937Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type) -> Type) (rl6989586621679131243 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131248Scrutinee_6989586621679120937Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type) -> Type) (rl6989586621679131243 :: k1) = (Let6989586621679131248Scrutinee_6989586621679120937Sym1 rl6989586621679131243 :: TyFun k2 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type)
type Apply (Lambda_6989586621679131229Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) (rl6989586621679131227 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131229Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) (rl6989586621679131227 :: k1) = (Lambda_6989586621679131229Sym1 rl6989586621679131227 :: TyFun k2 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type)
type Apply (Let6989586621679131232Scrutinee_6989586621679120939Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type) -> Type) (rl6989586621679131227 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131232Scrutinee_6989586621679120939Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type) -> Type) (rl6989586621679131227 :: k1) = (Let6989586621679131232Scrutinee_6989586621679120939Sym1 rl6989586621679131227 :: TyFun k2 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type)
type Apply (Let6989586621679606251RSym1 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606246 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym1 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606246 :: a6989586621679120391) = Let6989586621679606251RSym2 vid6989586621679606245 a6989586621679606246
type Apply (Let6989586621679606286RSym1 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606281 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym1 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606281 :: a6989586621679120391) = Let6989586621679606286RSym2 vid6989586621679606280 a6989586621679606281
type Apply (Let6989586621679606321RSym1 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606316 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym1 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606316 :: a6989586621679120391) = Let6989586621679606321RSym2 vid6989586621679606315 a6989586621679606316
type Apply (Let6989586621679606356RSym1 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606351 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym1 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679606351 :: a6989586621679120391) = Let6989586621679606356RSym2 vid6989586621679606350 a6989586621679606351
type Apply (Let6989586621679606463RSym1 vid6989586621679606458 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679606459 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606463RSym1 vid6989586621679606458 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679606459 :: Nat) = (Let6989586621679606463RSym2 vid6989586621679606458 vdim6989586621679606459 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type)
type Apply (Let6989586621679606408RSym1 vid6989586621679606403 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679606404 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606408RSym1 vid6989586621679606403 :: TyFun Nat (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679606404 :: Nat) = (Let6989586621679606408RSym2 vid6989586621679606403 vdim6989586621679606404 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679130962Sym0 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130959 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130962Sym0 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130959 :: k1) = (Lambda_6989586621679130962Sym1 xs6989586621679130959 :: TyFun (NonEmpty a6989586621679120391) (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679130999Sym0 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679130996 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130999Sym0 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679130996 :: k1) = (Lambda_6989586621679130999Sym1 ys6989586621679130996 :: TyFun (NonEmpty a6989586621679120391) (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679130940Sym0 :: TyFun k2 (TyFun (NonEmpty a6989586621679120286) (TyFun k3 (TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130936 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130940Sym0 :: TyFun k2 (TyFun (NonEmpty a6989586621679120286) (TyFun k3 (TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130936 :: k2) = (Lambda_6989586621679130940Sym1 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120286) (TyFun k3 (TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679131262Sym1 rl6989586621679131259 :: TyFun k1 (TyFun (NonEmpty a6989586621679120261) (TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> Type) -> Type) -> Type) (is6989586621679131260 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131262Sym1 rl6989586621679131259 :: TyFun k1 (TyFun (NonEmpty a6989586621679120261) (TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> Type) -> Type) -> Type) (is6989586621679131260 :: k1) = Lambda_6989586621679131262Sym2 rl6989586621679131259 is6989586621679131260
type Apply (SurjSym2ConRankSym3 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606491 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym3 a6989586621679606490 a6989586621679606489 a6989586621679606488 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606491 :: Symbol) = SurjSym2ConRankSym4 a6989586621679606490 a6989586621679606489 a6989586621679606488 a6989586621679606491
type Apply (InjSym2CovRankSym3 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606451 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym3 a6989586621679606450 a6989586621679606449 a6989586621679606448 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606451 :: Symbol) = InjSym2CovRankSym4 a6989586621679606450 a6989586621679606449 a6989586621679606448 a6989586621679606451
type Apply (SurjSym2CovRankSym3 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606436 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym3 a6989586621679606435 a6989586621679606434 a6989586621679606433 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606436 :: Symbol) = SurjSym2CovRankSym4 a6989586621679606435 a6989586621679606434 a6989586621679606433 a6989586621679606436
type Apply (InjSym2ConRankSym3 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606396 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym3 a6989586621679606395 a6989586621679606394 a6989586621679606393 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606396 :: Symbol) = InjSym2ConRankSym4 a6989586621679606395 a6989586621679606394 a6989586621679606393 a6989586621679606396
type Apply (InjAreaConRankSym3 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606341 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym3 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606341 :: Symbol) = InjAreaConRankSym4 a6989586621679606340 a6989586621679606339 a6989586621679606338 a6989586621679606341
type Apply (InjAreaCovRankSym3 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606306 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym3 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606306 :: Symbol) = InjAreaCovRankSym4 a6989586621679606305 a6989586621679606304 a6989586621679606303 a6989586621679606306
type Apply (SurjAreaConRankSym3 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606271 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym3 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606271 :: Symbol) = SurjAreaConRankSym4 a6989586621679606270 a6989586621679606269 a6989586621679606268 a6989586621679606271
type Apply (SurjAreaCovRankSym3 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606236 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym3 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679606236 :: Symbol) = SurjAreaCovRankSym4 a6989586621679606235 a6989586621679606234 a6989586621679606233 a6989586621679606236
type Apply (CanTransposeConSym1 a6989586621679130564 :: TyFun s6989586621679120277 (s6989586621679120277 ~> ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool)) -> Type) (a6989586621679130565 :: s6989586621679120277) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym1 a6989586621679130564 :: TyFun s6989586621679120277 (s6989586621679120277 ~> ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool)) -> Type) (a6989586621679130565 :: s6989586621679120277) = CanTransposeConSym2 a6989586621679130564 a6989586621679130565
type Apply (CanTransposeCovSym1 a6989586621679130659 :: TyFun s6989586621679120275 (s6989586621679120275 ~> ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool)) -> Type) (a6989586621679130660 :: s6989586621679120275) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym1 a6989586621679130659 :: TyFun s6989586621679120275 (s6989586621679120275 ~> ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool)) -> Type) (a6989586621679130660 :: s6989586621679120275) = CanTransposeCovSym2 a6989586621679130659 a6989586621679130660
type Apply (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) (r6989586621679131160 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) (r6989586621679131160 :: k) = (Let6989586621679131161GoSym2 i6989586621679131159 r6989586621679131160 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type)
type Apply (Lambda_6989586621679131245Sym1 rl6989586621679131243 :: TyFun k1 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) (is6989586621679131244 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131245Sym1 rl6989586621679131243 :: TyFun k1 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) (is6989586621679131244 :: k1) = (Lambda_6989586621679131245Sym2 rl6989586621679131243 is6989586621679131244 :: TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type)
type Apply (Let6989586621679131248Scrutinee_6989586621679120937Sym1 rl6989586621679131243 :: TyFun k1 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type) (is6989586621679131244 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131248Scrutinee_6989586621679120937Sym1 rl6989586621679131243 :: TyFun k1 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type) (is6989586621679131244 :: k1) = (Let6989586621679131248Scrutinee_6989586621679120937Sym2 rl6989586621679131243 is6989586621679131244 :: TyFun (IList a6989586621679120302) Bool -> Type)
type Apply (Lambda_6989586621679131229Sym1 rl6989586621679131227 :: TyFun k1 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) (is6989586621679131228 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131229Sym1 rl6989586621679131227 :: TyFun k1 (TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) (is6989586621679131228 :: k1) = (Lambda_6989586621679131229Sym2 rl6989586621679131227 is6989586621679131228 :: TyFun (IList a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type)
type Apply (Let6989586621679131232Scrutinee_6989586621679120939Sym1 rl6989586621679131227 :: TyFun k1 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type) (is6989586621679131228 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131232Scrutinee_6989586621679120939Sym1 rl6989586621679131227 :: TyFun k1 (TyFun (IList a6989586621679120302) Bool -> Type) -> Type) (is6989586621679131228 :: k1) = (Let6989586621679131232Scrutinee_6989586621679120939Sym2 rl6989586621679131227 is6989586621679131228 :: TyFun (IList a6989586621679120302) Bool -> Type)
type Apply (Lambda_6989586621679130973Sym1 xs6989586621679130970 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (ys6989586621679130971 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130973Sym1 xs6989586621679130970 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (ys6989586621679130971 :: k1) = (Lambda_6989586621679130973Sym2 xs6989586621679130970 ys6989586621679130971 :: TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type)
type Apply (Let6989586621679131268L'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) -> Type) -> Type) -> Type) (rl6989586621679131259 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131268L'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) -> Type) -> Type) -> Type) (rl6989586621679131259 :: k1) = (Let6989586621679131268L'Sym1 rl6989586621679131259 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679131265Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) -> Type) -> Type) (rl6989586621679131259 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131265Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) -> Type) -> Type) (rl6989586621679131259 :: k1) = (Lambda_6989586621679131265Sym1 rl6989586621679131259 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606251RSym2 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606247 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym2 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606247 :: a6989586621679120391) = Let6989586621679606251RSym3 a6989586621679606246 vid6989586621679606245 b6989586621679606247
type Apply (Let6989586621679606286RSym2 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606282 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym2 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606282 :: a6989586621679120391) = Let6989586621679606286RSym3 a6989586621679606281 vid6989586621679606280 b6989586621679606282
type Apply (Let6989586621679606321RSym2 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606317 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym2 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606317 :: a6989586621679120391) = Let6989586621679606321RSym3 a6989586621679606316 vid6989586621679606315 b6989586621679606317
type Apply (Let6989586621679606356RSym2 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606352 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym2 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) -> Type) (b6989586621679606352 :: a6989586621679120391) = Let6989586621679606356RSym3 a6989586621679606351 vid6989586621679606350 b6989586621679606352
type Apply (Let6989586621679606463RSym2 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (a6989586621679606460 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606463RSym2 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (a6989586621679606460 :: a6989586621679120391) = Let6989586621679606463RSym3 vdim6989586621679606459 vid6989586621679606458 a6989586621679606460
type Apply (Let6989586621679606408RSym2 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (a6989586621679606405 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606408RSym2 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (a6989586621679606405 :: a6989586621679120391) = Let6989586621679606408RSym3 vdim6989586621679606404 vid6989586621679606403 a6989586621679606405
type Apply (Lambda_6989586621679130984Sym1 xs6989586621679130981 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (xs'6989586621679130982 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130984Sym1 xs6989586621679130981 :: TyFun k1 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (xs'6989586621679130982 :: k1) = (Lambda_6989586621679130984Sym2 xs6989586621679130981 xs'6989586621679130982 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type)
type Apply (CanTransposeConSym2 a6989586621679130565 a6989586621679130564 :: TyFun s6989586621679120277 ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool) -> Type) (a6989586621679130566 :: s6989586621679120277) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym2 a6989586621679130565 a6989586621679130564 :: TyFun s6989586621679120277 ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool) -> Type) (a6989586621679130566 :: s6989586621679120277) = CanTransposeConSym3 a6989586621679130565 a6989586621679130564 a6989586621679130566
type Apply (CanTransposeCovSym2 a6989586621679130660 a6989586621679130659 :: TyFun s6989586621679120275 ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool) -> Type) (a6989586621679130661 :: s6989586621679120275) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym2 a6989586621679130660 a6989586621679130659 :: TyFun s6989586621679120275 ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool) -> Type) (a6989586621679130661 :: s6989586621679120275) = CanTransposeCovSym3 a6989586621679130660 a6989586621679130659 a6989586621679130661
type Apply (InjAreaConRankSym4 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606342 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym4 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606342 :: Symbol) = InjAreaConRankSym5 a6989586621679606341 a6989586621679606340 a6989586621679606339 a6989586621679606338 a6989586621679606342
type Apply (InjAreaCovRankSym4 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606307 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym4 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606307 :: Symbol) = InjAreaCovRankSym5 a6989586621679606306 a6989586621679606305 a6989586621679606304 a6989586621679606303 a6989586621679606307
type Apply (SurjAreaConRankSym4 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606272 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym4 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606272 :: Symbol) = SurjAreaConRankSym5 a6989586621679606271 a6989586621679606270 a6989586621679606269 a6989586621679606268 a6989586621679606272
type Apply (SurjAreaCovRankSym4 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606237 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym4 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679606237 :: Symbol) = SurjAreaCovRankSym5 a6989586621679606236 a6989586621679606235 a6989586621679606234 a6989586621679606233 a6989586621679606237
type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym4 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) (y'6989586621679130868 :: a6989586621679120281) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym4 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) (y'6989586621679130868 :: a6989586621679120281) = Let6989586621679130870Scrutinee_6989586621679120793Sym5 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 y'6989586621679130868
type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym4 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) (x'6989586621679130852 :: a6989586621679120281) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym4 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) (x'6989586621679130852 :: a6989586621679120281) = Let6989586621679130854Scrutinee_6989586621679120803Sym5 ys6989586621679130827 y6989586621679130826 xs6989586621679130825 x6989586621679130824 x'6989586621679130852
type Apply (Lambda_6989586621679130943Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130936 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130943Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130936 :: k1) = (Lambda_6989586621679130943Sym1 xs6989586621679130936 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679131268L'Sym1 rl6989586621679131259 :: TyFun k1 (TyFun k3 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) -> Type) -> Type) (is6989586621679131260 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131268L'Sym1 rl6989586621679131259 :: TyFun k1 (TyFun k3 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) -> Type) -> Type) (is6989586621679131260 :: k1) = (Let6989586621679131268L'Sym2 rl6989586621679131259 is6989586621679131260 :: TyFun k3 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679131265Sym1 rl6989586621679131259 :: TyFun k1 (TyFun k3 (TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) -> Type) (is6989586621679131260 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131265Sym1 rl6989586621679131259 :: TyFun k1 (TyFun k3 (TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) -> Type) (is6989586621679131260 :: k1) = (Lambda_6989586621679131265Sym2 rl6989586621679131259 is6989586621679131260 :: TyFun k3 (TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606251RSym3 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606248 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym3 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606248 :: a6989586621679120391) = Let6989586621679606251RSym4 b6989586621679606247 a6989586621679606246 vid6989586621679606245 c6989586621679606248
type Apply (Let6989586621679606286RSym3 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606283 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym3 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606283 :: a6989586621679120391) = Let6989586621679606286RSym4 b6989586621679606282 a6989586621679606281 vid6989586621679606280 c6989586621679606283
type Apply (Let6989586621679606321RSym3 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606318 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym3 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606318 :: a6989586621679120391) = Let6989586621679606321RSym4 b6989586621679606317 a6989586621679606316 vid6989586621679606315 c6989586621679606318
type Apply (Let6989586621679606356RSym3 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606353 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym3 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) -> Type) (c6989586621679606353 :: a6989586621679120391) = Let6989586621679606356RSym4 b6989586621679606352 a6989586621679606351 vid6989586621679606350 c6989586621679606353
type Apply (Let6989586621679606463RSym3 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (b6989586621679606461 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606463RSym3 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (b6989586621679606461 :: a6989586621679120391) = Let6989586621679606463RSym4 a6989586621679606460 vdim6989586621679606459 vid6989586621679606458 b6989586621679606461
type Apply (Let6989586621679606408RSym3 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (b6989586621679606406 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606408RSym3 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (b6989586621679606406 :: a6989586621679120391) = Let6989586621679606408RSym4 a6989586621679606405 vdim6989586621679606404 vid6989586621679606403 b6989586621679606406
type Apply (Lambda_6989586621679130962Sym2 ys6989586621679130960 xs6989586621679130959 :: TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) (xs'6989586621679130961 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130962Sym2 ys6989586621679130960 xs6989586621679130959 :: TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) (xs'6989586621679130961 :: k2) = Lambda_6989586621679130962Sym3 ys6989586621679130960 xs6989586621679130959 xs'6989586621679130961
type Apply (Lambda_6989586621679130973Sym2 ys6989586621679130971 xs6989586621679130970 :: TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) (ys'6989586621679130972 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130973Sym2 ys6989586621679130971 xs6989586621679130970 :: TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) (ys'6989586621679130972 :: k2) = Lambda_6989586621679130973Sym3 ys6989586621679130971 xs6989586621679130970 ys'6989586621679130972
type Apply (Lambda_6989586621679130999Sym2 xs6989586621679130997 ys6989586621679130996 :: TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) (ys'6989586621679130998 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130999Sym2 xs6989586621679130997 ys6989586621679130996 :: TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) (ys'6989586621679130998 :: k2) = Lambda_6989586621679130999Sym3 xs6989586621679130997 ys6989586621679130996 ys'6989586621679130998
type Apply (Lambda_6989586621679130940Sym2 ys6989586621679130937 xs6989586621679130936 :: TyFun k3 (TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) -> Type) (xs'6989586621679130938 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130940Sym2 ys6989586621679130937 xs6989586621679130936 :: TyFun k3 (TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) -> Type) (xs'6989586621679130938 :: k3) = Lambda_6989586621679130940Sym3 ys6989586621679130937 xs6989586621679130936 xs'6989586621679130938
type Apply (Lambda_6989586621679130943Sym1 xs6989586621679130936 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) -> Type) (ys6989586621679130937 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130943Sym1 xs6989586621679130936 :: TyFun k1 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) -> Type) (ys6989586621679130937 :: k1) = (Lambda_6989586621679130943Sym2 xs6989586621679130936 ys6989586621679130937 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type)
type Apply (Let6989586621679606251RSym4 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606249 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606251RSym4 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606249 :: a6989586621679120391) = Let6989586621679606251RSym5 c6989586621679606248 b6989586621679606247 a6989586621679606246 vid6989586621679606245 d6989586621679606249
type Apply (Let6989586621679606286RSym4 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606284 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606286RSym4 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606284 :: a6989586621679120391) = Let6989586621679606286RSym5 c6989586621679606283 b6989586621679606282 a6989586621679606281 vid6989586621679606280 d6989586621679606284
type Apply (Let6989586621679606321RSym4 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606319 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606321RSym4 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606319 :: a6989586621679120391) = Let6989586621679606321RSym5 c6989586621679606318 b6989586621679606317 a6989586621679606316 vid6989586621679606315 d6989586621679606319
type Apply (Let6989586621679606356RSym4 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606354 :: a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679606356RSym4 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 :: TyFun a6989586621679120391 (TyFun a6989586621679120391 [(VSpace k1 Nat, IList a6989586621679120391)] -> Type) -> Type) (d6989586621679606354 :: a6989586621679120391) = Let6989586621679606356RSym5 c6989586621679606353 b6989586621679606352 a6989586621679606351 vid6989586621679606350 d6989586621679606354
type Apply (Let6989586621679131268L'Sym2 is6989586621679131260 rl6989586621679131259 :: TyFun k3 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) -> Type) (js6989586621679131261 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131268L'Sym2 is6989586621679131260 rl6989586621679131259 :: TyFun k3 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) -> Type) (js6989586621679131261 :: k3) = (Let6989586621679131268L'Sym3 is6989586621679131260 rl6989586621679131259 js6989586621679131261 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type)
type Apply (Lambda_6989586621679131265Sym2 is6989586621679131260 rl6989586621679131259 :: TyFun k3 (TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) (js6989586621679131261 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131265Sym2 is6989586621679131260 rl6989586621679131259 :: TyFun k3 (TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) -> Type) (js6989586621679131261 :: k3) = (Lambda_6989586621679131265Sym3 is6989586621679131260 rl6989586621679131259 js6989586621679131261 :: TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type)
type Apply (Lambda_6989586621679130943Sym2 ys6989586621679130937 xs6989586621679130936 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) (xs'6989586621679130938 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130943Sym2 ys6989586621679130937 xs6989586621679130936 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) (xs'6989586621679130938 :: k3) = (Lambda_6989586621679130943Sym3 ys6989586621679130937 xs6989586621679130936 xs'6989586621679130938 :: TyFun k4 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679130943Sym3 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun k4 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (ys'6989586621679130939 :: k4) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130943Sym3 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun k4 (TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (ys'6989586621679130939 :: k4) = (Lambda_6989586621679130943Sym4 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 ys'6989586621679130939 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type)
type Apply (Let6989586621679131346Scrutinee_6989586621679120941Sym0 :: TyFun (NonEmpty (a6989586621679120257, a6989586621679120257)) (TyFun (IList a6989586621679120257) (Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) -> Type) (rl6989586621679131344 :: NonEmpty (a6989586621679120257, a6989586621679120257)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131346Scrutinee_6989586621679120941Sym0 :: TyFun (NonEmpty (a6989586621679120257, a6989586621679120257)) (TyFun (IList a6989586621679120257) (Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) -> Type) (rl6989586621679131344 :: NonEmpty (a6989586621679120257, a6989586621679120257)) = Let6989586621679131346Scrutinee_6989586621679120941Sym1 rl6989586621679131344
type Apply (Let6989586621679131300Scrutinee_6989586621679120925Sym0 :: TyFun (NonEmpty (a6989586621679120257, a6989586621679120257)) (TyFun (IList a6989586621679120257) (Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) -> Type) (rl6989586621679131298 :: NonEmpty (a6989586621679120257, a6989586621679120257)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131300Scrutinee_6989586621679120925Sym0 :: TyFun (NonEmpty (a6989586621679120257, a6989586621679120257)) (TyFun (IList a6989586621679120257) (Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) -> Type) (rl6989586621679131298 :: NonEmpty (a6989586621679120257, a6989586621679120257)) = Let6989586621679131300Scrutinee_6989586621679120925Sym1 rl6989586621679131298
type Apply (MergeILSym0 :: TyFun (IList a6989586621679120288) (IList a6989586621679120288 ~> Maybe (IList a6989586621679120288)) -> Type) (a6989586621679130932 :: IList a6989586621679120288) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeILSym0 :: TyFun (IList a6989586621679120288) (IList a6989586621679120288 ~> Maybe (IList a6989586621679120288)) -> Type) (a6989586621679130932 :: IList a6989586621679120288) = MergeILSym1 a6989586621679130932
type Apply (RelabelIL'Sym0 :: TyFun (NonEmpty (a6989586621679120257, a6989586621679120257)) (IList a6989586621679120257 ~> Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) (a6989586621679131223 :: NonEmpty (a6989586621679120257, a6989586621679120257)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelIL'Sym0 :: TyFun (NonEmpty (a6989586621679120257, a6989586621679120257)) (IList a6989586621679120257 ~> Maybe (IList (a6989586621679120257, a6989586621679120257))) -> Type) (a6989586621679131223 :: NonEmpty (a6989586621679120257, a6989586621679120257)) = RelabelIL'Sym1 a6989586621679131223
type Apply (RelabelILSym0 :: TyFun (NonEmpty (a6989586621679120258, a6989586621679120258)) (IList a6989586621679120258 ~> Maybe (IList a6989586621679120258)) -> Type) (a6989586621679131294 :: NonEmpty (a6989586621679120258, a6989586621679120258)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelILSym0 :: TyFun (NonEmpty (a6989586621679120258, a6989586621679120258)) (IList a6989586621679120258 ~> Maybe (IList a6989586621679120258)) -> Type) (a6989586621679131294 :: NonEmpty (a6989586621679120258, a6989586621679120258)) = RelabelILSym1 a6989586621679131294
type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a6989586621679120256, a6989586621679120256)) (IList a6989586621679120256 ~> Maybe [(N, N)]) -> Type) (a6989586621679131340 :: NonEmpty (a6989586621679120256, a6989586621679120256)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a6989586621679120256, a6989586621679120256)) (IList a6989586621679120256 ~> Maybe [(N, N)]) -> Type) (a6989586621679131340 :: NonEmpty (a6989586621679120256, a6989586621679120256)) = RelabelTranspositionsSym1 a6989586621679131340
type Apply (Compare_6989586621679136468Sym0 :: TyFun (IList a6989586621679120391) (IList a6989586621679120391 ~> Ordering) -> Type) (a6989586621679136466 :: IList a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679136468Sym0 :: TyFun (IList a6989586621679120391) (IList a6989586621679120391 ~> Ordering) -> Type) (a6989586621679136466 :: IList a6989586621679120391) = Compare_6989586621679136468Sym1 a6989586621679136466
type Apply (ConCovSym0 :: TyFun (NonEmpty a6989586621679120391) (NonEmpty a6989586621679120391 ~> IList a6989586621679120391) -> Type) (t6989586621679130255 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ConCovSym0 :: TyFun (NonEmpty a6989586621679120391) (NonEmpty a6989586621679120391 ~> IList a6989586621679120391) -> Type) (t6989586621679130255 :: NonEmpty a6989586621679120391) = ConCovSym1 t6989586621679130255
type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym1 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130825 :: [a6989586621679120281]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym1 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130825 :: [a6989586621679120281]) = Let6989586621679130870Scrutinee_6989586621679120793Sym2 x6989586621679130824 xs6989586621679130825
type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym1 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130825 :: [a6989586621679120281]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym1 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130825 :: [a6989586621679120281]) = Let6989586621679130854Scrutinee_6989586621679120803Sym2 x6989586621679130824 xs6989586621679130825
type Apply (Lambda_6989586621679131262Sym0 :: TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (TyFun k1 (TyFun (NonEmpty a6989586621679120261) (TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> Type) -> Type) -> Type) -> Type) (rl6989586621679131259 :: NonEmpty (a6989586621679120261, a6989586621679120261)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131262Sym0 :: TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (TyFun k1 (TyFun (NonEmpty a6989586621679120261) (TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> Type) -> Type) -> Type) -> Type) (rl6989586621679131259 :: NonEmpty (a6989586621679120261, a6989586621679120261)) = (Lambda_6989586621679131262Sym1 rl6989586621679131259 :: TyFun k1 (TyFun (NonEmpty a6989586621679120261) (TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> Type) -> Type) -> Type)
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679131136 :: [(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) (a6989586621679131136 :: [(VSpace s n, IList s)]) = HeadR a6989586621679131136
type Apply (MergeRSym0 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (a6989586621679131011 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym0 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (a6989586621679131011 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) = MergeRSym1 a6989586621679131011
type Apply (RemoveUntilSym0 :: TyFun (Ix s6989586621679120271) ([(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] ~> [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)]) -> Type) (a6989586621679131155 :: Ix s6989586621679120271) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym0 :: TyFun (Ix s6989586621679120271) ([(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] ~> [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)]) -> Type) (a6989586621679131155 :: Ix s6989586621679120271) = (RemoveUntilSym1 a6989586621679131155 n6989586621679120272 :: TyFun [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] -> Type)
type Apply (ShowsPrec_6989586621679136449Sym1 a6989586621679136446 a6989586621679120391 :: TyFun (IList a6989586621679120391) (Symbol ~> Symbol) -> Type) (a6989586621679136447 :: IList a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679136449Sym1 a6989586621679136446 a6989586621679120391 :: TyFun (IList a6989586621679120391) (Symbol ~> Symbol) -> Type) (a6989586621679136447 :: IList a6989586621679120391) = ShowsPrec_6989586621679136449Sym2 a6989586621679136446 a6989586621679136447
type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679131518 :: TransRule s6989586621679120266) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679131518 :: TransRule s6989586621679120266) = Let6989586621679131520Scrutinee_6989586621679120863Sym2 vs6989586621679131517 tl6989586621679131518
type Apply (Lambda_6989586621679130973Sym0 :: TyFun (NonEmpty a6989586621679120391) (TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130970 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130973Sym0 :: TyFun (NonEmpty a6989586621679120391) (TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679130970 :: NonEmpty a6989586621679120391) = (Lambda_6989586621679130973Sym1 xs6989586621679130970 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type)
type Apply (Let6989586621679131161GoSym0 :: TyFun (Ix s6989586621679120291) (TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) -> Type) (i6989586621679131159 :: Ix s6989586621679120291) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131161GoSym0 :: TyFun (Ix s6989586621679120291) (TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) -> Type) (i6989586621679131159 :: Ix s6989586621679120291) = (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type)
type Apply (Lambda_6989586621679131032Sym1 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))))) -> Type) (xl6989586621679131018 :: IList s6989586621679120289) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym1 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))))) -> Type) (xl6989586621679131018 :: IList s6989586621679120289) = Lambda_6989586621679131032Sym2 xv6989586621679131017 xl6989586621679131018
type Apply (RelabelRSym1 a6989586621679131310 :: TyFun (NonEmpty (s6989586621679120259, s6989586621679120259)) ([(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] ~> Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)]) -> Type) (a6989586621679131311 :: NonEmpty (s6989586621679120259, s6989586621679120259)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym1 a6989586621679131310 :: TyFun (NonEmpty (s6989586621679120259, s6989586621679120259)) ([(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] ~> Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)]) -> Type) (a6989586621679131311 :: NonEmpty (s6989586621679120259, s6989586621679120259)) = RelabelRSym2 a6989586621679131310 a6989586621679131311
type Apply (TranspositionsSym1 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) (a6989586621679131459 :: TransRule s6989586621679120266) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) (a6989586621679131459 :: TransRule s6989586621679120266) = TranspositionsSym2 a6989586621679131458 a6989586621679131459
type Apply (CanTransposeMultSym1 a6989586621679131511 :: TyFun (TransRule s6989586621679120268) ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool) -> Type) (a6989586621679131512 :: TransRule s6989586621679120268) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679131511 :: TyFun (TransRule s6989586621679120268) ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool) -> Type) (a6989586621679131512 :: TransRule s6989586621679120268) = CanTransposeMultSym2 a6989586621679131511 a6989586621679131512
type Apply (CanTransposeSym1 a6989586621679130754 :: TyFun (Ix s6989586621679120273) (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool)) -> Type) (a6989586621679130755 :: Ix s6989586621679120273) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679130754 :: TyFun (Ix s6989586621679120273) (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool)) -> Type) (a6989586621679130755 :: Ix s6989586621679120273) = CanTransposeSym2 a6989586621679130754 a6989586621679130755
type Apply (Lambda_6989586621679130962Sym1 xs6989586621679130959 :: TyFun (NonEmpty a6989586621679120391) (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (ys6989586621679130960 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130962Sym1 xs6989586621679130959 :: TyFun (NonEmpty a6989586621679120391) (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (ys6989586621679130960 :: NonEmpty a6989586621679120391) = (Lambda_6989586621679130962Sym2 xs6989586621679130959 ys6989586621679130960 :: TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type)
type Apply (Lambda_6989586621679130999Sym1 ys6989586621679130996 :: TyFun (NonEmpty a6989586621679120391) (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (xs6989586621679130997 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130999Sym1 ys6989586621679130996 :: TyFun (NonEmpty a6989586621679120391) (TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) -> Type) (xs6989586621679130997 :: NonEmpty a6989586621679120391) = (Lambda_6989586621679130999Sym2 ys6989586621679130996 xs6989586621679130997 :: TyFun k2 (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type)
type Apply (Let6989586621679131061L'Sym1 v6989586621679131058 :: TyFun (IList a6989586621679120391) (TyFun k2 (Maybe (IList a6989586621679120391)) -> Type) -> Type) (l6989586621679131059 :: IList a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131061L'Sym1 v6989586621679131058 :: TyFun (IList a6989586621679120391) (TyFun k2 (Maybe (IList a6989586621679120391)) -> Type) -> Type) (l6989586621679131059 :: IList a6989586621679120391) = (Let6989586621679131061L'Sym2 v6989586621679131058 l6989586621679131059 :: TyFun k2 (Maybe (IList a6989586621679120391)) -> Type)
type Apply (Let6989586621679130890Scrutinee_6989586621679120785Sym1 v6989586621679130887 :: TyFun (IList a6989586621679120281) (TyFun k2 (Maybe (IList a6989586621679120281)) -> Type) -> Type) (is6989586621679130888 :: IList a6989586621679120281) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130890Scrutinee_6989586621679120785Sym1 v6989586621679130887 :: TyFun (IList a6989586621679120281) (TyFun k2 (Maybe (IList a6989586621679120281)) -> Type) -> Type) (is6989586621679130888 :: IList a6989586621679120281) = (Let6989586621679130890Scrutinee_6989586621679120785Sym2 v6989586621679130887 is6989586621679130888 :: TyFun k2 (Maybe (IList a6989586621679120281)) -> Type)
type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym3 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) (ys6989586621679130827 :: [a6989586621679120281]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130870Scrutinee_6989586621679120793Sym3 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) (ys6989586621679130827 :: [a6989586621679120281]) = Let6989586621679130870Scrutinee_6989586621679120793Sym4 y6989586621679130826 xs6989586621679130825 x6989586621679130824 ys6989586621679130827
type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym3 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) (ys6989586621679130827 :: [a6989586621679120281]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130854Scrutinee_6989586621679120803Sym3 y6989586621679130826 xs6989586621679130825 x6989586621679130824 :: TyFun [a6989586621679120281] (TyFun a6989586621679120281 (TyFun [a6989586621679120281] (Maybe (IList a6989586621679120281)) -> Type) -> Type) -> Type) (ys6989586621679130827 :: [a6989586621679120281]) = Let6989586621679130854Scrutinee_6989586621679120803Sym4 y6989586621679130826 xs6989586621679130825 x6989586621679130824 ys6989586621679130827
type Apply (Lambda_6989586621679130940Sym1 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120286) (TyFun k3 (TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679130937 :: NonEmpty a6989586621679120286) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130940Sym1 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120286) (TyFun k3 (TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679130937 :: NonEmpty a6989586621679120286) = (Lambda_6989586621679130940Sym2 xs6989586621679130936 ys6989586621679130937 :: TyFun k3 (TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679131262Sym2 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120261) (TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> Type) -> Type) (js6989586621679131261 :: NonEmpty a6989586621679120261) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131262Sym2 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120261) (TyFun (NonEmpty (a6989586621679120261, a6989586621679120261)) (Maybe (IList (a6989586621679120261, a6989586621679120261))) -> Type) -> Type) (js6989586621679131261 :: NonEmpty a6989586621679120261) = Lambda_6989586621679131262Sym3 is6989586621679131260 rl6989586621679131259 js6989586621679131261
type Apply (CanTransposeSym2 a6989586621679130755 a6989586621679130754 :: TyFun (Ix s6989586621679120273) ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool) -> Type) (a6989586621679130756 :: Ix s6989586621679120273) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679130755 a6989586621679130754 :: TyFun (Ix s6989586621679120273) ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool) -> Type) (a6989586621679130756 :: Ix s6989586621679120273) = CanTransposeSym3 a6989586621679130755 a6989586621679130754 a6989586621679130756
type Apply (Lambda_6989586621679131032Sym2 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))) -> Type) (xs6989586621679131019 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym2 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))) -> Type) (xs6989586621679131019 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) = Lambda_6989586621679131032Sym3 xl6989586621679131018 xv6989586621679131017 xs6989586621679131019
type Apply (Lambda_6989586621679130984Sym2 xs'6989586621679130982 xs6989586621679130981 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) (ys6989586621679130983 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130984Sym2 xs'6989586621679130982 xs6989586621679130981 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) (ys6989586621679130983 :: NonEmpty a6989586621679120391) = Lambda_6989586621679130984Sym3 xs'6989586621679130982 xs6989586621679130981 ys6989586621679130983
type Apply (Let6989586621679131161GoSym2 r6989586621679131160 i6989586621679131159 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) (a6989586621679131162 :: Ix s6989586621679120291) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131161GoSym2 r6989586621679131160 i6989586621679131159 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) (a6989586621679131162 :: Ix s6989586621679120291) = (Let6989586621679131161GoSym3 r6989586621679131160 i6989586621679131159 a6989586621679131162 :: TyFun [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] -> Type)
type Apply (Lambda_6989586621679130940Sym3 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) (ys'6989586621679130939 :: NonEmpty a6989586621679120286) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130940Sym3 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120286) (TyFun (NonEmpty a6989586621679120286) (Maybe (IList a6989586621679120286)) -> Type) -> Type) (ys'6989586621679130939 :: NonEmpty a6989586621679120286) = Lambda_6989586621679130940Sym4 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 ys'6989586621679130939
type Apply (Lambda_6989586621679131032Sym4 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])) -> Type) (yl6989586621679131021 :: IList s6989586621679120289) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym4 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (IList s6989586621679120289) ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])) -> Type) (yl6989586621679131021 :: IList s6989586621679120289) = Lambda_6989586621679131032Sym5 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 yl6989586621679131021
type Apply (Let6989586621679131268L'Sym3 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) (is'6989586621679131264 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131268L'Sym3 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (IList a6989586621679120391) -> Type) -> Type) (is'6989586621679131264 :: NonEmpty a6989586621679120391) = Let6989586621679131268L'Sym4 js6989586621679131261 is6989586621679131260 rl6989586621679131259 is'6989586621679131264
type Apply (Lambda_6989586621679131265Sym3 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) (is'6989586621679131264 :: NonEmpty a6989586621679120302) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131265Sym3 js6989586621679131261 is6989586621679131260 rl6989586621679131259 :: TyFun (NonEmpty a6989586621679120302) (TyFun (NonEmpty a6989586621679120302) (Maybe (IList a6989586621679120302)) -> Type) -> Type) (is'6989586621679131264 :: NonEmpty a6989586621679120302) = Lambda_6989586621679131265Sym4 js6989586621679131261 is6989586621679131260 rl6989586621679131259 is'6989586621679131264
type Apply (Lambda_6989586621679131032Sym5 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (ys6989586621679131022 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym5 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) -> Type) (ys6989586621679131022 :: [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]) = Lambda_6989586621679131032Sym6 yl6989586621679131021 yv6989586621679131020 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 ys6989586621679131022
type Apply (Lambda_6989586621679130943Sym4 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) (xs''6989586621679130942 :: NonEmpty a6989586621679120391) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130943Sym4 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 :: TyFun (NonEmpty a6989586621679120391) (TyFun (NonEmpty a6989586621679120391) (Maybe (IList a6989586621679120391)) -> Type) -> Type) (xs''6989586621679130942 :: NonEmpty a6989586621679120391) = Lambda_6989586621679130943Sym5 ys'6989586621679130939 xs'6989586621679130938 ys6989586621679130937 xs6989586621679130936 xs''6989586621679130942
type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679131517 :: VSpace s6989586621679120266 n6989586621679120267) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679131517 :: VSpace s6989586621679120266 n6989586621679120267) = Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517
type Apply (CanTransposeSym0 :: TyFun (VSpace s6989586621679120273 n6989586621679120274) (Ix s6989586621679120273 ~> (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool))) -> Type) (a6989586621679130754 :: VSpace s6989586621679120273 n6989586621679120274) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym0 :: TyFun (VSpace s6989586621679120273 n6989586621679120274) (Ix s6989586621679120273 ~> (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool))) -> Type) (a6989586621679130754 :: VSpace s6989586621679120273 n6989586621679120274) = CanTransposeSym1 a6989586621679130754
type Apply (Lambda_6989586621679131032Sym0 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))))) -> Type) (xv6989586621679131017 :: VSpace s6989586621679120289 n6989586621679120290) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym0 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (VSpace s6989586621679120289 n6989586621679120290 ~> (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)])))))) -> Type) (xv6989586621679131017 :: VSpace s6989586621679120289 n6989586621679120290) = Lambda_6989586621679131032Sym1 xv6989586621679131017
type Apply (TranspositionsSym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TransRule s6989586621679120266 ~> ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)])) -> Type) (a6989586621679131458 :: VSpace s6989586621679120266 n6989586621679120267) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TransRule s6989586621679120266 ~> ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)])) -> Type) (a6989586621679131458 :: VSpace s6989586621679120266 n6989586621679120267) = TranspositionsSym1 a6989586621679131458
type Apply (CanTransposeMultSym0 :: TyFun (VSpace s6989586621679120268 n6989586621679120269) (TransRule s6989586621679120268 ~> ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool)) -> Type) (a6989586621679131511 :: VSpace s6989586621679120268 n6989586621679120269) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym0 :: TyFun (VSpace s6989586621679120268 n6989586621679120269) (TransRule s6989586621679120268 ~> ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool)) -> Type) (a6989586621679131511 :: VSpace s6989586621679120268 n6989586621679120269) = CanTransposeMultSym1 a6989586621679131511
type Apply (CanTransposeConSym0 :: TyFun (VSpace s6989586621679120277 n6989586621679120278) (s6989586621679120277 ~> (s6989586621679120277 ~> ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool))) -> Type) (a6989586621679130564 :: VSpace s6989586621679120277 n6989586621679120278) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym0 :: TyFun (VSpace s6989586621679120277 n6989586621679120278) (s6989586621679120277 ~> (s6989586621679120277 ~> ([(VSpace s6989586621679120277 n6989586621679120278, IList s6989586621679120277)] ~> Bool))) -> Type) (a6989586621679130564 :: VSpace s6989586621679120277 n6989586621679120278) = CanTransposeConSym1 a6989586621679130564
type Apply (CanTransposeCovSym0 :: TyFun (VSpace s6989586621679120275 n6989586621679120276) (s6989586621679120275 ~> (s6989586621679120275 ~> ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool))) -> Type) (a6989586621679130659 :: VSpace s6989586621679120275 n6989586621679120276) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym0 :: TyFun (VSpace s6989586621679120275 n6989586621679120276) (s6989586621679120275 ~> (s6989586621679120275 ~> ([(VSpace s6989586621679120275 n6989586621679120276, IList s6989586621679120275)] ~> Bool))) -> Type) (a6989586621679130659 :: VSpace s6989586621679120275 n6989586621679120276) = CanTransposeCovSym1 a6989586621679130659
type Apply (RelabelRSym0 :: TyFun (VSpace s6989586621679120259 n6989586621679120260) (NonEmpty (s6989586621679120259, s6989586621679120259) ~> ([(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] ~> Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)])) -> Type) (a6989586621679131310 :: VSpace s6989586621679120259 n6989586621679120260) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym0 :: TyFun (VSpace s6989586621679120259 n6989586621679120260) (NonEmpty (s6989586621679120259, s6989586621679120259) ~> ([(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)] ~> Maybe [(VSpace s6989586621679120259 n6989586621679120260, IList s6989586621679120259)])) -> Type) (a6989586621679131310 :: VSpace s6989586621679120259 n6989586621679120260) = RelabelRSym1 a6989586621679131310
type Apply (Lambda_6989586621679131032Sym3 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))) -> Type) (yv6989586621679131020 :: VSpace s6989586621679120289 n6989586621679120290) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679131032Sym3 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 :: TyFun (VSpace s6989586621679120289 n6989586621679120290) (IList s6989586621679120289 ~> ([(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)] ~> (IList s6989586621679120289 ~> Maybe [(VSpace s6989586621679120289 n6989586621679120290, IList s6989586621679120289)]))) -> Type) (yv6989586621679131020 :: VSpace s6989586621679120289 n6989586621679120290) = Lambda_6989586621679131032Sym4 xs6989586621679131019 xl6989586621679131018 xv6989586621679131017 yv6989586621679131020

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
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 :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: Sing t -> Sing (Apply Show_Sym0 t) #

sShowList :: 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 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

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

(%==) :: Sing a0 -> Sing b -> Sing (a0 == b) #

(%/=) :: 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

(%~) :: 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 :: Sing a0 -> Demote (Ix a) #

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

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

ShowSing a => Show (Sing z) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

SuppressUnusedWarnings (ShowsPrec_6989586621679136405Sym0 :: TyFun Nat (Ix a6989586621679120382 ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (IxCompareSym0 :: TyFun (Ix a6989586621679120305) (Ix a6989586621679120305 ~> Ordering) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679136420Sym0 :: TyFun (Ix a6989586621679120382) (Ix a6989586621679120382 ~> Ordering) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (IConSym0 :: TyFun a6989586621679120382 (Ix a6989586621679120382) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ICovSym0 :: TyFun a6989586621679120382 (Ix a6989586621679120382) -> 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 s6989586621679120293 n6989586621679120294, IList s6989586621679120293)] (VSpace s6989586621679120293 n6989586621679120294, Ix s6989586621679120293) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (IxCompareSym1 a6989586621679131382 :: TyFun (Ix a6989586621679120305) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679136405Sym1 a6989586621679136402 a6989586621679120382 :: TyFun (Ix a6989586621679120382) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679136420Sym1 a6989586621679136418 :: TyFun (Ix a6989586621679120382) 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 a6989586621679130754 :: TyFun (Ix s6989586621679120273) (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131161GoSym0 :: TyFun (Ix s6989586621679120291) (TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> 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) #

SingI (TyCon1 (ICon :: a -> Ix a) :: a ~> Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon1 ICon) #

SingI (TyCon1 (ICov :: a -> Ix a) :: a ~> Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon1 ICov) #

SuppressUnusedWarnings (CanTransposeSym2 a6989586621679130755 a6989586621679130754 :: TyFun (Ix s6989586621679120273) ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> 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 (Let6989586621679131161GoSym2 r6989586621679131160 i6989586621679131159 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IxCompareSym1 a6989586621679131382 :: TyFun (Ix a) Ordering -> Type) (a6989586621679131383 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IxCompareSym1 a6989586621679131382 :: TyFun (Ix a) Ordering -> Type) (a6989586621679131383 :: Ix a) = IxCompare a6989586621679131382 a6989586621679131383
type Apply (Compare_6989586621679136420Sym1 a6989586621679136418 :: TyFun (Ix a) Ordering -> Type) (a6989586621679136419 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679136420Sym1 a6989586621679136418 :: TyFun (Ix a) Ordering -> Type) (a6989586621679136419 :: Ix a) = Compare_6989586621679136420 a6989586621679136418 a6989586621679136419
data Sing (b :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

data Sing (b :: Ix a) where
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__6989586621680262835Sym0 :: 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_6989586621680262846Sym0 :: 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_6989586621679380340Sym0 :: 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_6989586621679380322Sym0 :: 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_6989586621679380304Sym0 :: 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_6989586621679380286Sym0 :: 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_6989586621679380268Sym0 :: 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_6989586621679380250Sym0 :: 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_6989586621679136420Sym0 :: 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_6989586621679136512 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_6989586621679136405Sym0 :: TyFun Nat (Ix a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (IConSym0 :: TyFun a (Ix a) -> Type) (t6989586621679130251 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IConSym0 :: TyFun a (Ix a) -> Type) (t6989586621679130251 :: a) = ICon t6989586621679130251
type Apply (ICovSym0 :: TyFun a (Ix a) -> Type) (t6989586621679130253 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ICovSym0 :: TyFun a (Ix a) -> Type) (t6989586621679130253 :: a) = ICov t6989586621679130253
type Apply (ShowsPrec_6989586621679136405Sym0 :: TyFun Nat (Ix a6989586621679120382 ~> (Symbol ~> Symbol)) -> Type) (a6989586621679136402 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679136405Sym0 :: TyFun Nat (Ix a6989586621679120382 ~> (Symbol ~> Symbol)) -> Type) (a6989586621679136402 :: Nat) = (ShowsPrec_6989586621679136405Sym1 a6989586621679136402 a6989586621679120382 :: TyFun (Ix a6989586621679120382) (Symbol ~> Symbol) -> Type)
type Apply (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) (r6989586621679131160 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) (r6989586621679131160 :: k) = (Let6989586621679131161GoSym2 i6989586621679131159 r6989586621679131160 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type)
type Apply (IxCompareSym0 :: TyFun (Ix a6989586621679120305) (Ix a6989586621679120305 ~> Ordering) -> Type) (a6989586621679131382 :: Ix a6989586621679120305) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IxCompareSym0 :: TyFun (Ix a6989586621679120305) (Ix a6989586621679120305 ~> Ordering) -> Type) (a6989586621679131382 :: Ix a6989586621679120305) = IxCompareSym1 a6989586621679131382
type Apply (Compare_6989586621679136420Sym0 :: TyFun (Ix a6989586621679120382) (Ix a6989586621679120382 ~> Ordering) -> Type) (a6989586621679136418 :: Ix a6989586621679120382) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679136420Sym0 :: TyFun (Ix a6989586621679120382) (Ix a6989586621679120382 ~> Ordering) -> Type) (a6989586621679136418 :: Ix a6989586621679120382) = Compare_6989586621679136420Sym1 a6989586621679136418
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679131136 :: [(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) (a6989586621679131136 :: [(VSpace s n, IList s)]) = HeadR a6989586621679131136
type Apply (RemoveUntilSym0 :: TyFun (Ix s6989586621679120271) ([(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] ~> [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)]) -> Type) (a6989586621679131155 :: Ix s6989586621679120271) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym0 :: TyFun (Ix s6989586621679120271) ([(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] ~> [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)]) -> Type) (a6989586621679131155 :: Ix s6989586621679120271) = (RemoveUntilSym1 a6989586621679131155 n6989586621679120272 :: TyFun [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] [(VSpace s6989586621679120271 n6989586621679120272, IList s6989586621679120271)] -> Type)
type Apply (ShowsPrec_6989586621679136405Sym1 a6989586621679136402 a6989586621679120382 :: TyFun (Ix a6989586621679120382) (Symbol ~> Symbol) -> Type) (a6989586621679136403 :: Ix a6989586621679120382) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679136405Sym1 a6989586621679136402 a6989586621679120382 :: TyFun (Ix a6989586621679120382) (Symbol ~> Symbol) -> Type) (a6989586621679136403 :: Ix a6989586621679120382) = ShowsPrec_6989586621679136405Sym2 a6989586621679136402 a6989586621679136403
type Apply (Let6989586621679131161GoSym0 :: TyFun (Ix s6989586621679120291) (TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) -> Type) (i6989586621679131159 :: Ix s6989586621679120291) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131161GoSym0 :: TyFun (Ix s6989586621679120291) (TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type) -> Type) (i6989586621679131159 :: Ix s6989586621679120291) = (Let6989586621679131161GoSym1 i6989586621679131159 :: TyFun k (TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) -> Type)
type Apply (CanTransposeSym1 a6989586621679130754 :: TyFun (Ix s6989586621679120273) (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool)) -> Type) (a6989586621679130755 :: Ix s6989586621679120273) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679130754 :: TyFun (Ix s6989586621679120273) (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool)) -> Type) (a6989586621679130755 :: Ix s6989586621679120273) = CanTransposeSym2 a6989586621679130754 a6989586621679130755
type Apply (CanTransposeSym2 a6989586621679130755 a6989586621679130754 :: TyFun (Ix s6989586621679120273) ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool) -> Type) (a6989586621679130756 :: Ix s6989586621679120273) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679130755 a6989586621679130754 :: TyFun (Ix s6989586621679120273) ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool) -> Type) (a6989586621679130756 :: Ix s6989586621679120273) = CanTransposeSym3 a6989586621679130755 a6989586621679130754 a6989586621679130756
type Apply (Let6989586621679131161GoSym2 r6989586621679131160 i6989586621679131159 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) (a6989586621679131162 :: Ix s6989586621679120291) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131161GoSym2 r6989586621679131160 i6989586621679131159 :: TyFun (Ix s6989586621679120291) ([(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] ~> [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)]) -> Type) (a6989586621679131162 :: Ix s6989586621679120291) = (Let6989586621679131161GoSym3 r6989586621679131160 i6989586621679131159 a6989586621679131162 :: TyFun [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] [(VSpace s6989586621679120291 n6989586621679120292, IList s6989586621679120291)] -> Type)
type Apply (CanTransposeSym0 :: TyFun (VSpace s6989586621679120273 n6989586621679120274) (Ix s6989586621679120273 ~> (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool))) -> Type) (a6989586621679130754 :: VSpace s6989586621679120273 n6989586621679120274) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym0 :: TyFun (VSpace s6989586621679120273 n6989586621679120274) (Ix s6989586621679120273 ~> (Ix s6989586621679120273 ~> ([(VSpace s6989586621679120273 n6989586621679120274, IList s6989586621679120273)] ~> Bool))) -> Type) (a6989586621679130754 :: VSpace s6989586621679120273 n6989586621679120274) = CanTransposeSym1 a6989586621679130754

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
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 :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: Sing t -> Sing (Apply Show_Sym0 t) #

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

(%==) :: Sing a0 -> Sing b -> Sing (a0 == b) #

(%/=) :: 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

(%~) :: 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) #

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

ShowSing (NonEmpty a) => Show (Sing z) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

SuppressUnusedWarnings (ShowsPrec_6989586621679136493Sym0 :: TyFun Nat (TransRule a6989586621679120583 ~> (Symbol ~> Symbol)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (SaneTransRuleSym0 :: TyFun (TransRule a6989586621679120270) Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransConSym0 :: TyFun (NonEmpty a6989586621679120583) (NonEmpty a6989586621679120583 ~> TransRule a6989586621679120583) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransCovSym0 :: TyFun (NonEmpty a6989586621679120583) (NonEmpty a6989586621679120583 ~> TransRule a6989586621679120583) -> 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 s6989586621679120266 n6989586621679120267) (TransRule s6989586621679120266 ~> ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679136493Sym1 a6989586621679136490 a6989586621679120583 :: TyFun (TransRule a6989586621679120583) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransConSym1 t6989586621679130263 :: TyFun (NonEmpty a6989586621679120583) (TransRule a6989586621679120583) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransCovSym1 t6989586621679130267 :: TyFun (NonEmpty a6989586621679120583) (TransRule a6989586621679120583) -> 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 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeMultSym1 a6989586621679131511 :: TyFun (TransRule s6989586621679120268) ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool) -> 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

SingI d => SingI (TyCon1 (TransCon d) :: NonEmpty a ~> TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon1 (TransCon d)) #

SingI d => SingI (TyCon1 (TransCov d) :: NonEmpty a ~> TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon1 (TransCov d)) #

SingI (TyCon2 (TransCon :: NonEmpty a -> NonEmpty a -> TransRule a) :: NonEmpty a ~> (NonEmpty a ~> TransRule a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon2 TransCon) #

SingI (TyCon2 (TransCov :: NonEmpty a -> NonEmpty a -> TransRule a) :: NonEmpty a ~> (NonEmpty a ~> TransRule a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon2 TransCov) #

SuppressUnusedWarnings (Let6989586621679131469Scrutinee_6989586621679120869Sym0 :: TyFun k1 (TyFun (TransRule a6989586621679120270) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131469Scrutinee_6989586621679120869Sym1 vs6989586621679131464 :: TyFun (TransRule a6989586621679120270) (TyFun k1 (TyFun k2 (TyFun k3 Bool -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (SaneTransRuleSym0 :: TyFun (TransRule a) Bool -> Type) (a6989586621679131356 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (SaneTransRuleSym0 :: TyFun (TransRule a) Bool -> Type) (a6989586621679131356 :: TransRule a) = SaneTransRule a6989586621679131356
data Sing (b :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

data Sing (b :: TransRule a) where
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__6989586621680262835Sym0 :: 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_6989586621680262846Sym0 :: 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_6989586621679136532 a2 b
type ShowsPrec a2 (a3 :: TransRule a1) a4 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransConSym1 t6989586621679130263 :: TyFun (NonEmpty a) (TransRule a) -> Type) (t6989586621679130264 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransConSym1 t6989586621679130263 :: TyFun (NonEmpty a) (TransRule a) -> Type) (t6989586621679130264 :: NonEmpty a) = TransCon t6989586621679130263 t6989586621679130264
type Apply (TransCovSym1 t6989586621679130267 :: TyFun (NonEmpty a) (TransRule a) -> Type) (t6989586621679130268 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransCovSym1 t6989586621679130267 :: TyFun (NonEmpty a) (TransRule a) -> Type) (t6989586621679130268 :: NonEmpty a) = TransCov t6989586621679130267 t6989586621679130268
type Apply (ShowsPrec_6989586621679136493Sym0 :: TyFun Nat (TransRule a6989586621679120583 ~> (Symbol ~> Symbol)) -> Type) (a6989586621679136490 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679136493Sym0 :: TyFun Nat (TransRule a6989586621679120583 ~> (Symbol ~> Symbol)) -> Type) (a6989586621679136490 :: Nat) = (ShowsPrec_6989586621679136493Sym1 a6989586621679136490 a6989586621679120583 :: TyFun (TransRule a6989586621679120583) (Symbol ~> Symbol) -> Type)
type Apply (Let6989586621679131469Scrutinee_6989586621679120869Sym0 :: TyFun k1 (TyFun (TransRule a6989586621679120270) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (vs6989586621679131464 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131469Scrutinee_6989586621679120869Sym0 :: TyFun k1 (TyFun (TransRule a6989586621679120270) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (vs6989586621679131464 :: k1) = (Let6989586621679131469Scrutinee_6989586621679120869Sym1 vs6989586621679131464 :: TyFun (TransRule a6989586621679120270) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type)
type Apply (TransConSym0 :: TyFun (NonEmpty a6989586621679120583) (NonEmpty a6989586621679120583 ~> TransRule a6989586621679120583) -> Type) (t6989586621679130263 :: NonEmpty a6989586621679120583) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransConSym0 :: TyFun (NonEmpty a6989586621679120583) (NonEmpty a6989586621679120583 ~> TransRule a6989586621679120583) -> Type) (t6989586621679130263 :: NonEmpty a6989586621679120583) = TransConSym1 t6989586621679130263
type Apply (TransCovSym0 :: TyFun (NonEmpty a6989586621679120583) (NonEmpty a6989586621679120583 ~> TransRule a6989586621679120583) -> Type) (t6989586621679130267 :: NonEmpty a6989586621679120583) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransCovSym0 :: TyFun (NonEmpty a6989586621679120583) (NonEmpty a6989586621679120583 ~> TransRule a6989586621679120583) -> Type) (t6989586621679130267 :: NonEmpty a6989586621679120583) = TransCovSym1 t6989586621679130267
type Apply (ShowsPrec_6989586621679136493Sym1 a6989586621679136490 a6989586621679120583 :: TyFun (TransRule a6989586621679120583) (Symbol ~> Symbol) -> Type) (a6989586621679136491 :: TransRule a6989586621679120583) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679136493Sym1 a6989586621679136490 a6989586621679120583 :: TyFun (TransRule a6989586621679120583) (Symbol ~> Symbol) -> Type) (a6989586621679136491 :: TransRule a6989586621679120583) = ShowsPrec_6989586621679136493Sym2 a6989586621679136490 a6989586621679136491
type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679131518 :: TransRule s6989586621679120266) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679131518 :: TransRule s6989586621679120266) = Let6989586621679131520Scrutinee_6989586621679120863Sym2 vs6989586621679131517 tl6989586621679131518
type Apply (TranspositionsSym1 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) (a6989586621679131459 :: TransRule s6989586621679120266) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) (a6989586621679131459 :: TransRule s6989586621679120266) = TranspositionsSym2 a6989586621679131458 a6989586621679131459
type Apply (CanTransposeMultSym1 a6989586621679131511 :: TyFun (TransRule s6989586621679120268) ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool) -> Type) (a6989586621679131512 :: TransRule s6989586621679120268) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679131511 :: TyFun (TransRule s6989586621679120268) ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool) -> Type) (a6989586621679131512 :: TransRule s6989586621679120268) = CanTransposeMultSym2 a6989586621679131511 a6989586621679131512
type Apply (Let6989586621679131469Scrutinee_6989586621679120869Sym1 vs6989586621679131464 :: TyFun (TransRule a6989586621679120270) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (tl6989586621679131465 :: TransRule a6989586621679120270) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131469Scrutinee_6989586621679120869Sym1 vs6989586621679131464 :: TyFun (TransRule a6989586621679120270) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (tl6989586621679131465 :: TransRule a6989586621679120270) = (Let6989586621679131469Scrutinee_6989586621679120869Sym2 vs6989586621679131464 tl6989586621679131465 :: TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type)
type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679131517 :: VSpace s6989586621679120266 n6989586621679120267) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679131517 :: VSpace s6989586621679120266 n6989586621679120267) = Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517
type Apply (TranspositionsSym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TransRule s6989586621679120266 ~> ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)])) -> Type) (a6989586621679131458 :: VSpace s6989586621679120266 n6989586621679120267) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TransRule s6989586621679120266 ~> ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)])) -> Type) (a6989586621679131458 :: VSpace s6989586621679120266 n6989586621679120267) = TranspositionsSym1 a6989586621679131458
type Apply (CanTransposeMultSym0 :: TyFun (VSpace s6989586621679120268 n6989586621679120269) (TransRule s6989586621679120268 ~> ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool)) -> Type) (a6989586621679131511 :: VSpace s6989586621679120268 n6989586621679120269) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym0 :: TyFun (VSpace s6989586621679120268 n6989586621679120269) (TransRule s6989586621679120268 ~> ([(VSpace s6989586621679120268 n6989586621679120269, IList s6989586621679120268)] ~> Bool)) -> Type) (a6989586621679131511 :: VSpace s6989586621679120268 n6989586621679120269) = CanTransposeMultSym1 a6989586621679131511

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
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
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 :: Sing t1 -> Sing t2 -> Sing t3 -> Sing (Apply (Apply (Apply ShowsPrecSym0 t1) t2) t3) #

sShow_ :: Sing t -> Sing (Apply Show_Sym0 t) #

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

(%+) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (+@#@$) t1) t2) #

(%-) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (-@#@$) t1) t2) #

(%*) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (*@#@$) t1) t2) #

sNegate :: Sing t -> Sing (Apply NegateSym0 t) #

sAbs :: Sing t -> Sing (Apply AbsSym0 t) #

sSignum :: Sing t -> Sing (Apply SignumSym0 t) #

sFromInteger :: 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 :: Sing t1 -> Sing t2 -> Sing (Apply (Apply CompareSym0 t1) t2) #

(%<) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<@#@$) t1) t2) #

(%<=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (<=@#@$) t1) t2) #

(%>) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>@#@$) t1) t2) #

(%>=) :: Sing t1 -> Sing t2 -> Sing (Apply (Apply (>=@#@$) t1) t2) #

sMax :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MaxSym0 t1) t2) #

sMin :: Sing t1 -> Sing t2 -> Sing (Apply (Apply MinSym0 t1) t2) #

SEq N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(%==) :: Sing a -> Sing b -> Sing (a == b) #

(%/=) :: 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

(%~) :: 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 :: Sing a -> Demote N #

toSing :: Demote N -> SomeSing N #

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

Show (Sing z) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

showsPrec :: Int -> Sing z -> ShowS #

show :: Sing z -> String #

showList :: [Sing z] -> ShowS #

SuppressUnusedWarnings FromInteger_6989586621679136349Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings FromNatSym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings ShowsPrec_6989586621679133919Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Signum_6989586621679136335Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Abs_6989586621679136328Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Negate_6989586621679136309Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings SSym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679135706Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679136320Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679136302Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679136289Sym0 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_6989586621679135706Sym1 a6989586621679135704 :: TyFun N Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679136320Sym1 a6989586621679136318 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679136302Sym1 a6989586621679136300 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679136289Sym1 a6989586621679136287 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679133919Sym1 a6989586621679133916 :: TyFun N (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelTranspositions'Sym0 :: TyFun (NonEmpty (a6989586621679120254, a6989586621679120254)) [(N, N)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Transpositions'Sym0 :: TyFun (NonEmpty a6989586621679120263) (NonEmpty a6989586621679120263 ~> (NonEmpty (Maybe a6989586621679120263) ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (LengthNESym0 :: TyFun (NonEmpty a6989586621679120300) 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 s6989586621679120297 n6989586621679120298, IList s6989586621679120297)] N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130274Is'Sym0 :: TyFun (NonEmpty (a6989586621679120726, b6989586621679120727)) (NonEmpty (N, b6989586621679120727)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130274Is'''Sym0 :: TyFun (NonEmpty (a6989586621679120726, b6989586621679120729)) (NonEmpty (N, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Transpositions'Sym1 a6989586621679130441 :: TyFun (NonEmpty a6989586621679120263) (NonEmpty (Maybe a6989586621679120263) ~> 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 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130274Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679120728, b6989586621679120729) ~> NonEmpty (a6989586621679120728, N)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130274GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679120726, b6989586621679120727) ~> NonEmpty (N, b6989586621679120727)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130512Sym0 :: 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_6989586621679130520Sym0 :: TyFun k1 (TyFun (NonEmpty a6989586621680748363) (TyFun (NonEmpty (Maybe a6989586621680748363)) (TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Transpositions'Sym2 a6989586621679130442 a6989586621679130441 :: TyFun (NonEmpty (Maybe a6989586621679120263)) (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (TyCon1 S) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TyCon1 S) #

(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 a6989586621679131459 a6989586621679131458 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679131520Scrutinee_6989586621679120863Sym2 tl6989586621679131518 vs6989586621679131517 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130274Go'Sym1 is6989586621679130273 a6989586621679120728 b6989586621679120729 :: TyFun N (NonEmpty (a6989586621679120728, b6989586621679120729) ~> NonEmpty (a6989586621679120728, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130274GoSym1 is6989586621679130273 a6989586621679120726 b6989586621679120727 :: TyFun N (NonEmpty (a6989586621679120726, b6989586621679120727) ~> NonEmpty (N, b6989586621679120727)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130450Xs'Sym1 sources6989586621679130447 :: TyFun k1 (TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130512Sym1 sources6989586621679130447 :: TyFun k1 (TyFun (NonEmpty (Maybe k2)) (TyFun k2 (Maybe N) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130523Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k4)) (TyFun k3 (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130520Sym1 sources6989586621679130447 :: TyFun (NonEmpty a6989586621680748363) (TyFun (NonEmpty (Maybe a6989586621680748363)) (TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, 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 (Let6989586621679130450FindSym1 sources6989586621679130447 :: TyFun k1 (TyFun k2 (TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130450Go'Sym1 sources6989586621679130447 :: TyFun k1 (TyFun k2 (TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130523Sym1 sources6989586621679130447 :: TyFun k1 (TyFun (NonEmpty (Maybe k3)) (TyFun k2 (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130512Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (Maybe k1)) (TyFun k1 (Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130520Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (Maybe a6989586621680748363)) (TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130274Go'Sym2 a6989586621679130284 is6989586621679130273 a6989586621679120728 b6989586621679120729 :: TyFun (NonEmpty (a6989586621679120728, b6989586621679120729)) (NonEmpty (a6989586621679120728, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130274GoSym2 a6989586621679130295 is6989586621679130273 a6989586621679120726 b6989586621679120727 :: TyFun (NonEmpty (a6989586621679120726, b6989586621679120727)) (NonEmpty (N, b6989586621679120727)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130450Xs'Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130450FindSym2 targets6989586621679130448 sources6989586621679130447 :: TyFun k1 (TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130450Go'Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun k1 (TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130512Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun k1 (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130523Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (Maybe k2)) (TyFun k1 (TyFun k2 (Maybe N) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130520Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130450Go'Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679120628 :: TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130450FindSym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679120629 :: TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130523Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun k1 (TyFun k2 (Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679130523Sym4 ss6989586621679130522 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun k2 (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130450FindSym4 a6989586621679130466 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (N, Maybe a6989586621679120629)) (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679130450Go'Sym4 a6989586621679130496 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679120628 :: TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

data Sing (a :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

data Sing (a :: N) where
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__6989586621680262835Sym0 :: 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_6989586621680262846Sym0 :: 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_6989586621679136320Sym0 a1) a2
type (a1 :: N) - (a2 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type (a1 :: N) + (a2 :: N) = Apply (Apply TFHelper_6989586621679136289Sym0 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_6989586621679380340Sym0 :: 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_6989586621679380322Sym0 :: 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_6989586621679380304Sym0 :: 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_6989586621679380286Sym0 :: 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_6989586621679135706Sym0 a1) a2
type (arg :: N) < (arg1 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: N) < (arg1 :: N) = Apply (Apply (TFHelper_6989586621679380250Sym0 :: 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_6989586621679380232Sym0 :: 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_6989586621679136498 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_6989586621679133919Sym0 a1) a2) a3
type Apply FromInteger_6989586621679136349Sym0 (a6989586621679136348 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply FromInteger_6989586621679136349Sym0 (a6989586621679136348 :: Nat) = FromInteger_6989586621679136349 a6989586621679136348
type Apply FromNatSym0 (a6989586621679131527 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply FromNatSym0 (a6989586621679131527 :: Nat) = FromNat a6989586621679131527
type Apply Signum_6989586621679136335Sym0 (a6989586621679136334 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Signum_6989586621679136335Sym0 (a6989586621679136334 :: N) = Signum_6989586621679136335 a6989586621679136334
type Apply Abs_6989586621679136328Sym0 (a6989586621679136327 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Abs_6989586621679136328Sym0 (a6989586621679136327 :: N) = Abs_6989586621679136328 a6989586621679136327
type Apply Negate_6989586621679136309Sym0 (a6989586621679136308 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Negate_6989586621679136309Sym0 (a6989586621679136308 :: N) = Negate_6989586621679136309 a6989586621679136308
type Apply SSym0 (t6989586621679130245 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply SSym0 (t6989586621679130245 :: N) = S t6989586621679130245
type Apply (TFHelper_6989586621679135706Sym1 a6989586621679135704 :: TyFun N Bool -> Type) (a6989586621679135705 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679135706Sym1 a6989586621679135704 :: TyFun N Bool -> Type) (a6989586621679135705 :: N) = TFHelper_6989586621679135706 a6989586621679135704 a6989586621679135705
type Apply (TFHelper_6989586621679136320Sym1 a6989586621679136318 :: TyFun N N -> Type) (a6989586621679136319 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679136320Sym1 a6989586621679136318 :: TyFun N N -> Type) (a6989586621679136319 :: N) = TFHelper_6989586621679136320 a6989586621679136318 a6989586621679136319
type Apply (TFHelper_6989586621679136302Sym1 a6989586621679136300 :: TyFun N N -> Type) (a6989586621679136301 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679136302Sym1 a6989586621679136300 :: TyFun N N -> Type) (a6989586621679136301 :: N) = TFHelper_6989586621679136302 a6989586621679136300 a6989586621679136301
type Apply (TFHelper_6989586621679136289Sym1 a6989586621679136287 :: TyFun N N -> Type) (a6989586621679136288 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679136289Sym1 a6989586621679136287 :: TyFun N N -> Type) (a6989586621679136288 :: N) = TFHelper_6989586621679136289 a6989586621679136287 a6989586621679136288
type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679131182 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679131182 :: IList a) = LengthIL a6989586621679131182
type Apply (LengthNESym0 :: TyFun (NonEmpty a) N -> Type) (a6989586621679131178 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (LengthNESym0 :: TyFun (NonEmpty a) N -> Type) (a6989586621679131178 :: NonEmpty a) = LengthNE a6989586621679131178
type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679131188 :: [(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) (a6989586621679131188 :: [(VSpace s n, IList s)]) = LengthR a6989586621679131188
type Apply (Lambda_6989586621679130512Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun k3 (Maybe N) -> Type) (t6989586621679130515 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130512Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun k3 (Maybe N) -> Type) (t6989586621679130515 :: k3) = Lambda_6989586621679130512 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 t6989586621679130515
type Apply (Lambda_6989586621679130523Sym4 ss6989586621679130522 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun k3 (Maybe N) -> Type) (t6989586621679130526 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130523Sym4 ss6989586621679130522 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun k3 (Maybe N) -> Type) (t6989586621679130526 :: k3) = Lambda_6989586621679130523 ss6989586621679130522 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 t6989586621679130526
type Apply (RelabelTranspositions'Sym0 :: TyFun (NonEmpty (a, a)) [(N, N)] -> Type) (a6989586621679130271 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositions'Sym0 :: TyFun (NonEmpty (a, a)) [(N, N)] -> Type) (a6989586621679130271 :: NonEmpty (a, a)) = RelabelTranspositions' a6989586621679130271
type Apply (RelabelTranspositionsSym1 a6989586621679131340 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679131341 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym1 a6989586621679131340 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679131341 :: IList a) = RelabelTranspositions a6989586621679131340 a6989586621679131341
type Apply (Let6989586621679130274Is'''Sym0 :: TyFun (NonEmpty (a6989586621679120726, b6989586621679120729)) (NonEmpty (N, N)) -> Type) (is6989586621679130273 :: NonEmpty (a6989586621679120726, b6989586621679120729)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130274Is'''Sym0 :: TyFun (NonEmpty (a6989586621679120726, b6989586621679120729)) (NonEmpty (N, N)) -> Type) (is6989586621679130273 :: NonEmpty (a6989586621679120726, b6989586621679120729)) = Let6989586621679130274Is''' is6989586621679130273
type Apply (Let6989586621679130274Is'Sym0 :: TyFun (NonEmpty (a6989586621679120726, b6989586621679120727)) (NonEmpty (N, b6989586621679120727)) -> Type) (is6989586621679130273 :: NonEmpty (a6989586621679120726, b6989586621679120727)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130274Is'Sym0 :: TyFun (NonEmpty (a6989586621679120726, b6989586621679120727)) (NonEmpty (N, b6989586621679120727)) -> Type) (is6989586621679130273 :: NonEmpty (a6989586621679120726, b6989586621679120727)) = Let6989586621679130274Is' is6989586621679130273
type Apply (Let6989586621679130274Is''Sym0 :: TyFun (NonEmpty (a6989586621679120726, k1)) (NonEmpty (N, k1)) -> Type) (is6989586621679130273 :: NonEmpty (a6989586621679120726, k1)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130274Is''Sym0 :: TyFun (NonEmpty (a6989586621679120726, k1)) (NonEmpty (N, k1)) -> Type) (is6989586621679130273 :: NonEmpty (a6989586621679120726, k1)) = Let6989586621679130274Is'' is6989586621679130273
type Apply (Transpositions'Sym2 a6989586621679130442 a6989586621679130441 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) (a6989586621679130443 :: NonEmpty (Maybe a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Transpositions'Sym2 a6989586621679130442 a6989586621679130441 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) (a6989586621679130443 :: NonEmpty (Maybe a)) = Transpositions' a6989586621679130442 a6989586621679130441 a6989586621679130443
type Apply (TranspositionsSym2 a6989586621679131459 a6989586621679131458 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679131460 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679131459 a6989586621679131458 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679131460 :: [(VSpace s n, IList s)]) = Transpositions a6989586621679131459 a6989586621679131458 a6989586621679131460
type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym2 tl6989586621679131518 vs6989586621679131517 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) (r6989586621679131519 :: [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym2 tl6989586621679131518 vs6989586621679131517 :: TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) (r6989586621679131519 :: [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)]) = Let6989586621679131520Scrutinee_6989586621679120863 tl6989586621679131518 vs6989586621679131517 r6989586621679131519
type Apply (Let6989586621679130274GoSym2 a6989586621679130295 is6989586621679130273 a6989586621679120726 b6989586621679120727 :: TyFun (NonEmpty (a6989586621679120726, b6989586621679120727)) (NonEmpty (N, b6989586621679120727)) -> Type) (a6989586621679130296 :: NonEmpty (a6989586621679120726, b6989586621679120727)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130274GoSym2 a6989586621679130295 is6989586621679130273 a6989586621679120726 b6989586621679120727 :: TyFun (NonEmpty (a6989586621679120726, b6989586621679120727)) (NonEmpty (N, b6989586621679120727)) -> Type) (a6989586621679130296 :: NonEmpty (a6989586621679120726, b6989586621679120727)) = Let6989586621679130274Go a6989586621679130295 is6989586621679130273 a6989586621679130296
type Apply (Let6989586621679130450Xs'Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) (xs6989586621679130449 :: NonEmpty a6989586621679120628) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450Xs'Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) (xs6989586621679130449 :: NonEmpty a6989586621679120628) = Let6989586621679130450Xs' targets6989586621679130448 sources6989586621679130447 xs6989586621679130449
type Apply (Let6989586621679130274Go'Sym2 a6989586621679130284 is6989586621679130273 a6989586621679120728 b6989586621679120729 :: TyFun (NonEmpty (a6989586621679120728, b6989586621679120729)) (NonEmpty (a6989586621679120728, N)) -> Type) (a6989586621679130285 :: NonEmpty (a6989586621679120728, b6989586621679120729)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130274Go'Sym2 a6989586621679130284 is6989586621679130273 a6989586621679120728 b6989586621679120729 :: TyFun (NonEmpty (a6989586621679120728, b6989586621679120729)) (NonEmpty (a6989586621679120728, N)) -> Type) (a6989586621679130285 :: NonEmpty (a6989586621679120728, b6989586621679120729)) = Let6989586621679130274Go' a6989586621679130284 is6989586621679130273 a6989586621679130285
type Apply (Lambda_6989586621679130520Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) (t6989586621679130541 :: NonEmpty a6989586621679120630) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130520Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) (t6989586621679130541 :: NonEmpty a6989586621679120630) = Lambda_6989586621679130520 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 t6989586621679130541
type Apply (Let6989586621679130450FindSym4 a6989586621679130466 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (N, Maybe a6989586621679120629)) (Maybe N) -> Type) (a6989586621679130467 :: NonEmpty (N, Maybe a6989586621679120629)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450FindSym4 a6989586621679130466 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (N, Maybe a6989586621679120629)) (Maybe N) -> Type) (a6989586621679130467 :: NonEmpty (N, Maybe a6989586621679120629)) = Let6989586621679130450Find a6989586621679130466 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679130467
type Apply (Let6989586621679130450Go'Sym4 a6989586621679130496 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679120628 :: TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) (a6989586621679130497 :: NonEmpty a6989586621679120628) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450Go'Sym4 a6989586621679130496 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679120628 :: TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) (a6989586621679130497 :: NonEmpty a6989586621679120628) = Let6989586621679130450Go' a6989586621679130496 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679130497
type Apply TFHelper_6989586621679135706Sym0 (a6989586621679135704 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679135706Sym0 (a6989586621679135704 :: N) = TFHelper_6989586621679135706Sym1 a6989586621679135704
type Apply TFHelper_6989586621679136320Sym0 (a6989586621679136318 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679136320Sym0 (a6989586621679136318 :: N) = TFHelper_6989586621679136320Sym1 a6989586621679136318
type Apply TFHelper_6989586621679136302Sym0 (a6989586621679136300 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679136302Sym0 (a6989586621679136300 :: N) = TFHelper_6989586621679136302Sym1 a6989586621679136300
type Apply TFHelper_6989586621679136289Sym0 (a6989586621679136287 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679136289Sym0 (a6989586621679136287 :: N) = TFHelper_6989586621679136289Sym1 a6989586621679136287
type Apply ShowsPrec_6989586621679133919Sym0 (a6989586621679133916 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply ShowsPrec_6989586621679133919Sym0 (a6989586621679133916 :: Nat) = ShowsPrec_6989586621679133919Sym1 a6989586621679133916
type Apply (ShowsPrec_6989586621679133919Sym1 a6989586621679133916 :: TyFun N (Symbol ~> Symbol) -> Type) (a6989586621679133917 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679133919Sym1 a6989586621679133916 :: TyFun N (Symbol ~> Symbol) -> Type) (a6989586621679133917 :: N) = ShowsPrec_6989586621679133919Sym2 a6989586621679133916 a6989586621679133917
type Apply (Let6989586621679130274Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679120728, b6989586621679120729) ~> NonEmpty (a6989586621679120728, N)) -> Type) -> Type) (is6989586621679130273 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130274Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679120728, b6989586621679120729) ~> NonEmpty (a6989586621679120728, N)) -> Type) -> Type) (is6989586621679130273 :: k) = (Let6989586621679130274Go'Sym1 is6989586621679130273 a6989586621679120728 b6989586621679120729 :: TyFun N (NonEmpty (a6989586621679120728, b6989586621679120729) ~> NonEmpty (a6989586621679120728, N)) -> Type)
type Apply (Let6989586621679130274GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679120726, b6989586621679120727) ~> NonEmpty (N, b6989586621679120727)) -> Type) -> Type) (is6989586621679130273 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130274GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679120726, b6989586621679120727) ~> NonEmpty (N, b6989586621679120727)) -> Type) -> Type) (is6989586621679130273 :: k) = (Let6989586621679130274GoSym1 is6989586621679130273 a6989586621679120726 b6989586621679120727 :: TyFun N (NonEmpty (a6989586621679120726, b6989586621679120727) ~> NonEmpty (N, b6989586621679120727)) -> Type)
type Apply (Let6989586621679130450Xs'Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450Xs'Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) = (Let6989586621679130450Xs'Sym1 sources6989586621679130447 :: TyFun k2 (TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) -> Type)
type Apply (Lambda_6989586621679130512Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130512Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) = (Lambda_6989586621679130512Sym1 sources6989586621679130447 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679130520Sym0 :: TyFun k1 (TyFun (NonEmpty a6989586621680748363) (TyFun (NonEmpty (Maybe a6989586621680748363)) (TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130520Sym0 :: TyFun k1 (TyFun (NonEmpty a6989586621680748363) (TyFun (NonEmpty (Maybe a6989586621680748363)) (TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) = (Lambda_6989586621679130520Sym1 sources6989586621679130447 :: TyFun (NonEmpty a6989586621680748363) (TyFun (NonEmpty (Maybe a6989586621680748363)) (TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) -> Type) -> Type)
type Apply (Let6989586621679130450FindSym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450FindSym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) = (Let6989586621679130450FindSym1 sources6989586621679130447 :: TyFun k2 (TyFun k3 (TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) -> Type) -> Type)
type Apply (Let6989586621679130450Go'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450Go'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) = (Let6989586621679130450Go'Sym1 sources6989586621679130447 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679130523Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k4 (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130523Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k4 (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) -> Type) (sources6989586621679130447 :: k1) = (Lambda_6989586621679130523Sym1 sources6989586621679130447 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k4 (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type)
type Apply (Lambda_6989586621679130512Sym1 sources6989586621679130447 :: TyFun k1 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679130448 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130512Sym1 sources6989586621679130447 :: TyFun k1 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679130448 :: k1) = (Lambda_6989586621679130512Sym2 sources6989586621679130447 targets6989586621679130448 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type)
type Apply (Let6989586621679130450Xs'Sym1 sources6989586621679130447 :: TyFun k1 (TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) -> Type) (targets6989586621679130448 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450Xs'Sym1 sources6989586621679130447 :: TyFun k1 (TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type) -> Type) (targets6989586621679130448 :: k1) = (Let6989586621679130450Xs'Sym2 sources6989586621679130447 targets6989586621679130448 :: TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type)
type Apply (Let6989586621679130274Go'Sym1 is6989586621679130273 a6989586621679120728 b6989586621679120729 :: TyFun N (NonEmpty (a6989586621679120728, b6989586621679120729) ~> NonEmpty (a6989586621679120728, N)) -> Type) (a6989586621679130284 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130274Go'Sym1 is6989586621679130273 a6989586621679120728 b6989586621679120729 :: TyFun N (NonEmpty (a6989586621679120728, b6989586621679120729) ~> NonEmpty (a6989586621679120728, N)) -> Type) (a6989586621679130284 :: N) = (Let6989586621679130274Go'Sym2 is6989586621679130273 a6989586621679130284 a6989586621679120728 b6989586621679120729 :: TyFun (NonEmpty (a6989586621679120728, b6989586621679120729)) (NonEmpty (a6989586621679120728, N)) -> Type)
type Apply (Let6989586621679130274GoSym1 is6989586621679130273 a6989586621679120726 b6989586621679120727 :: TyFun N (NonEmpty (a6989586621679120726, b6989586621679120727) ~> NonEmpty (N, b6989586621679120727)) -> Type) (a6989586621679130295 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130274GoSym1 is6989586621679130273 a6989586621679120726 b6989586621679120727 :: TyFun N (NonEmpty (a6989586621679120726, b6989586621679120727) ~> NonEmpty (N, b6989586621679120727)) -> Type) (a6989586621679130295 :: N) = (Let6989586621679130274GoSym2 is6989586621679130273 a6989586621679130295 a6989586621679120726 b6989586621679120727 :: TyFun (NonEmpty (a6989586621679120726, b6989586621679120727)) (NonEmpty (N, b6989586621679120727)) -> Type)
type Apply (Let6989586621679130450FindSym1 sources6989586621679130447 :: TyFun k1 (TyFun k3 (TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) -> Type) -> Type) (targets6989586621679130448 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450FindSym1 sources6989586621679130447 :: TyFun k1 (TyFun k3 (TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) -> Type) -> Type) (targets6989586621679130448 :: k1) = (Let6989586621679130450FindSym2 sources6989586621679130447 targets6989586621679130448 :: TyFun k3 (TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) -> Type)
type Apply (Let6989586621679130450Go'Sym1 sources6989586621679130447 :: TyFun k1 (TyFun k3 (TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) -> Type) -> Type) (targets6989586621679130448 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450Go'Sym1 sources6989586621679130447 :: TyFun k1 (TyFun k3 (TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) -> Type) -> Type) (targets6989586621679130448 :: k1) = (Let6989586621679130450Go'Sym2 sources6989586621679130447 targets6989586621679130448 :: TyFun k3 (TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) -> Type)
type Apply (Lambda_6989586621679130523Sym1 sources6989586621679130447 :: TyFun k1 (TyFun (NonEmpty (Maybe k3)) (TyFun k4 (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) (targets6989586621679130448 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130523Sym1 sources6989586621679130447 :: TyFun k1 (TyFun (NonEmpty (Maybe k3)) (TyFun k4 (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) (targets6989586621679130448 :: k1) = (Lambda_6989586621679130523Sym2 sources6989586621679130447 targets6989586621679130448 :: TyFun (NonEmpty (Maybe k3)) (TyFun k4 (TyFun k3 (Maybe N) -> Type) -> Type) -> Type)
type Apply (Let6989586621679130450Go'Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun k3 (TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) -> Type) (xs6989586621679130449 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450Go'Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun k3 (TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) -> Type) (xs6989586621679130449 :: k3) = (Let6989586621679130450Go'Sym3 targets6989586621679130448 sources6989586621679130447 xs6989586621679130449 a6989586621679120628 :: TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type)
type Apply (Let6989586621679130450FindSym2 targets6989586621679130448 sources6989586621679130447 :: TyFun k3 (TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) -> Type) (xs6989586621679130449 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450FindSym2 targets6989586621679130448 sources6989586621679130447 :: TyFun k3 (TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) -> Type) (xs6989586621679130449 :: k3) = (Let6989586621679130450FindSym3 targets6989586621679130448 sources6989586621679130447 xs6989586621679130449 a6989586621679120629 :: TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type)
type Apply (Lambda_6989586621679130523Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun k4 (TyFun k3 (Maybe N) -> Type) -> Type) (ss6989586621679130522 :: k4) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130523Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 :: TyFun k4 (TyFun k3 (Maybe N) -> Type) -> Type) (ss6989586621679130522 :: k4) = Lambda_6989586621679130523Sym4 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 ss6989586621679130522
type Apply (Let6989586621679130450FindSym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679120629 :: TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) (a6989586621679130466 :: a6989586621679120629) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450FindSym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679120629 :: TyFun a6989586621679120629 (NonEmpty (N, Maybe a6989586621679120629) ~> Maybe N) -> Type) (a6989586621679130466 :: a6989586621679120629) = Let6989586621679130450FindSym4 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679130466
type Apply (Let6989586621679130450Go'Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679120628 :: TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) (a6989586621679130496 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679130450Go'Sym3 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679120628 :: TyFun N (NonEmpty a6989586621679120628 ~> NonEmpty (N, a6989586621679120628)) -> Type) (a6989586621679130496 :: N) = (Let6989586621679130450Go'Sym4 xs6989586621679130449 targets6989586621679130448 sources6989586621679130447 a6989586621679130496 a6989586621679120628 :: TyFun (NonEmpty a6989586621679120628) (NonEmpty (N, a6989586621679120628)) -> Type)
type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a6989586621679120256, a6989586621679120256)) (IList a6989586621679120256 ~> Maybe [(N, N)]) -> Type) (a6989586621679131340 :: NonEmpty (a6989586621679120256, a6989586621679120256)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a6989586621679120256, a6989586621679120256)) (IList a6989586621679120256 ~> Maybe [(N, N)]) -> Type) (a6989586621679131340 :: NonEmpty (a6989586621679120256, a6989586621679120256)) = RelabelTranspositionsSym1 a6989586621679131340
type Apply (Transpositions'Sym0 :: TyFun (NonEmpty a6989586621679120263) (NonEmpty a6989586621679120263 ~> (NonEmpty (Maybe a6989586621679120263) ~> Maybe [(N, N)])) -> Type) (a6989586621679130441 :: NonEmpty a6989586621679120263) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Transpositions'Sym0 :: TyFun (NonEmpty a6989586621679120263) (NonEmpty a6989586621679120263 ~> (NonEmpty (Maybe a6989586621679120263) ~> Maybe [(N, N)])) -> Type) (a6989586621679130441 :: NonEmpty a6989586621679120263) = Transpositions'Sym1 a6989586621679130441
type Apply (Transpositions'Sym1 a6989586621679130441 :: TyFun (NonEmpty a6989586621679120263) (NonEmpty (Maybe a6989586621679120263) ~> Maybe [(N, N)]) -> Type) (a6989586621679130442 :: NonEmpty a6989586621679120263) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Transpositions'Sym1 a6989586621679130441 :: TyFun (NonEmpty a6989586621679120263) (NonEmpty (Maybe a6989586621679120263) ~> Maybe [(N, N)]) -> Type) (a6989586621679130442 :: NonEmpty a6989586621679120263) = Transpositions'Sym2 a6989586621679130441 a6989586621679130442
type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679131518 :: TransRule s6989586621679120266) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517 :: TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679131518 :: TransRule s6989586621679120266) = Let6989586621679131520Scrutinee_6989586621679120863Sym2 vs6989586621679131517 tl6989586621679131518
type Apply (TranspositionsSym1 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) (a6989586621679131459 :: TransRule s6989586621679120266) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679131458 :: TyFun (TransRule s6989586621679120266) ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)]) -> Type) (a6989586621679131459 :: TransRule s6989586621679120266) = TranspositionsSym2 a6989586621679131458 a6989586621679131459
type Apply (Lambda_6989586621679130520Sym1 sources6989586621679130447 :: TyFun (NonEmpty a6989586621680748363) (TyFun (NonEmpty (Maybe a6989586621680748363)) (TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) -> Type) -> Type) (targets6989586621679130448 :: NonEmpty a6989586621680748363) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130520Sym1 sources6989586621679130447 :: TyFun (NonEmpty a6989586621680748363) (TyFun (NonEmpty (Maybe a6989586621680748363)) (TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) -> Type) -> Type) (targets6989586621679130448 :: NonEmpty a6989586621680748363) = (Lambda_6989586621679130520Sym2 sources6989586621679130447 targets6989586621679130448 :: TyFun (NonEmpty (Maybe a6989586621680748363)) (TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) -> Type)
type Apply (Lambda_6989586621679130512Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) (xs6989586621679130449 :: NonEmpty (Maybe k3)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130512Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) (xs6989586621679130449 :: NonEmpty (Maybe k3)) = Lambda_6989586621679130512Sym3 targets6989586621679130448 sources6989586621679130447 xs6989586621679130449
type Apply (Lambda_6989586621679130520Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (Maybe a6989586621680748363)) (TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) -> Type) (xs6989586621679130449 :: NonEmpty (Maybe a6989586621680748363)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130520Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (Maybe a6989586621680748363)) (TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type) -> Type) (xs6989586621679130449 :: NonEmpty (Maybe a6989586621680748363)) = (Lambda_6989586621679130520Sym3 targets6989586621679130448 sources6989586621679130447 xs6989586621679130449 :: TyFun (NonEmpty a6989586621679120630) (Maybe [(a6989586621679120630, N)]) -> Type)
type Apply (Lambda_6989586621679130523Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (Maybe k3)) (TyFun k4 (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) (xs6989586621679130449 :: NonEmpty (Maybe k3)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679130523Sym2 targets6989586621679130448 sources6989586621679130447 :: TyFun (NonEmpty (Maybe k3)) (TyFun k4 (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) (xs6989586621679130449 :: NonEmpty (Maybe k3)) = (Lambda_6989586621679130523Sym3 targets6989586621679130448 sources6989586621679130447 xs6989586621679130449 :: TyFun k4 (TyFun k3 (Maybe N) -> Type) -> Type)
type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679131517 :: VSpace s6989586621679120266 n6989586621679120267) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679131520Scrutinee_6989586621679120863Sym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TyFun (TransRule s6989586621679120266) (TyFun [(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679131517 :: VSpace s6989586621679120266 n6989586621679120267) = Let6989586621679131520Scrutinee_6989586621679120863Sym1 vs6989586621679131517
type Apply (TranspositionsSym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TransRule s6989586621679120266 ~> ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)])) -> Type) (a6989586621679131458 :: VSpace s6989586621679120266 n6989586621679120267) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym0 :: TyFun (VSpace s6989586621679120266 n6989586621679120267) (TransRule s6989586621679120266 ~> ([(VSpace s6989586621679120266 n6989586621679120267, IList s6989586621679120266)] ~> Maybe [(N, N)])) -> Type) (a6989586621679131458 :: VSpace s6989586621679120266 n6989586621679120267) = TranspositionsSym1 a6989586621679131458

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