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

Math.Tensor.Safe

Description

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

Synopsis

Tensor calculus

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

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

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

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

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

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

using the Einstein summation convention and the tensor product.

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

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

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

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

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

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

Generalized rank

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

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

data VSpace a b Source #

Constructors

VSpace 

Fields

Instances

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

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

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

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

show :: VSpace a b -> String #

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

Generic (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

rnf :: VSpace a b -> () #

PShow (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

POrd (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

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

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

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

PEq (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

SuppressUnusedWarnings DeltaRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings EpsilonRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings EpsilonInvRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI DeltaRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI EpsilonRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI EpsilonInvRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym1 d) #

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonRankSym1 d) #

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing MergeRSym0 #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing TailRSym0 #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing HeadRSym0 #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing SaneSym0 #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2ConRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2CovRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2ConRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2CovRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing VIdSym0 #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing VDimSym0 #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing VSpaceSym0 #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonInvRankSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (DeltaRankSym3 a6989586621679548003 a6989586621679548004 a6989586621679548005 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym3 a6989586621679547924 a6989586621679547925 a6989586621679547926 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym3 a6989586621679547901 a6989586621679547902 a6989586621679547903 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym3 a6989586621679547885 a6989586621679547886 a6989586621679547887 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym3 a6989586621679547859 a6989586621679547860 a6989586621679547861 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym3 a6989586621679547824 a6989586621679547825 a6989586621679547826 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym3 a6989586621679547798 a6989586621679547799 a6989586621679547800 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym3 a6989586621679547772 a6989586621679547773 a6989586621679547774 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym3 a6989586621679547746 a6989586621679547747 a6989586621679547748 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RemoveUntilSym1 d) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (MergeRSym1 d) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2ConRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2CovRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2ConRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2CovRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym1 d) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (VSpaceSym1 d) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelRSym1 d) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjSym2ConRankSym4 a6989586621679547924 a6989586621679547925 a6989586621679547926 a6989586621679547927 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym4 a6989586621679547901 a6989586621679547902 a6989586621679547903 a6989586621679547904 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym4 a6989586621679547885 a6989586621679547886 a6989586621679547887 a6989586621679547888 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym4 a6989586621679547859 a6989586621679547860 a6989586621679547861 a6989586621679547862 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym4 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym4 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym4 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym4 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('VSpace n1 n2) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelRSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TranspositionsSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeMultSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeCovSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeConSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym2 d1 d2) #

SuppressUnusedWarnings (CanTransposeConSym3 a6989586621679096435 a6989586621679096436 a6989586621679096437 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym3 a6989586621679096380 a6989586621679096381 a6989586621679096382 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym3 a6989586621679096353 a6989586621679096354 a6989586621679096355 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjAreaConRankSym5 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 a6989586621679547828 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym5 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 a6989586621679547802 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym5 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 a6989586621679547776 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym5 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 a6989586621679547750 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeCovSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeConSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

SuppressUnusedWarnings (Let6989586621679096334GoSym3 i6989586621679096332 r6989586621679096333 a6989586621679096335 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096703Sym4 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679547758RSym4 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547784RSym4 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547810RSym4 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547836RSym4 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547934RSym4 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 b6989586621679547932 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547911RSym4 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 b6989586621679547909 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679096703Sym5 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679547758RSym5 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 d6989586621679547756 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547784RSym5 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 d6989586621679547782 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547810RSym5 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 d6989586621679547808 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547836RSym5 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 d6989586621679547834 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679096703Sym6 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 ys6989586621679096698 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (DeltaRankSym3 a6989586621679548003 a6989586621679548004 a6989586621679548005 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679548006 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym3 a6989586621679548003 a6989586621679548004 a6989586621679548005 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679548006 :: Symbol) = DeltaRankSym4 a6989586621679548003 a6989586621679548004 a6989586621679548005 a6989586621679548006
type Apply (InjSym2ConRankSym4 a6989586621679547924 a6989586621679547925 a6989586621679547926 a6989586621679547927 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547928 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym4 a6989586621679547924 a6989586621679547925 a6989586621679547926 a6989586621679547927 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547928 :: Symbol) = InjSym2ConRankSym5 a6989586621679547924 a6989586621679547925 a6989586621679547926 a6989586621679547927 a6989586621679547928
type Apply (InjSym2CovRankSym4 a6989586621679547901 a6989586621679547902 a6989586621679547903 a6989586621679547904 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547905 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym4 a6989586621679547901 a6989586621679547902 a6989586621679547903 a6989586621679547904 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547905 :: Symbol) = InjSym2CovRankSym5 a6989586621679547901 a6989586621679547902 a6989586621679547903 a6989586621679547904 a6989586621679547905
type Apply (SurjSym2ConRankSym4 a6989586621679547885 a6989586621679547886 a6989586621679547887 a6989586621679547888 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547889 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym4 a6989586621679547885 a6989586621679547886 a6989586621679547887 a6989586621679547888 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547889 :: Symbol) = SurjSym2ConRankSym5 a6989586621679547885 a6989586621679547886 a6989586621679547887 a6989586621679547888 a6989586621679547889
type Apply (SurjSym2CovRankSym4 a6989586621679547859 a6989586621679547860 a6989586621679547861 a6989586621679547862 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547863 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym4 a6989586621679547859 a6989586621679547860 a6989586621679547861 a6989586621679547862 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547863 :: Symbol) = SurjSym2CovRankSym5 a6989586621679547859 a6989586621679547860 a6989586621679547861 a6989586621679547862 a6989586621679547863
type Apply (InjAreaConRankSym5 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 a6989586621679547828 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547829 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym5 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 a6989586621679547828 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547829 :: Symbol) = InjAreaConRankSym6 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 a6989586621679547828 a6989586621679547829
type Apply (InjAreaCovRankSym5 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 a6989586621679547802 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547803 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym5 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 a6989586621679547802 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547803 :: Symbol) = InjAreaCovRankSym6 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 a6989586621679547802 a6989586621679547803
type Apply (SurjAreaConRankSym5 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 a6989586621679547776 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547777 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym5 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 a6989586621679547776 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547777 :: Symbol) = SurjAreaConRankSym6 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 a6989586621679547776 a6989586621679547777
type Apply (SurjAreaCovRankSym5 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 a6989586621679547750 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547751 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym5 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 a6989586621679547750 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547751 :: Symbol) = SurjAreaCovRankSym6 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 a6989586621679547750 a6989586621679547751
type Apply (Let6989586621679547934RSym4 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 b6989586621679547932 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547933 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547934RSym4 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 b6989586621679547932 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547933 :: a) = Let6989586621679547934RSym5 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 b6989586621679547932 i6989586621679547933
type Apply (Let6989586621679547911RSym4 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 b6989586621679547909 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547910 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547911RSym4 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 b6989586621679547909 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547910 :: a) = Let6989586621679547911RSym5 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 b6989586621679547909 i6989586621679547910
type Apply (Let6989586621679547758RSym5 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 d6989586621679547756 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547757 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym5 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 d6989586621679547756 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547757 :: a) = Let6989586621679547758RSym6 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 d6989586621679547756 i6989586621679547757
type Apply (Let6989586621679547784RSym5 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 d6989586621679547782 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547783 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym5 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 d6989586621679547782 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547783 :: a) = Let6989586621679547784RSym6 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 d6989586621679547782 i6989586621679547783
type Apply (Let6989586621679547810RSym5 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 d6989586621679547808 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547809 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym5 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 d6989586621679547808 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547809 :: a) = Let6989586621679547810RSym6 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 d6989586621679547808 i6989586621679547809
type Apply (Let6989586621679547836RSym5 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 d6989586621679547834 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547835 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym5 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 d6989586621679547834 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547835 :: a) = Let6989586621679547836RSym6 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 d6989586621679547834 i6989586621679547835
type Apply DeltaRankSym0 (a6989586621679548003 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply DeltaRankSym0 (a6989586621679548003 :: Symbol) = DeltaRankSym1 a6989586621679548003
type Apply InjSym2ConRankSym0 (a6989586621679547924 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2ConRankSym0 (a6989586621679547924 :: Symbol) = InjSym2ConRankSym1 a6989586621679547924
type Apply InjSym2CovRankSym0 (a6989586621679547901 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2CovRankSym0 (a6989586621679547901 :: Symbol) = InjSym2CovRankSym1 a6989586621679547901
type Apply SurjSym2ConRankSym0 (a6989586621679547885 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2ConRankSym0 (a6989586621679547885 :: Symbol) = SurjSym2ConRankSym1 a6989586621679547885
type Apply SurjSym2CovRankSym0 (a6989586621679547859 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2CovRankSym0 (a6989586621679547859 :: Symbol) = SurjSym2CovRankSym1 a6989586621679547859
type Apply EpsilonRankSym0 (a6989586621679547982 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonRankSym0 (a6989586621679547982 :: Symbol) = EpsilonRankSym1 a6989586621679547982
type Apply EpsilonInvRankSym0 (a6989586621679547962 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonInvRankSym0 (a6989586621679547962 :: Symbol) = EpsilonInvRankSym1 a6989586621679547962
type Apply InjAreaConRankSym0 (a6989586621679547824 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaConRankSym0 (a6989586621679547824 :: Symbol) = InjAreaConRankSym1 a6989586621679547824
type Apply InjAreaCovRankSym0 (a6989586621679547798 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaCovRankSym0 (a6989586621679547798 :: Symbol) = InjAreaCovRankSym1 a6989586621679547798
type Apply SurjAreaConRankSym0 (a6989586621679547772 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjAreaConRankSym0 (a6989586621679547772 :: Symbol) = SurjAreaConRankSym1 a6989586621679547772
type Apply SurjAreaCovRankSym0 (a6989586621679547746 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym1 a6989586621679548003 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679548004 :: Nat) = DeltaRankSym2 a6989586621679548003 a6989586621679548004
type Apply (InjSym2ConRankSym1 a6989586621679547924 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547925 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym1 a6989586621679547924 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547925 :: Nat) = InjSym2ConRankSym2 a6989586621679547924 a6989586621679547925
type Apply (InjSym2CovRankSym1 a6989586621679547901 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547902 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym1 a6989586621679547901 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547902 :: Nat) = InjSym2CovRankSym2 a6989586621679547901 a6989586621679547902
type Apply (SurjSym2ConRankSym1 a6989586621679547885 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547886 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym1 a6989586621679547885 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547886 :: Nat) = SurjSym2ConRankSym2 a6989586621679547885 a6989586621679547886
type Apply (SurjSym2CovRankSym1 a6989586621679547859 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547860 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym1 a6989586621679547859 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547860 :: Nat) = SurjSym2CovRankSym2 a6989586621679547859 a6989586621679547860
type Apply (EpsilonRankSym1 a6989586621679547982 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547983 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym1 a6989586621679547982 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547983 :: Nat) = EpsilonRankSym2 a6989586621679547982 a6989586621679547983
type Apply (EpsilonInvRankSym1 a6989586621679547962 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547963 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym1 a6989586621679547962 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547963 :: Nat) = EpsilonInvRankSym2 a6989586621679547962 a6989586621679547963
type Apply (InjAreaConRankSym1 a6989586621679547824 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547825 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym1 a6989586621679547824 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547825 :: Symbol) = InjAreaConRankSym2 a6989586621679547824 a6989586621679547825
type Apply (InjAreaCovRankSym1 a6989586621679547798 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547799 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym1 a6989586621679547798 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547799 :: Symbol) = InjAreaCovRankSym2 a6989586621679547798 a6989586621679547799
type Apply (SurjAreaConRankSym1 a6989586621679547772 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547773 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym1 a6989586621679547772 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547773 :: Symbol) = SurjAreaConRankSym2 a6989586621679547772 a6989586621679547773
type Apply (SurjAreaCovRankSym1 a6989586621679547746 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547747 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym1 a6989586621679547746 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547747 :: Symbol) = SurjAreaCovRankSym2 a6989586621679547746 a6989586621679547747
type Apply (ShowsPrec_6989586621679100036Sym0 :: TyFun Nat (VSpace a b ~> (Symbol ~> Symbol)) -> Type) (a6989586621679100044 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679100036Sym0 :: TyFun Nat (VSpace a b ~> (Symbol ~> Symbol)) -> Type) (a6989586621679100044 :: Nat) = ShowsPrec_6989586621679100036Sym1 a6989586621679100044 :: TyFun (VSpace a b) (Symbol ~> Symbol) -> Type
type Apply (DeltaRankSym2 a6989586621679548003 a6989586621679548004 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679548005 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym2 a6989586621679548003 a6989586621679548004 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679548005 :: Symbol) = DeltaRankSym3 a6989586621679548003 a6989586621679548004 a6989586621679548005
type Apply (InjSym2ConRankSym2 a6989586621679547924 a6989586621679547925 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547926 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym2 a6989586621679547924 a6989586621679547925 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547926 :: Symbol) = InjSym2ConRankSym3 a6989586621679547924 a6989586621679547925 a6989586621679547926
type Apply (InjSym2CovRankSym2 a6989586621679547901 a6989586621679547902 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547903 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym2 a6989586621679547901 a6989586621679547902 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547903 :: Symbol) = InjSym2CovRankSym3 a6989586621679547901 a6989586621679547902 a6989586621679547903
type Apply (SurjSym2ConRankSym2 a6989586621679547885 a6989586621679547886 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547887 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym2 a6989586621679547885 a6989586621679547886 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547887 :: Symbol) = SurjSym2ConRankSym3 a6989586621679547885 a6989586621679547886 a6989586621679547887
type Apply (SurjSym2CovRankSym2 a6989586621679547859 a6989586621679547860 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547861 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym2 a6989586621679547859 a6989586621679547860 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547861 :: Symbol) = SurjSym2CovRankSym3 a6989586621679547859 a6989586621679547860 a6989586621679547861
type Apply (InjAreaConRankSym2 a6989586621679547824 a6989586621679547825 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547826 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym2 a6989586621679547824 a6989586621679547825 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547826 :: Symbol) = InjAreaConRankSym3 a6989586621679547824 a6989586621679547825 a6989586621679547826
type Apply (InjAreaCovRankSym2 a6989586621679547798 a6989586621679547799 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547800 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym2 a6989586621679547798 a6989586621679547799 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547800 :: Symbol) = InjAreaCovRankSym3 a6989586621679547798 a6989586621679547799 a6989586621679547800
type Apply (SurjAreaConRankSym2 a6989586621679547772 a6989586621679547773 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547774 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym2 a6989586621679547772 a6989586621679547773 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547774 :: Symbol) = SurjAreaConRankSym3 a6989586621679547772 a6989586621679547773 a6989586621679547774
type Apply (SurjAreaCovRankSym2 a6989586621679547746 a6989586621679547747 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547748 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym2 a6989586621679547746 a6989586621679547747 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547748 :: Symbol) = SurjAreaCovRankSym3 a6989586621679547746 a6989586621679547747 a6989586621679547748
type Apply (VSpaceSym0 :: TyFun a (b ~> VSpace a b) -> Type) (a6989586621679095876 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547752 :: k1) = Let6989586621679547758RSym1 vid6989586621679547752 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547784RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547778 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547778 :: k1) = Let6989586621679547784RSym1 vid6989586621679547778 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547810RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547804 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547804 :: k1) = Let6989586621679547810RSym1 vid6989586621679547804 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547836RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547830 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547830 :: k1) = Let6989586621679547836RSym1 vid6989586621679547830 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547934RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547929 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547934RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547929 :: k1) = Let6989586621679547934RSym1 vid6989586621679547929 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547911RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547906 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547911RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547906 :: k1) = Let6989586621679547911RSym1 vid6989586621679547906 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547934RSym1 vid6989586621679547929 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679547930 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547934RSym1 vid6989586621679547929 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679547930 :: Nat) = Let6989586621679547934RSym2 vid6989586621679547929 vdim6989586621679547930 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (Let6989586621679547911RSym1 vid6989586621679547906 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679547907 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547911RSym1 vid6989586621679547906 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679547907 :: Nat) = Let6989586621679547911RSym2 vid6989586621679547906 vdim6989586621679547907 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (InjSym2ConRankSym3 a6989586621679547924 a6989586621679547925 a6989586621679547926 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547927 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym3 a6989586621679547924 a6989586621679547925 a6989586621679547926 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547927 :: Symbol) = InjSym2ConRankSym4 a6989586621679547924 a6989586621679547925 a6989586621679547926 a6989586621679547927
type Apply (InjSym2CovRankSym3 a6989586621679547901 a6989586621679547902 a6989586621679547903 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547904 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym3 a6989586621679547901 a6989586621679547902 a6989586621679547903 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547904 :: Symbol) = InjSym2CovRankSym4 a6989586621679547901 a6989586621679547902 a6989586621679547903 a6989586621679547904
type Apply (SurjSym2ConRankSym3 a6989586621679547885 a6989586621679547886 a6989586621679547887 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547888 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym3 a6989586621679547885 a6989586621679547886 a6989586621679547887 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547888 :: Symbol) = SurjSym2ConRankSym4 a6989586621679547885 a6989586621679547886 a6989586621679547887 a6989586621679547888
type Apply (SurjSym2CovRankSym3 a6989586621679547859 a6989586621679547860 a6989586621679547861 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547862 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym3 a6989586621679547859 a6989586621679547860 a6989586621679547861 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547862 :: Symbol) = SurjSym2CovRankSym4 a6989586621679547859 a6989586621679547860 a6989586621679547861 a6989586621679547862
type Apply (InjAreaConRankSym3 a6989586621679547824 a6989586621679547825 a6989586621679547826 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547827 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym3 a6989586621679547824 a6989586621679547825 a6989586621679547826 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547827 :: Symbol) = InjAreaConRankSym4 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827
type Apply (InjAreaCovRankSym3 a6989586621679547798 a6989586621679547799 a6989586621679547800 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547801 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym3 a6989586621679547798 a6989586621679547799 a6989586621679547800 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547801 :: Symbol) = InjAreaCovRankSym4 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801
type Apply (SurjAreaConRankSym3 a6989586621679547772 a6989586621679547773 a6989586621679547774 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547775 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym3 a6989586621679547772 a6989586621679547773 a6989586621679547774 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547775 :: Symbol) = SurjAreaConRankSym4 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775
type Apply (SurjAreaCovRankSym3 a6989586621679547746 a6989586621679547747 a6989586621679547748 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547749 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym3 a6989586621679547746 a6989586621679547747 a6989586621679547748 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547749 :: Symbol) = SurjAreaCovRankSym4 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749
type Apply (VSpaceSym1 a6989586621679095876 :: TyFun b (VSpace a b) -> Type) (a6989586621679095877 :: b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (VSpaceSym1 a6989586621679095876 :: TyFun b (VSpace a b) -> Type) (a6989586621679095877 :: b) = VSpaceSym2 a6989586621679095876 a6989586621679095877
type Apply (CanTransposeConSym1 a6989586621679096435 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096436 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym1 a6989586621679096435 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096436 :: s) = CanTransposeConSym2 a6989586621679096435 a6989586621679096436
type Apply (CanTransposeCovSym1 a6989586621679096380 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096381 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym1 a6989586621679096380 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096381 :: s) = CanTransposeCovSym2 a6989586621679096380 a6989586621679096381
type Apply (Let6989586621679547758RSym1 vid6989586621679547752 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547753 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym1 vid6989586621679547752 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547753 :: a) = Let6989586621679547758RSym2 vid6989586621679547752 a6989586621679547753
type Apply (Let6989586621679547784RSym1 vid6989586621679547778 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547779 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym1 vid6989586621679547778 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547779 :: a) = Let6989586621679547784RSym2 vid6989586621679547778 a6989586621679547779
type Apply (Let6989586621679547810RSym1 vid6989586621679547804 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547805 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym1 vid6989586621679547804 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547805 :: a) = Let6989586621679547810RSym2 vid6989586621679547804 a6989586621679547805
type Apply (Let6989586621679547836RSym1 vid6989586621679547830 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547831 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym1 vid6989586621679547830 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547831 :: a) = Let6989586621679547836RSym2 vid6989586621679547830 a6989586621679547831
type Apply (InjAreaConRankSym4 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547828 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym4 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547828 :: Symbol) = InjAreaConRankSym5 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 a6989586621679547828
type Apply (InjAreaCovRankSym4 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547802 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym4 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547802 :: Symbol) = InjAreaCovRankSym5 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 a6989586621679547802
type Apply (SurjAreaConRankSym4 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547776 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym4 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547776 :: Symbol) = SurjAreaConRankSym5 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 a6989586621679547776
type Apply (SurjAreaCovRankSym4 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547750 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym4 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547750 :: Symbol) = SurjAreaCovRankSym5 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 a6989586621679547750
type Apply (CanTransposeConSym2 a6989586621679096435 a6989586621679096436 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096437 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym2 a6989586621679096435 a6989586621679096436 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096437 :: s) = CanTransposeConSym3 a6989586621679096435 a6989586621679096436 a6989586621679096437
type Apply (CanTransposeCovSym2 a6989586621679096380 a6989586621679096381 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096382 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym2 a6989586621679096380 a6989586621679096381 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096382 :: s) = CanTransposeCovSym3 a6989586621679096380 a6989586621679096381 a6989586621679096382
type Apply (Let6989586621679096334GoSym1 i6989586621679096332 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679096333 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096334GoSym1 i6989586621679096332 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679096333 :: k) = Let6989586621679096334GoSym2 i6989586621679096332 r6989586621679096333 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type
type Apply (Let6989586621679547758RSym2 vid6989586621679547752 a6989586621679547753 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547754 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym2 vid6989586621679547752 a6989586621679547753 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547754 :: a) = Let6989586621679547758RSym3 vid6989586621679547752 a6989586621679547753 b6989586621679547754
type Apply (Let6989586621679547784RSym2 vid6989586621679547778 a6989586621679547779 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547780 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym2 vid6989586621679547778 a6989586621679547779 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547780 :: a) = Let6989586621679547784RSym3 vid6989586621679547778 a6989586621679547779 b6989586621679547780
type Apply (Let6989586621679547810RSym2 vid6989586621679547804 a6989586621679547805 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547806 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym2 vid6989586621679547804 a6989586621679547805 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547806 :: a) = Let6989586621679547810RSym3 vid6989586621679547804 a6989586621679547805 b6989586621679547806
type Apply (Let6989586621679547836RSym2 vid6989586621679547830 a6989586621679547831 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547832 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym2 vid6989586621679547830 a6989586621679547831 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547832 :: a) = Let6989586621679547836RSym3 vid6989586621679547830 a6989586621679547831 b6989586621679547832
type Apply (Let6989586621679547934RSym2 vid6989586621679547929 vdim6989586621679547930 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679547931 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547934RSym2 vid6989586621679547929 vdim6989586621679547930 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679547931 :: a) = Let6989586621679547934RSym3 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931
type Apply (Let6989586621679547911RSym2 vid6989586621679547906 vdim6989586621679547907 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679547908 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547911RSym2 vid6989586621679547906 vdim6989586621679547907 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679547908 :: a) = Let6989586621679547911RSym3 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908
type Apply (Let6989586621679547758RSym3 vid6989586621679547752 a6989586621679547753 b6989586621679547754 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547755 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym3 vid6989586621679547752 a6989586621679547753 b6989586621679547754 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547755 :: a) = Let6989586621679547758RSym4 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755
type Apply (Let6989586621679547784RSym3 vid6989586621679547778 a6989586621679547779 b6989586621679547780 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547781 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym3 vid6989586621679547778 a6989586621679547779 b6989586621679547780 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547781 :: a) = Let6989586621679547784RSym4 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781
type Apply (Let6989586621679547810RSym3 vid6989586621679547804 a6989586621679547805 b6989586621679547806 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547807 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym3 vid6989586621679547804 a6989586621679547805 b6989586621679547806 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547807 :: a) = Let6989586621679547810RSym4 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807
type Apply (Let6989586621679547836RSym3 vid6989586621679547830 a6989586621679547831 b6989586621679547832 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547833 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym3 vid6989586621679547830 a6989586621679547831 b6989586621679547832 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547833 :: a) = Let6989586621679547836RSym4 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833
type Apply (Let6989586621679547934RSym3 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679547932 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547934RSym3 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679547932 :: a) = Let6989586621679547934RSym4 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 b6989586621679547932
type Apply (Let6989586621679547911RSym3 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679547909 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547911RSym3 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679547909 :: a) = Let6989586621679547911RSym4 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 b6989586621679547909
type Apply (Let6989586621679547758RSym4 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547756 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym4 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547756 :: a) = Let6989586621679547758RSym5 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 d6989586621679547756
type Apply (Let6989586621679547784RSym4 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547782 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym4 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547782 :: a) = Let6989586621679547784RSym5 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 d6989586621679547782
type Apply (Let6989586621679547810RSym4 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547808 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym4 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547808 :: a) = Let6989586621679547810RSym5 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 d6989586621679547808
type Apply (Let6989586621679547836RSym4 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547834 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym4 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547834 :: a) = Let6989586621679547836RSym5 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 d6989586621679547834
type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679096795 :: [(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) (a6989586621679096795 :: [(VSpace s n, IList s)]) = LengthRSym1 a6989586621679096795
type Apply (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) (a6989586621679096786 :: [(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) (a6989586621679096786 :: [(VSpace a b, IList a)]) = SaneSym1 a6989586621679096786
type Apply (CanTransposeMultSym2 a6989586621679096305 a6989586621679096306 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096307 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym2 a6989586621679096305 a6989586621679096306 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096307 :: [(VSpace s n, IList s)]) = CanTransposeMultSym3 a6989586621679096305 a6989586621679096306 a6989586621679096307
type Apply (CanTransposeConSym3 a6989586621679096435 a6989586621679096436 a6989586621679096437 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096438 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym3 a6989586621679096435 a6989586621679096436 a6989586621679096437 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096438 :: [(VSpace s n, IList s)]) = CanTransposeConSym4 a6989586621679096435 a6989586621679096436 a6989586621679096437 a6989586621679096438
type Apply (CanTransposeCovSym3 a6989586621679096380 a6989586621679096381 a6989586621679096382 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096383 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym3 a6989586621679096380 a6989586621679096381 a6989586621679096382 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096383 :: [(VSpace s n, IList s)]) = CanTransposeCovSym4 a6989586621679096380 a6989586621679096381 a6989586621679096382 a6989586621679096383
type Apply (CanTransposeSym3 a6989586621679096353 a6989586621679096354 a6989586621679096355 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096356 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym3 a6989586621679096353 a6989586621679096354 a6989586621679096355 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096356 :: [(VSpace s n, IList s)]) = CanTransposeSym4 a6989586621679096353 a6989586621679096354 a6989586621679096355 a6989586621679096356
type Rep1 (VSpace a :: Type -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep1 (VSpace a :: Type -> Type) = D1 ('MetaData "VSpace" "Math.Tensor.Safe.TH" "safe-tensor-0.2.1.1-HV6XtoU04VwKCpzbN3KLoQ" 'False) (C1 ('MetaCons "VSpace" 'PrefixI 'True) (S1 ('MetaSel ('Just "vId") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a) :*: S1 ('MetaSel ('Just "vDim") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Apply (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096593 :: [(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) (a6989586621679096593 :: [(VSpace s n, IList s)]) = ContractRSym1 a6989586621679096593
type Apply (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096714 :: [(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) (a6989586621679096714 :: [(VSpace s n, IList s)]) = TailRSym1 a6989586621679096714
type Apply (EpsilonRankSym2 a6989586621679547982 a6989586621679547983 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547984 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym2 a6989586621679547982 a6989586621679547983 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547984 :: NonEmpty Symbol) = EpsilonRankSym3 a6989586621679547982 a6989586621679547983 a6989586621679547984
type Apply (EpsilonInvRankSym2 a6989586621679547962 a6989586621679547963 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547964 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym2 a6989586621679547962 a6989586621679547963 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547964 :: NonEmpty Symbol) = EpsilonInvRankSym3 a6989586621679547962 a6989586621679547963 a6989586621679547964
type Apply (MergeRSym1 a6989586621679096689 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096690 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym1 a6989586621679096689 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096690 :: [(VSpace s n, IList s)]) = MergeRSym2 a6989586621679096689 a6989586621679096690
type Apply (RemoveUntilSym1 a6989586621679096330 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096331 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym1 a6989586621679096330 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096331 :: [(VSpace s n, IList s)]) = RemoveUntilSym2 a6989586621679096330 a6989586621679096331
type Apply (RelabelRSym2 a6989586621679096054 a6989586621679096055 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096056 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym2 a6989586621679096054 a6989586621679096055 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096056 :: [(VSpace s n, IList s)]) = RelabelRSym3 a6989586621679096054 a6989586621679096055 a6989586621679096056
type Apply (TranspositionsSym2 a6989586621679096259 a6989586621679096260 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679096261 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679096259 a6989586621679096260 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679096261 :: [(VSpace s n, IList s)]) = TranspositionsSym3 a6989586621679096259 a6989586621679096260 a6989586621679096261
type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym2 vs6989586621679096308 tl6989586621679096309 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679096310 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym2 vs6989586621679096308 tl6989586621679096309 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679096310 :: [(VSpace s n, IList s)]) = Let6989586621679096311Scrutinee_6989586621679091469Sym3 vs6989586621679096308 tl6989586621679096309 r6989586621679096310
type Apply (Let6989586621679096334GoSym3 i6989586621679096332 r6989586621679096333 a6989586621679096335 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096336 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096334GoSym3 i6989586621679096332 r6989586621679096333 a6989586621679096335 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096336 :: [(VSpace s n, IList s)]) = Let6989586621679096334GoSym4 i6989586621679096332 r6989586621679096333 a6989586621679096335 a6989586621679096336
type Apply (Lambda_6989586621679096703Sym6 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 ys6989586621679096698 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679096705 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym6 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 ys6989586621679096698 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679096705 :: IList s) = Lambda_6989586621679096703Sym7 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 ys6989586621679096698 xl'6989586621679096705
type Apply (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096689 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096689 :: [(VSpace s n, IList s)]) = MergeRSym1 a6989586621679096689
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679096769 :: [(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) (a6989586621679096769 :: [(VSpace s n, IList s)]) = HeadRSym1 a6989586621679096769
type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679096330 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679096353 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096354 :: Ix s) = CanTransposeSym2 a6989586621679096353 a6989586621679096354
type Apply (Let6989586621679096334GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679096332 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096334GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679096332 :: Ix s) = Let6989586621679096334GoSym1 i6989586621679096332 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type
type Apply (Lambda_6989586621679096703Sym1 xv6989586621679096693 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))))) -> Type) (xl6989586621679096694 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym1 xv6989586621679096693 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))))) -> Type) (xl6989586621679096694 :: IList s) = Lambda_6989586621679096703Sym2 xv6989586621679096693 xl6989586621679096694
type Apply (TranspositionsSym1 a6989586621679096259 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679096260 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679096259 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679096260 :: TransRule s) = TranspositionsSym2 a6989586621679096259 a6989586621679096260
type Apply (CanTransposeMultSym1 a6989586621679096305 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096306 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679096305 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096306 :: TransRule s) = CanTransposeMultSym2 a6989586621679096305 a6989586621679096306
type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679096309 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679096309 :: TransRule s) = Let6989586621679096311Scrutinee_6989586621679091469Sym2 vs6989586621679096308 tl6989586621679096309
type Apply (RelabelRSym1 a6989586621679096054 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096055 :: NonEmpty (s, s)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym1 a6989586621679096054 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096055 :: NonEmpty (s, s)) = RelabelRSym2 a6989586621679096054 a6989586621679096055
type Apply (Lambda_6989586621679096703Sym2 xv6989586621679096693 xl6989586621679096694 :: TyFun [(VSpace s n, IList s)] (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))) -> Type) (xs6989586621679096695 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym2 xv6989586621679096693 xl6989586621679096694 :: TyFun [(VSpace s n, IList s)] (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))) -> Type) (xs6989586621679096695 :: [(VSpace s n, IList s)]) = Lambda_6989586621679096703Sym3 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695
type Apply (CanTransposeSym2 a6989586621679096353 a6989586621679096354 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096355 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679096353 a6989586621679096354 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096355 :: Ix s) = CanTransposeSym3 a6989586621679096353 a6989586621679096354 a6989586621679096355
type Apply (Let6989586621679096334GoSym2 i6989586621679096332 r6989586621679096333 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679096335 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096334GoSym2 i6989586621679096332 r6989586621679096333 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679096335 :: Ix s) = Let6989586621679096334GoSym3 i6989586621679096332 r6989586621679096333 a6989586621679096335 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (Lambda_6989586621679096703Sym4 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679096697 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym4 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679096697 :: IList s) = Lambda_6989586621679096703Sym5 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697
type Apply (Lambda_6989586621679096703Sym5 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679096698 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym5 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679096698 :: [(VSpace s n, IList s)]) = Lambda_6989586621679096703Sym6 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 ys6989586621679096698
type Rep (VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: VSpace a b) = Apply (Show__6989586621680289856Sym0 :: 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_6989586621680289864Sym0 :: 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_6989586621679392900Sym0 :: 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_6989586621679392884Sym0 :: 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_6989586621679392868Sym0 :: 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_6989586621679392852Sym0 :: 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_6989586621679392836Sym0 :: 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_6989586621679392820Sym0 :: 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_6989586621679100053Sym0 :: 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_6989586621679100174 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_6989586621679100036Sym0 :: TyFun Nat (VSpace a1 b ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (VDimSym0 :: TyFun (VSpace a b) b -> Type) (a6989586621679096871 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (VIdSym0 :: TyFun (VSpace a b) a -> Type) (a6989586621679096875 :: VSpace a b) = VIdSym1 a6989586621679096875
type Apply (Compare_6989586621679100053Sym1 a6989586621679100058 :: TyFun (VSpace a b) Ordering -> Type) (a6989586621679100059 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679100053Sym1 a6989586621679100058 :: TyFun (VSpace a b) Ordering -> Type) (a6989586621679100059 :: VSpace a b) = Compare_6989586621679100053Sym2 a6989586621679100058 a6989586621679100059
type Apply (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679096435 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym0 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))))) -> Type) (xv6989586621679096693 :: VSpace s n) = Lambda_6989586621679096703Sym1 xv6989586621679096693
type Apply (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) (a6989586621679096054 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679096308 :: VSpace s n) = Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308
type Apply (Compare_6989586621679100053Sym0 :: TyFun (VSpace a b) (VSpace a b ~> Ordering) -> Type) (a6989586621679100058 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679100053Sym0 :: TyFun (VSpace a b) (VSpace a b ~> Ordering) -> Type) (a6989586621679100058 :: VSpace a b) = Compare_6989586621679100053Sym1 a6989586621679100058
type Apply (ShowsPrec_6989586621679100036Sym1 a6989586621679100044 :: TyFun (VSpace a b) (Symbol ~> Symbol) -> Type) (a6989586621679100045 :: VSpace a b) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679100036Sym1 a6989586621679100044 :: TyFun (VSpace a b) (Symbol ~> Symbol) -> Type) (a6989586621679100045 :: VSpace a b) = ShowsPrec_6989586621679100036Sym2 a6989586621679100044 a6989586621679100045
type Apply (Lambda_6989586621679096703Sym3 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679096696 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym3 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679096696 :: VSpace s n) = Lambda_6989586621679096703Sym4 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696

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

data IList a Source #

Constructors

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

Instances

Instances details
NFData1 IList Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

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

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

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

show :: IList a -> String #

showList :: [IList a] -> ShowS #

Generic (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

rnf :: IList a -> () #

PShow (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

POrd (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

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

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

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

PEq (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

Generic1 IList Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Rep1 IList :: k -> Type #

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('Cov n) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('Con n) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('ConCov n1 n2) #

SuppressUnusedWarnings DeltaRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings EpsilonRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings EpsilonInvRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings InjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings SurjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI DeltaRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjSym2ConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjSym2CovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI EpsilonRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI EpsilonInvRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI InjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjAreaConRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SingI SurjAreaCovRankSym0 Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym1 d) #

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonRankSym1 d) #

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ConSym0 #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing CovSym0 #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ConCovSym0 #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679100129Sym1 a6989586621679100134 :: TyFun (IList a) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing MergeRSym0 #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing TailRSym0 #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing HeadRSym0 #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing SaneSym0 #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2ConRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2CovRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2ConRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2CovRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelIL'Sym1 d) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelILSym1 d) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (PrepICovSym1 d) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (PrepIConSym1 d) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (MergeILSym1 d) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonRankSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (EpsilonInvRankSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (ConCovSym1 d) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (DeltaRankSym3 a6989586621679548003 a6989586621679548004 a6989586621679548005 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2ConRankSym3 a6989586621679547924 a6989586621679547925 a6989586621679547926 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym3 a6989586621679547901 a6989586621679547902 a6989586621679547903 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym3 a6989586621679547885 a6989586621679547886 a6989586621679547887 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym3 a6989586621679547859 a6989586621679547860 a6989586621679547861 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym3 a6989586621679547824 a6989586621679547825 a6989586621679547826 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym3 a6989586621679547798 a6989586621679547799 a6989586621679547800 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym3 a6989586621679547772 a6989586621679547773 a6989586621679547774 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym3 a6989586621679547746 a6989586621679547747 a6989586621679547748 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096553Scrutinee_6989586621679091399Sym2 y'6989586621679096551 ys'6989586621679096552 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096542Scrutinee_6989586621679091409Sym2 x'6989586621679096540 xs'6989586621679096541 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RemoveUntilSym1 d) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (MergeRSym1 d) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (DeltaRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2ConRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjSym2CovRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2ConRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjSym2CovRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaConRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (InjAreaCovRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaConRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

sing :: Sing (SurjAreaCovRankSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym1 d) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelRSym1 d) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096553Scrutinee_6989586621679091399Sym3 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096542Scrutinee_6989586621679091409Sym3 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjSym2ConRankSym4 a6989586621679547924 a6989586621679547925 a6989586621679547926 a6989586621679547927 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjSym2CovRankSym4 a6989586621679547901 a6989586621679547902 a6989586621679547903 a6989586621679547904 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2ConRankSym4 a6989586621679547885 a6989586621679547886 a6989586621679547887 a6989586621679547888 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjSym2CovRankSym4 a6989586621679547859 a6989586621679547860 a6989586621679547861 a6989586621679547862 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaConRankSym4 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym4 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym4 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym4 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (RelabelRSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TranspositionsSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeMultSym2 d1 d2) #

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeCovSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeConSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym2 d1 d2) #

SuppressUnusedWarnings (CanTransposeConSym3 a6989586621679096435 a6989586621679096436 a6989586621679096437 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeCovSym3 a6989586621679096380 a6989586621679096381 a6989586621679096382 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (CanTransposeSym3 a6989586621679096353 a6989586621679096354 a6989586621679096355 :: TyFun [(VSpace s n, IList s)] Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (InjAreaConRankSym5 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 a6989586621679547828 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (InjAreaCovRankSym5 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 a6989586621679547802 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaConRankSym5 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 a6989586621679547776 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (SurjAreaCovRankSym5 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 a6989586621679547750 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096007Sym2 rl6989586621679096005 is6989586621679096006 :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679095996Sym2 rl6989586621679095994 is6989586621679095995 :: TyFun (IList a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096653Sym2 xs6989586621679096650 ys6989586621679096651 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096660Sym2 xs6989586621679096657 ys6989586621679096658 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096678Sym2 ys6989586621679096675 xs6989586621679096676 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096718L'Sym2 v6989586621679096715 l6989586621679096716 :: TyFun k2 (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096597Scrutinee_6989586621679091391Sym2 v6989586621679096594 is6989586621679096595 :: TyFun k2 (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096553Scrutinee_6989586621679091399Sym4 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 xs6989586621679096516 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096542Scrutinee_6989586621679091409Sym4 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 xs6989586621679096516 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096642Sym2 xs6989586621679096638 ys6989586621679096639 :: TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679096019Sym3 rl6989586621679096016 is6989586621679096017 js6989586621679096018 :: TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096667Sym2 xs6989586621679096664 xs'6989586621679096665 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeCovSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeConSym3 d1 d2 d3) #

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

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

Defined in Math.Tensor.Basic.TH

Methods

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

SuppressUnusedWarnings (Let6989586621679096334GoSym3 i6989586621679096332 r6989586621679096333 a6989586621679096335 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096553Scrutinee_6989586621679091399Sym5 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 xs6989586621679096516 y6989586621679096517 :: TyFun [a] (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096542Scrutinee_6989586621679091409Sym5 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 xs6989586621679096516 y6989586621679096517 :: TyFun [a] (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096703Sym4 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096025L'Sym2 js'6989586621679096024 is'6989586621679096021 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096022Sym2 is'6989586621679096021 rl6989586621679096016 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679547758RSym4 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547784RSym4 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547810RSym4 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547836RSym4 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547934RSym4 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 b6989586621679547932 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547911RSym4 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 b6989586621679547909 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679096653Sym3 xs6989586621679096650 ys6989586621679096651 xs'6989586621679096652 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096660Sym3 xs6989586621679096657 ys6989586621679096658 ys'6989586621679096659 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096667Sym3 xs6989586621679096664 xs'6989586621679096665 ys6989586621679096666 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096678Sym3 ys6989586621679096675 xs6989586621679096676 ys'6989586621679096677 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096642Sym3 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096703Sym5 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096025L'Sym3 js'6989586621679096024 is'6989586621679096021 rl6989586621679096016 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096645Sym2 xs''6989586621679096644 xs6989586621679096638 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096022Sym3 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679547758RSym5 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 d6989586621679547756 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547784RSym5 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 d6989586621679547782 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547810RSym5 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 d6989586621679547808 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Let6989586621679547836RSym5 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 d6989586621679547834 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

SuppressUnusedWarnings (Lambda_6989586621679096642Sym4 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 ys'6989586621679096641 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096703Sym6 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 ys6989586621679096698 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096025L'Sym4 js'6989586621679096024 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 :: TyFun k3 (IList a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096645Sym3 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096022Sym4 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 js6989586621679096018 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096645Sym4 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096645Sym5 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 ys'6989586621679096641 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (DeltaRankSym3 a6989586621679548003 a6989586621679548004 a6989586621679548005 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679548006 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym3 a6989586621679548003 a6989586621679548004 a6989586621679548005 :: TyFun Symbol [(VSpace Symbol Nat, IList Symbol)] -> Type) (a6989586621679548006 :: Symbol) = DeltaRankSym4 a6989586621679548003 a6989586621679548004 a6989586621679548005 a6989586621679548006
type Apply (InjSym2ConRankSym4 a6989586621679547924 a6989586621679547925 a6989586621679547926 a6989586621679547927 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547928 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym4 a6989586621679547924 a6989586621679547925 a6989586621679547926 a6989586621679547927 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547928 :: Symbol) = InjSym2ConRankSym5 a6989586621679547924 a6989586621679547925 a6989586621679547926 a6989586621679547927 a6989586621679547928
type Apply (InjSym2CovRankSym4 a6989586621679547901 a6989586621679547902 a6989586621679547903 a6989586621679547904 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547905 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym4 a6989586621679547901 a6989586621679547902 a6989586621679547903 a6989586621679547904 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547905 :: Symbol) = InjSym2CovRankSym5 a6989586621679547901 a6989586621679547902 a6989586621679547903 a6989586621679547904 a6989586621679547905
type Apply (SurjSym2ConRankSym4 a6989586621679547885 a6989586621679547886 a6989586621679547887 a6989586621679547888 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547889 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym4 a6989586621679547885 a6989586621679547886 a6989586621679547887 a6989586621679547888 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547889 :: Symbol) = SurjSym2ConRankSym5 a6989586621679547885 a6989586621679547886 a6989586621679547887 a6989586621679547888 a6989586621679547889
type Apply (SurjSym2CovRankSym4 a6989586621679547859 a6989586621679547860 a6989586621679547861 a6989586621679547862 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547863 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym4 a6989586621679547859 a6989586621679547860 a6989586621679547861 a6989586621679547862 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547863 :: Symbol) = SurjSym2CovRankSym5 a6989586621679547859 a6989586621679547860 a6989586621679547861 a6989586621679547862 a6989586621679547863
type Apply (InjAreaConRankSym5 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 a6989586621679547828 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547829 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym5 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 a6989586621679547828 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547829 :: Symbol) = InjAreaConRankSym6 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 a6989586621679547828 a6989586621679547829
type Apply (InjAreaCovRankSym5 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 a6989586621679547802 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547803 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym5 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 a6989586621679547802 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547803 :: Symbol) = InjAreaCovRankSym6 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 a6989586621679547802 a6989586621679547803
type Apply (SurjAreaConRankSym5 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 a6989586621679547776 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547777 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym5 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 a6989586621679547776 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547777 :: Symbol) = SurjAreaConRankSym6 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 a6989586621679547776 a6989586621679547777
type Apply (SurjAreaCovRankSym5 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 a6989586621679547750 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547751 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym5 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 a6989586621679547750 :: TyFun Symbol (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547751 :: Symbol) = SurjAreaCovRankSym6 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 a6989586621679547750 a6989586621679547751
type Apply (Let6989586621679096718L'Sym2 v6989586621679096715 l6989586621679096716 :: TyFun k2 (Maybe (IList a)) -> Type) (ls6989586621679096717 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096718L'Sym2 v6989586621679096715 l6989586621679096716 :: TyFun k2 (Maybe (IList a)) -> Type) (ls6989586621679096717 :: k2) = Let6989586621679096718L'Sym3 v6989586621679096715 l6989586621679096716 ls6989586621679096717
type Apply (Let6989586621679096597Scrutinee_6989586621679091391Sym2 v6989586621679096594 is6989586621679096595 :: TyFun k2 (Maybe (IList a)) -> Type) (xs6989586621679096596 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096597Scrutinee_6989586621679091391Sym2 v6989586621679096594 is6989586621679096595 :: TyFun k2 (Maybe (IList a)) -> Type) (xs6989586621679096596 :: k2) = Let6989586621679096597Scrutinee_6989586621679091391Sym3 v6989586621679096594 is6989586621679096595 xs6989586621679096596
type Apply (Let6989586621679547934RSym4 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 b6989586621679547932 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547933 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547934RSym4 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 b6989586621679547932 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547933 :: a) = Let6989586621679547934RSym5 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 b6989586621679547932 i6989586621679547933
type Apply (Let6989586621679547911RSym4 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 b6989586621679547909 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547910 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547911RSym4 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 b6989586621679547909 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547910 :: a) = Let6989586621679547911RSym5 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 b6989586621679547909 i6989586621679547910
type Apply (Let6989586621679547758RSym5 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 d6989586621679547756 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547757 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym5 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 d6989586621679547756 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547757 :: a) = Let6989586621679547758RSym6 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 d6989586621679547756 i6989586621679547757
type Apply (Let6989586621679547784RSym5 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 d6989586621679547782 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547783 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym5 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 d6989586621679547782 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547783 :: a) = Let6989586621679547784RSym6 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 d6989586621679547782 i6989586621679547783
type Apply (Let6989586621679547810RSym5 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 d6989586621679547808 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547809 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym5 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 d6989586621679547808 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547809 :: a) = Let6989586621679547810RSym6 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 d6989586621679547808 i6989586621679547809
type Apply (Let6989586621679547836RSym5 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 d6989586621679547834 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547835 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym5 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 d6989586621679547834 :: TyFun a [(VSpace k1 Nat, IList a)] -> Type) (i6989586621679547835 :: a) = Let6989586621679547836RSym6 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 d6989586621679547834 i6989586621679547835
type Apply (Let6989586621679096025L'Sym4 js'6989586621679096024 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 :: TyFun k3 (IList a) -> Type) (js6989586621679096018 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096025L'Sym4 js'6989586621679096024 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 :: TyFun k3 (IList a) -> Type) (js6989586621679096018 :: k3) = Let6989586621679096025L'Sym5 js'6989586621679096024 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 js6989586621679096018
type Apply DeltaRankSym0 (a6989586621679548003 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply DeltaRankSym0 (a6989586621679548003 :: Symbol) = DeltaRankSym1 a6989586621679548003
type Apply InjSym2ConRankSym0 (a6989586621679547924 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2ConRankSym0 (a6989586621679547924 :: Symbol) = InjSym2ConRankSym1 a6989586621679547924
type Apply InjSym2CovRankSym0 (a6989586621679547901 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjSym2CovRankSym0 (a6989586621679547901 :: Symbol) = InjSym2CovRankSym1 a6989586621679547901
type Apply SurjSym2ConRankSym0 (a6989586621679547885 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2ConRankSym0 (a6989586621679547885 :: Symbol) = SurjSym2ConRankSym1 a6989586621679547885
type Apply SurjSym2CovRankSym0 (a6989586621679547859 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjSym2CovRankSym0 (a6989586621679547859 :: Symbol) = SurjSym2CovRankSym1 a6989586621679547859
type Apply EpsilonRankSym0 (a6989586621679547982 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonRankSym0 (a6989586621679547982 :: Symbol) = EpsilonRankSym1 a6989586621679547982
type Apply EpsilonInvRankSym0 (a6989586621679547962 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply EpsilonInvRankSym0 (a6989586621679547962 :: Symbol) = EpsilonInvRankSym1 a6989586621679547962
type Apply InjAreaConRankSym0 (a6989586621679547824 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaConRankSym0 (a6989586621679547824 :: Symbol) = InjAreaConRankSym1 a6989586621679547824
type Apply InjAreaCovRankSym0 (a6989586621679547798 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply InjAreaCovRankSym0 (a6989586621679547798 :: Symbol) = InjAreaCovRankSym1 a6989586621679547798
type Apply SurjAreaConRankSym0 (a6989586621679547772 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply SurjAreaConRankSym0 (a6989586621679547772 :: Symbol) = SurjAreaConRankSym1 a6989586621679547772
type Apply SurjAreaCovRankSym0 (a6989586621679547746 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym1 a6989586621679548003 :: TyFun Nat (Symbol ~> (Symbol ~> [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679548004 :: Nat) = DeltaRankSym2 a6989586621679548003 a6989586621679548004
type Apply (InjSym2ConRankSym1 a6989586621679547924 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547925 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym1 a6989586621679547924 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547925 :: Nat) = InjSym2ConRankSym2 a6989586621679547924 a6989586621679547925
type Apply (InjSym2CovRankSym1 a6989586621679547901 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547902 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym1 a6989586621679547901 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547902 :: Nat) = InjSym2CovRankSym2 a6989586621679547901 a6989586621679547902
type Apply (SurjSym2ConRankSym1 a6989586621679547885 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547886 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym1 a6989586621679547885 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547886 :: Nat) = SurjSym2ConRankSym2 a6989586621679547885 a6989586621679547886
type Apply (SurjSym2CovRankSym1 a6989586621679547859 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547860 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym1 a6989586621679547859 :: TyFun Nat (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547860 :: Nat) = SurjSym2CovRankSym2 a6989586621679547859 a6989586621679547860
type Apply (ShowsPrec_6989586621679100102Sym0 :: TyFun Nat (IList a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679100114 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679100102Sym0 :: TyFun Nat (IList a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679100114 :: Nat) = ShowsPrec_6989586621679100102Sym1 a6989586621679100114 :: TyFun (IList a) (Symbol ~> Symbol) -> Type
type Apply (EpsilonRankSym1 a6989586621679547982 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547983 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym1 a6989586621679547982 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547983 :: Nat) = EpsilonRankSym2 a6989586621679547982 a6989586621679547983
type Apply (EpsilonInvRankSym1 a6989586621679547962 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547963 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym1 a6989586621679547962 :: TyFun Nat (NonEmpty Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547963 :: Nat) = EpsilonInvRankSym2 a6989586621679547962 a6989586621679547963
type Apply (InjAreaConRankSym1 a6989586621679547824 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547825 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym1 a6989586621679547824 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547825 :: Symbol) = InjAreaConRankSym2 a6989586621679547824 a6989586621679547825
type Apply (InjAreaCovRankSym1 a6989586621679547798 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547799 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym1 a6989586621679547798 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547799 :: Symbol) = InjAreaCovRankSym2 a6989586621679547798 a6989586621679547799
type Apply (SurjAreaConRankSym1 a6989586621679547772 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547773 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym1 a6989586621679547772 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547773 :: Symbol) = SurjAreaConRankSym2 a6989586621679547772 a6989586621679547773
type Apply (SurjAreaCovRankSym1 a6989586621679547746 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])))) -> Type) (a6989586621679547747 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096553Scrutinee_6989586621679091399Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (y'6989586621679096551 :: a) = Let6989586621679096553Scrutinee_6989586621679091399Sym1 y'6989586621679096551
type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x'6989586621679096540 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym0 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (x'6989586621679096540 :: a) = Let6989586621679096542Scrutinee_6989586621679091409Sym1 x'6989586621679096540
type Apply (DeltaRankSym2 a6989586621679548003 a6989586621679548004 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679548005 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (DeltaRankSym2 a6989586621679548003 a6989586621679548004 :: TyFun Symbol (Symbol ~> [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679548005 :: Symbol) = DeltaRankSym3 a6989586621679548003 a6989586621679548004 a6989586621679548005
type Apply (InjSym2ConRankSym2 a6989586621679547924 a6989586621679547925 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547926 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym2 a6989586621679547924 a6989586621679547925 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547926 :: Symbol) = InjSym2ConRankSym3 a6989586621679547924 a6989586621679547925 a6989586621679547926
type Apply (InjSym2CovRankSym2 a6989586621679547901 a6989586621679547902 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547903 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym2 a6989586621679547901 a6989586621679547902 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547903 :: Symbol) = InjSym2CovRankSym3 a6989586621679547901 a6989586621679547902 a6989586621679547903
type Apply (SurjSym2ConRankSym2 a6989586621679547885 a6989586621679547886 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547887 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym2 a6989586621679547885 a6989586621679547886 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547887 :: Symbol) = SurjSym2ConRankSym3 a6989586621679547885 a6989586621679547886 a6989586621679547887
type Apply (SurjSym2CovRankSym2 a6989586621679547859 a6989586621679547860 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547861 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym2 a6989586621679547859 a6989586621679547860 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547861 :: Symbol) = SurjSym2CovRankSym3 a6989586621679547859 a6989586621679547860 a6989586621679547861
type Apply (InjAreaConRankSym2 a6989586621679547824 a6989586621679547825 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547826 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym2 a6989586621679547824 a6989586621679547825 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547826 :: Symbol) = InjAreaConRankSym3 a6989586621679547824 a6989586621679547825 a6989586621679547826
type Apply (InjAreaCovRankSym2 a6989586621679547798 a6989586621679547799 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547800 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym2 a6989586621679547798 a6989586621679547799 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547800 :: Symbol) = InjAreaCovRankSym3 a6989586621679547798 a6989586621679547799 a6989586621679547800
type Apply (SurjAreaConRankSym2 a6989586621679547772 a6989586621679547773 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547774 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym2 a6989586621679547772 a6989586621679547773 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547774 :: Symbol) = SurjAreaConRankSym3 a6989586621679547772 a6989586621679547773 a6989586621679547774
type Apply (SurjAreaCovRankSym2 a6989586621679547746 a6989586621679547747 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547748 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym2 a6989586621679547746 a6989586621679547747 :: TyFun Symbol (Symbol ~> (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]))) -> Type) (a6989586621679547748 :: Symbol) = SurjAreaCovRankSym3 a6989586621679547746 a6989586621679547747 a6989586621679547748
type Apply (Let6989586621679547758RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547752 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547752 :: k1) = Let6989586621679547758RSym1 vid6989586621679547752 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547784RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547778 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547778 :: k1) = Let6989586621679547784RSym1 vid6989586621679547778 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547810RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547804 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547804 :: k1) = Let6989586621679547810RSym1 vid6989586621679547804 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547836RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547830 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym0 :: TyFun k1 (TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547830 :: k1) = Let6989586621679547836RSym1 vid6989586621679547830 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547934RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547929 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547934RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547929 :: k1) = Let6989586621679547934RSym1 vid6989586621679547929 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547911RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547906 :: k1) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547911RSym0 :: TyFun k1 (TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (vid6989586621679547906 :: k1) = Let6989586621679547911RSym1 vid6989586621679547906 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679547934RSym1 vid6989586621679547929 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679547930 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547934RSym1 vid6989586621679547929 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679547930 :: Nat) = Let6989586621679547934RSym2 vid6989586621679547929 vdim6989586621679547930 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (Let6989586621679547911RSym1 vid6989586621679547906 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679547907 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547911RSym1 vid6989586621679547906 :: TyFun Nat (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (vdim6989586621679547907 :: Nat) = Let6989586621679547911RSym2 vid6989586621679547906 vdim6989586621679547907 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type
type Apply (InjSym2ConRankSym3 a6989586621679547924 a6989586621679547925 a6989586621679547926 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547927 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2ConRankSym3 a6989586621679547924 a6989586621679547925 a6989586621679547926 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547927 :: Symbol) = InjSym2ConRankSym4 a6989586621679547924 a6989586621679547925 a6989586621679547926 a6989586621679547927
type Apply (InjSym2CovRankSym3 a6989586621679547901 a6989586621679547902 a6989586621679547903 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547904 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjSym2CovRankSym3 a6989586621679547901 a6989586621679547902 a6989586621679547903 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547904 :: Symbol) = InjSym2CovRankSym4 a6989586621679547901 a6989586621679547902 a6989586621679547903 a6989586621679547904
type Apply (SurjSym2ConRankSym3 a6989586621679547885 a6989586621679547886 a6989586621679547887 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547888 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2ConRankSym3 a6989586621679547885 a6989586621679547886 a6989586621679547887 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547888 :: Symbol) = SurjSym2ConRankSym4 a6989586621679547885 a6989586621679547886 a6989586621679547887 a6989586621679547888
type Apply (SurjSym2CovRankSym3 a6989586621679547859 a6989586621679547860 a6989586621679547861 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547862 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjSym2CovRankSym3 a6989586621679547859 a6989586621679547860 a6989586621679547861 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547862 :: Symbol) = SurjSym2CovRankSym4 a6989586621679547859 a6989586621679547860 a6989586621679547861 a6989586621679547862
type Apply (InjAreaConRankSym3 a6989586621679547824 a6989586621679547825 a6989586621679547826 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547827 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym3 a6989586621679547824 a6989586621679547825 a6989586621679547826 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547827 :: Symbol) = InjAreaConRankSym4 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827
type Apply (InjAreaCovRankSym3 a6989586621679547798 a6989586621679547799 a6989586621679547800 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547801 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym3 a6989586621679547798 a6989586621679547799 a6989586621679547800 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547801 :: Symbol) = InjAreaCovRankSym4 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801
type Apply (SurjAreaConRankSym3 a6989586621679547772 a6989586621679547773 a6989586621679547774 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547775 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym3 a6989586621679547772 a6989586621679547773 a6989586621679547774 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547775 :: Symbol) = SurjAreaConRankSym4 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775
type Apply (SurjAreaCovRankSym3 a6989586621679547746 a6989586621679547747 a6989586621679547748 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547749 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym3 a6989586621679547746 a6989586621679547747 a6989586621679547748 :: TyFun Symbol (Symbol ~> (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)])) -> Type) (a6989586621679547749 :: Symbol) = SurjAreaCovRankSym4 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749
type Apply (Lambda_6989586621679096653Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679096650 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096653Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679096650 :: k1) = Lambda_6989586621679096653Sym1 xs6989586621679096650 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096667Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679096664 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096667Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679096664 :: k1) = Lambda_6989586621679096667Sym1 xs6989586621679096664 :: TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096678Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679096675 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096678Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679096675 :: k1) = Lambda_6989586621679096678Sym1 ys6989586621679096675 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Let6989586621679096718L'Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679096715 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096718L'Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679096715 :: k1) = Let6989586621679096718L'Sym1 v6989586621679096715 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type
type Apply (CanTransposeConSym1 a6989586621679096435 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096436 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym1 a6989586621679096435 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096436 :: s) = CanTransposeConSym2 a6989586621679096435 a6989586621679096436
type Apply (CanTransposeCovSym1 a6989586621679096380 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096381 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym1 a6989586621679096380 :: TyFun s (s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096381 :: s) = CanTransposeCovSym2 a6989586621679096380 a6989586621679096381
type Apply (Let6989586621679096597Scrutinee_6989586621679091391Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679096594 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096597Scrutinee_6989586621679091391Sym0 :: TyFun k1 (TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) -> Type) (v6989586621679096594 :: k1) = Let6989586621679096597Scrutinee_6989586621679091391Sym1 v6989586621679096594 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type
type Apply (Let6989586621679096553Scrutinee_6989586621679091399Sym2 y'6989586621679096551 ys'6989586621679096552 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679096515 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096553Scrutinee_6989586621679091399Sym2 y'6989586621679096551 ys'6989586621679096552 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679096515 :: a) = Let6989586621679096553Scrutinee_6989586621679091399Sym3 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515
type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym2 x'6989586621679096540 xs'6989586621679096541 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679096515 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym2 x'6989586621679096540 xs'6989586621679096541 :: TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (x6989586621679096515 :: a) = Let6989586621679096542Scrutinee_6989586621679091409Sym3 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515
type Apply (Lambda_6989586621679096642Sym0 :: TyFun k2 (TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679096638 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096642Sym0 :: TyFun k2 (TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679096638 :: k2) = Lambda_6989586621679096642Sym1 xs6989586621679096638 :: TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096019Sym1 rl6989586621679096016 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) (is6989586621679096017 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096019Sym1 rl6989586621679096016 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) (is6989586621679096017 :: k1) = Lambda_6989586621679096019Sym2 rl6989586621679096016 is6989586621679096017
type Apply (Lambda_6989586621679096007Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679096005 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096007Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679096005 :: k1) = Lambda_6989586621679096007Sym1 rl6989586621679096005 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679095996Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679095994 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679095996Sym0 :: TyFun k1 (TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) -> Type) (rl6989586621679095994 :: k1) = Lambda_6989586621679095996Sym1 rl6989586621679095994 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type
type Apply (Let6989586621679547758RSym1 vid6989586621679547752 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547753 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym1 vid6989586621679547752 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547753 :: a) = Let6989586621679547758RSym2 vid6989586621679547752 a6989586621679547753
type Apply (Let6989586621679547784RSym1 vid6989586621679547778 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547779 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym1 vid6989586621679547778 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547779 :: a) = Let6989586621679547784RSym2 vid6989586621679547778 a6989586621679547779
type Apply (Let6989586621679547810RSym1 vid6989586621679547804 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547805 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym1 vid6989586621679547804 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547805 :: a) = Let6989586621679547810RSym2 vid6989586621679547804 a6989586621679547805
type Apply (Let6989586621679547836RSym1 vid6989586621679547830 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547831 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym1 vid6989586621679547830 :: TyFun a (TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) -> Type) (a6989586621679547831 :: a) = Let6989586621679547836RSym2 vid6989586621679547830 a6989586621679547831
type Apply (InjAreaConRankSym4 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547828 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaConRankSym4 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547828 :: Symbol) = InjAreaConRankSym5 a6989586621679547824 a6989586621679547825 a6989586621679547826 a6989586621679547827 a6989586621679547828
type Apply (InjAreaCovRankSym4 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547802 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (InjAreaCovRankSym4 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547802 :: Symbol) = InjAreaCovRankSym5 a6989586621679547798 a6989586621679547799 a6989586621679547800 a6989586621679547801 a6989586621679547802
type Apply (SurjAreaConRankSym4 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547776 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaConRankSym4 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547776 :: Symbol) = SurjAreaConRankSym5 a6989586621679547772 a6989586621679547773 a6989586621679547774 a6989586621679547775 a6989586621679547776
type Apply (SurjAreaCovRankSym4 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547750 :: Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (SurjAreaCovRankSym4 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 :: TyFun Symbol (Symbol ~> Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547750 :: Symbol) = SurjAreaCovRankSym5 a6989586621679547746 a6989586621679547747 a6989586621679547748 a6989586621679547749 a6989586621679547750
type Apply (Lambda_6989586621679096660Sym1 xs6989586621679096657 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679096658 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096660Sym1 xs6989586621679096657 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679096658 :: k1) = Lambda_6989586621679096660Sym2 xs6989586621679096657 ys6989586621679096658 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679096667Sym1 xs6989586621679096664 :: TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679096665 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096667Sym1 xs6989586621679096664 :: TyFun k2 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679096665 :: k2) = Lambda_6989586621679096667Sym2 xs6989586621679096664 xs'6989586621679096665 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (CanTransposeConSym2 a6989586621679096435 a6989586621679096436 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096437 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym2 a6989586621679096435 a6989586621679096436 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096437 :: s) = CanTransposeConSym3 a6989586621679096435 a6989586621679096436 a6989586621679096437
type Apply (CanTransposeCovSym2 a6989586621679096380 a6989586621679096381 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096382 :: s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym2 a6989586621679096380 a6989586621679096381 :: TyFun s ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096382 :: s) = CanTransposeCovSym3 a6989586621679096380 a6989586621679096381 a6989586621679096382
type Apply (Let6989586621679096334GoSym1 i6989586621679096332 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679096333 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096334GoSym1 i6989586621679096332 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679096333 :: k) = Let6989586621679096334GoSym2 i6989586621679096332 r6989586621679096333 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type
type Apply (Lambda_6989586621679096007Sym1 rl6989586621679096005 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679096006 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096007Sym1 rl6989586621679096005 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679096006 :: k2) = Lambda_6989586621679096007Sym2 rl6989586621679096005 is6989586621679096006 :: TyFun (IList a) (Maybe (IList a)) -> Type
type Apply (Lambda_6989586621679095996Sym1 rl6989586621679095994 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679095995 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679095996Sym1 rl6989586621679095994 :: TyFun k2 (TyFun (IList a) (Maybe (IList a)) -> Type) -> Type) (is6989586621679095995 :: k2) = Lambda_6989586621679095996Sym2 rl6989586621679095994 is6989586621679095995 :: TyFun (IList a) (Maybe (IList a)) -> Type
type Apply (Let6989586621679547758RSym2 vid6989586621679547752 a6989586621679547753 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547754 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym2 vid6989586621679547752 a6989586621679547753 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547754 :: a) = Let6989586621679547758RSym3 vid6989586621679547752 a6989586621679547753 b6989586621679547754
type Apply (Let6989586621679547784RSym2 vid6989586621679547778 a6989586621679547779 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547780 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym2 vid6989586621679547778 a6989586621679547779 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547780 :: a) = Let6989586621679547784RSym3 vid6989586621679547778 a6989586621679547779 b6989586621679547780
type Apply (Let6989586621679547810RSym2 vid6989586621679547804 a6989586621679547805 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547806 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym2 vid6989586621679547804 a6989586621679547805 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547806 :: a) = Let6989586621679547810RSym3 vid6989586621679547804 a6989586621679547805 b6989586621679547806
type Apply (Let6989586621679547836RSym2 vid6989586621679547830 a6989586621679547831 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547832 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym2 vid6989586621679547830 a6989586621679547831 :: TyFun a (TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) -> Type) (b6989586621679547832 :: a) = Let6989586621679547836RSym3 vid6989586621679547830 a6989586621679547831 b6989586621679547832
type Apply (Let6989586621679547934RSym2 vid6989586621679547929 vdim6989586621679547930 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679547931 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547934RSym2 vid6989586621679547929 vdim6989586621679547930 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679547931 :: a) = Let6989586621679547934RSym3 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931
type Apply (Let6989586621679547911RSym2 vid6989586621679547906 vdim6989586621679547907 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679547908 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547911RSym2 vid6989586621679547906 vdim6989586621679547907 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (a6989586621679547908 :: a) = Let6989586621679547911RSym3 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908
type Apply (Lambda_6989586621679096653Sym2 xs6989586621679096650 ys6989586621679096651 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (xs'6989586621679096652 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096653Sym2 xs6989586621679096650 ys6989586621679096651 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (xs'6989586621679096652 :: k2) = Lambda_6989586621679096653Sym3 xs6989586621679096650 ys6989586621679096651 xs'6989586621679096652
type Apply (Lambda_6989586621679096660Sym2 xs6989586621679096657 ys6989586621679096658 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679096659 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096660Sym2 xs6989586621679096657 ys6989586621679096658 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679096659 :: k2) = Lambda_6989586621679096660Sym3 xs6989586621679096657 ys6989586621679096658 ys'6989586621679096659
type Apply (Lambda_6989586621679096678Sym2 ys6989586621679096675 xs6989586621679096676 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679096677 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096678Sym2 ys6989586621679096675 xs6989586621679096676 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679096677 :: k2) = Lambda_6989586621679096678Sym3 ys6989586621679096675 xs6989586621679096676 ys'6989586621679096677
type Apply (Let6989586621679096553Scrutinee_6989586621679091399Sym4 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 xs6989586621679096516 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679096517 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096553Scrutinee_6989586621679091399Sym4 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 xs6989586621679096516 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679096517 :: a) = Let6989586621679096553Scrutinee_6989586621679091399Sym5 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 xs6989586621679096516 y6989586621679096517
type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym4 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 xs6989586621679096516 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679096517 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym4 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 xs6989586621679096516 :: TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) (y6989586621679096517 :: a) = Let6989586621679096542Scrutinee_6989586621679091409Sym5 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 xs6989586621679096516 y6989586621679096517
type Apply (Lambda_6989586621679096642Sym2 xs6989586621679096638 ys6989586621679096639 :: TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679096640 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096642Sym2 xs6989586621679096638 ys6989586621679096639 :: TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679096640 :: k3) = Lambda_6989586621679096642Sym3 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640
type Apply (Lambda_6989586621679096022Sym1 is'6989586621679096021 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (rl6989586621679096016 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096022Sym1 is'6989586621679096021 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (rl6989586621679096016 :: k1) = Lambda_6989586621679096022Sym2 is'6989586621679096021 rl6989586621679096016 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Let6989586621679547758RSym3 vid6989586621679547752 a6989586621679547753 b6989586621679547754 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547755 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym3 vid6989586621679547752 a6989586621679547753 b6989586621679547754 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547755 :: a) = Let6989586621679547758RSym4 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755
type Apply (Let6989586621679547784RSym3 vid6989586621679547778 a6989586621679547779 b6989586621679547780 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547781 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym3 vid6989586621679547778 a6989586621679547779 b6989586621679547780 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547781 :: a) = Let6989586621679547784RSym4 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781
type Apply (Let6989586621679547810RSym3 vid6989586621679547804 a6989586621679547805 b6989586621679547806 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547807 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym3 vid6989586621679547804 a6989586621679547805 b6989586621679547806 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547807 :: a) = Let6989586621679547810RSym4 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807
type Apply (Let6989586621679547836RSym3 vid6989586621679547830 a6989586621679547831 b6989586621679547832 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547833 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym3 vid6989586621679547830 a6989586621679547831 b6989586621679547832 :: TyFun a (TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) -> Type) (c6989586621679547833 :: a) = Let6989586621679547836RSym4 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833
type Apply (Let6989586621679547934RSym3 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679547932 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547934RSym3 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679547932 :: a) = Let6989586621679547934RSym4 vid6989586621679547929 vdim6989586621679547930 a6989586621679547931 b6989586621679547932
type Apply (Let6989586621679547911RSym3 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679547909 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547911RSym3 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (b6989586621679547909 :: a) = Let6989586621679547911RSym4 vid6989586621679547906 vdim6989586621679547907 a6989586621679547908 b6989586621679547909
type Apply (Let6989586621679096025L'Sym2 js'6989586621679096024 is'6989586621679096021 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) (rl6989586621679096016 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096025L'Sym2 js'6989586621679096024 is'6989586621679096021 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) (rl6989586621679096016 :: k1) = Let6989586621679096025L'Sym3 js'6989586621679096024 is'6989586621679096021 rl6989586621679096016 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type
type Apply (Lambda_6989586621679096645Sym1 xs''6989586621679096644 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679096638 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096645Sym1 xs''6989586621679096644 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs6989586621679096638 :: k1) = Lambda_6989586621679096645Sym2 xs''6989586621679096644 xs6989586621679096638 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096022Sym2 is'6989586621679096021 rl6989586621679096016 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (is6989586621679096017 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096022Sym2 is'6989586621679096021 rl6989586621679096016 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (is6989586621679096017 :: k2) = Lambda_6989586621679096022Sym3 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Let6989586621679547758RSym4 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547756 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547758RSym4 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547756 :: a) = Let6989586621679547758RSym5 vid6989586621679547752 a6989586621679547753 b6989586621679547754 c6989586621679547755 d6989586621679547756
type Apply (Let6989586621679547784RSym4 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547782 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547784RSym4 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547782 :: a) = Let6989586621679547784RSym5 vid6989586621679547778 a6989586621679547779 b6989586621679547780 c6989586621679547781 d6989586621679547782
type Apply (Let6989586621679547810RSym4 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547808 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547810RSym4 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547808 :: a) = Let6989586621679547810RSym5 vid6989586621679547804 a6989586621679547805 b6989586621679547806 c6989586621679547807 d6989586621679547808
type Apply (Let6989586621679547836RSym4 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547834 :: a) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (Let6989586621679547836RSym4 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 :: TyFun a (TyFun a [(VSpace k1 Nat, IList a)] -> Type) -> Type) (d6989586621679547834 :: a) = Let6989586621679547836RSym5 vid6989586621679547830 a6989586621679547831 b6989586621679547832 c6989586621679547833 d6989586621679547834
type Apply (Let6989586621679096025L'Sym3 js'6989586621679096024 is'6989586621679096021 rl6989586621679096016 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) (is6989586621679096017 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096025L'Sym3 js'6989586621679096024 is'6989586621679096021 rl6989586621679096016 :: TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) (is6989586621679096017 :: k2) = Let6989586621679096025L'Sym4 js'6989586621679096024 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 :: TyFun k3 (IList a) -> Type
type Apply (Lambda_6989586621679096645Sym2 xs''6989586621679096644 xs6989586621679096638 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679096639 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096645Sym2 xs''6989586621679096644 xs6989586621679096638 :: TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679096639 :: k2) = Lambda_6989586621679096645Sym3 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096022Sym3 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (js6989586621679096018 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096022Sym3 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 :: TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (js6989586621679096018 :: k3) = Lambda_6989586621679096022Sym4 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 js6989586621679096018
type Apply (Lambda_6989586621679096645Sym3 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679096640 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096645Sym3 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 :: TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs'6989586621679096640 :: k3) = Lambda_6989586621679096645Sym4 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679096645Sym4 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679096641 :: k4) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096645Sym4 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 :: TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679096641 :: k4) = Lambda_6989586621679096645Sym5 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 ys'6989586621679096641
type Rep (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing = SIList :: IList a -> Type
type Demote (IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Demote (IList a) = IList (Demote a)
type Rep1 IList Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: IList a) = Apply (Show__6989586621680289856Sym0 :: 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_6989586621680289864Sym0 :: 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_6989586621679392900Sym0 :: 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_6989586621679392884Sym0 :: 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_6989586621679392868Sym0 :: 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_6989586621679392852Sym0 :: 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_6989586621679392836Sym0 :: 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_6989586621679392820Sym0 :: 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_6989586621679100129Sym0 :: 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_6989586621679100190 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_6989586621679100102Sym0 :: TyFun Nat (IList a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679096800 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (IsAscendingISym0 :: TyFun (IList a) Bool -> Type) (a6989586621679096821 :: IList a) = IsAscendingISym1 a6989586621679096821
type Apply (LengthRSym0 :: TyFun [(VSpace s n, IList s)] N -> Type) (a6989586621679096795 :: [(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) (a6989586621679096795 :: [(VSpace s n, IList s)]) = LengthRSym1 a6989586621679096795
type Apply (SaneSym0 :: TyFun [(VSpace a b, IList a)] Bool -> Type) (a6989586621679096786 :: [(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) (a6989586621679096786 :: [(VSpace a b, IList a)]) = SaneSym1 a6989586621679096786
type Apply (Compare_6989586621679100129Sym1 a6989586621679100134 :: TyFun (IList a) Ordering -> Type) (a6989586621679100135 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679100129Sym1 a6989586621679100134 :: TyFun (IList a) Ordering -> Type) (a6989586621679100135 :: IList a) = Compare_6989586621679100129Sym2 a6989586621679100134 a6989586621679100135
type Apply (CanTransposeMultSym2 a6989586621679096305 a6989586621679096306 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096307 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym2 a6989586621679096305 a6989586621679096306 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096307 :: [(VSpace s n, IList s)]) = CanTransposeMultSym3 a6989586621679096305 a6989586621679096306 a6989586621679096307
type Apply (CanTransposeConSym3 a6989586621679096435 a6989586621679096436 a6989586621679096437 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096438 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeConSym3 a6989586621679096435 a6989586621679096436 a6989586621679096437 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096438 :: [(VSpace s n, IList s)]) = CanTransposeConSym4 a6989586621679096435 a6989586621679096436 a6989586621679096437 a6989586621679096438
type Apply (CanTransposeCovSym3 a6989586621679096380 a6989586621679096381 a6989586621679096382 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096383 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeCovSym3 a6989586621679096380 a6989586621679096381 a6989586621679096382 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096383 :: [(VSpace s n, IList s)]) = CanTransposeCovSym4 a6989586621679096380 a6989586621679096381 a6989586621679096382 a6989586621679096383
type Apply (CanTransposeSym3 a6989586621679096353 a6989586621679096354 a6989586621679096355 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096356 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym3 a6989586621679096353 a6989586621679096354 a6989586621679096355 :: TyFun [(VSpace s n, IList s)] Bool -> Type) (a6989586621679096356 :: [(VSpace s n, IList s)]) = CanTransposeSym4 a6989586621679096353 a6989586621679096354 a6989586621679096355 a6989586621679096356
type Apply (ContractISym0 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679096514 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (ConSym0 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679095888 :: NonEmpty a) = ConSym1 a6989586621679095888
type Apply (ContractRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096593 :: [(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) (a6989586621679096593 :: [(VSpace s n, IList s)]) = ContractRSym1 a6989586621679096593
type Apply (TailRSym0 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096714 :: [(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) (a6989586621679096714 :: [(VSpace s n, IList s)]) = TailRSym1 a6989586621679096714
type Apply (PrepICovSym1 a6989586621679096566 :: TyFun (IList a) (IList a) -> Type) (a6989586621679096567 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepICovSym1 a6989586621679096566 :: TyFun (IList a) (IList a) -> Type) (a6989586621679096567 :: IList a) = PrepICovSym2 a6989586621679096566 a6989586621679096567
type Apply (PrepIConSym1 a6989586621679096580 :: TyFun (IList a) (IList a) -> Type) (a6989586621679096581 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (PrepIConSym1 a6989586621679096580 :: TyFun (IList a) (IList a) -> Type) (a6989586621679096581 :: IList a) = PrepIConSym2 a6989586621679096580 a6989586621679096581
type Apply (MergeILSym1 a6989586621679096636 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679096637 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeILSym1 a6989586621679096636 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679096637 :: IList a) = MergeILSym2 a6989586621679096636 a6989586621679096637
type Apply (RelabelIL'Sym1 a6989586621679095992 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (a6989586621679095993 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelIL'Sym1 a6989586621679095992 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (a6989586621679095993 :: IList a) = RelabelIL'Sym2 a6989586621679095992 a6989586621679095993
type Apply (RelabelILSym1 a6989586621679096037 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679096038 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelILSym1 a6989586621679096037 :: TyFun (IList a) (Maybe (IList a)) -> Type) (a6989586621679096038 :: IList a) = RelabelILSym2 a6989586621679096037 a6989586621679096038
type Apply (Let6989586621679096041Scrutinee_6989586621679091531Sym1 rl6989586621679096039 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679096040 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096041Scrutinee_6989586621679091531Sym1 rl6989586621679096039 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679096040 :: IList a) = Let6989586621679096041Scrutinee_6989586621679091531Sym2 rl6989586621679096039 is6989586621679096040
type Apply (RelabelTranspositionsSym1 a6989586621679095976 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679095977 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym1 a6989586621679095976 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679095977 :: IList a) = RelabelTranspositionsSym2 a6989586621679095976 a6989586621679095977
type Apply (Let6989586621679095980Scrutinee_6989586621679091547Sym1 rl6989586621679095978 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679095979 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095980Scrutinee_6989586621679091547Sym1 rl6989586621679095978 :: TyFun (IList a) (Maybe (IList (a, a))) -> Type) (is6989586621679095979 :: IList a) = Let6989586621679095980Scrutinee_6989586621679091547Sym2 rl6989586621679095978 is6989586621679095979
type Apply (EpsilonRankSym2 a6989586621679547982 a6989586621679547983 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547984 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonRankSym2 a6989586621679547982 a6989586621679547983 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547984 :: NonEmpty Symbol) = EpsilonRankSym3 a6989586621679547982 a6989586621679547983 a6989586621679547984
type Apply (EpsilonInvRankSym2 a6989586621679547962 a6989586621679547963 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547964 :: NonEmpty Symbol) Source # 
Instance details

Defined in Math.Tensor.Basic.TH

type Apply (EpsilonInvRankSym2 a6989586621679547962 a6989586621679547963 :: TyFun (NonEmpty Symbol) (Maybe [(VSpace Symbol Nat, IList Symbol)]) -> Type) (a6989586621679547964 :: NonEmpty Symbol) = EpsilonInvRankSym3 a6989586621679547962 a6989586621679547963 a6989586621679547964
type Apply (ConCovSym1 a6989586621679095883 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679095884 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ConCovSym1 a6989586621679095883 :: TyFun (NonEmpty a) (IList a) -> Type) (a6989586621679095884 :: NonEmpty a) = ConCovSym2 a6989586621679095883 a6989586621679095884
type Apply (MergeRSym1 a6989586621679096689 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096690 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym1 a6989586621679096689 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096690 :: [(VSpace s n, IList s)]) = MergeRSym2 a6989586621679096689 a6989586621679096690
type Apply (RemoveUntilSym1 a6989586621679096330 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096331 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym1 a6989586621679096330 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096331 :: [(VSpace s n, IList s)]) = RemoveUntilSym2 a6989586621679096330 a6989586621679096331
type Apply (RelabelRSym2 a6989586621679096054 a6989586621679096055 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096056 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym2 a6989586621679096054 a6989586621679096055 :: TyFun [(VSpace s n, IList s)] (Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096056 :: [(VSpace s n, IList s)]) = RelabelRSym3 a6989586621679096054 a6989586621679096055 a6989586621679096056
type Apply (TranspositionsSym2 a6989586621679096259 a6989586621679096260 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679096261 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679096259 a6989586621679096260 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679096261 :: [(VSpace s n, IList s)]) = TranspositionsSym3 a6989586621679096259 a6989586621679096260 a6989586621679096261
type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym2 vs6989586621679096308 tl6989586621679096309 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679096310 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym2 vs6989586621679096308 tl6989586621679096309 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679096310 :: [(VSpace s n, IList s)]) = Let6989586621679096311Scrutinee_6989586621679091469Sym3 vs6989586621679096308 tl6989586621679096309 r6989586621679096310
type Apply (Lambda_6989586621679096007Sym2 rl6989586621679096005 is6989586621679096006 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679096009 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096007Sym2 rl6989586621679096005 is6989586621679096006 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679096009 :: IList a) = Lambda_6989586621679096007Sym3 rl6989586621679096005 is6989586621679096006 is'6989586621679096009
type Apply (Lambda_6989586621679095996Sym2 rl6989586621679095994 is6989586621679095995 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679095998 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679095996Sym2 rl6989586621679095994 is6989586621679095995 :: TyFun (IList a) (Maybe (IList a)) -> Type) (is'6989586621679095998 :: IList a) = Lambda_6989586621679095996Sym3 rl6989586621679095994 is6989586621679095995 is'6989586621679095998
type Apply (Lambda_6989586621679096019Sym3 rl6989586621679096016 is6989586621679096017 js6989586621679096018 :: TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) (is'6989586621679096021 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096019Sym3 rl6989586621679096016 is6989586621679096017 js6989586621679096018 :: TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) (is'6989586621679096021 :: NonEmpty (a, a)) = Lambda_6989586621679096019Sym4 rl6989586621679096016 is6989586621679096017 js6989586621679096018 is'6989586621679096021
type Apply (Let6989586621679096334GoSym3 i6989586621679096332 r6989586621679096333 a6989586621679096335 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096336 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096334GoSym3 i6989586621679096332 r6989586621679096333 a6989586621679096335 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type) (a6989586621679096336 :: [(VSpace s n, IList s)]) = Let6989586621679096334GoSym4 i6989586621679096332 r6989586621679096333 a6989586621679096335 a6989586621679096336
type Apply (Let6989586621679096553Scrutinee_6989586621679091399Sym5 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 xs6989586621679096516 y6989586621679096517 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679096518 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096553Scrutinee_6989586621679091399Sym5 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 xs6989586621679096516 y6989586621679096517 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679096518 :: [a]) = Let6989586621679096553Scrutinee_6989586621679091399Sym6 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 xs6989586621679096516 y6989586621679096517 ys6989586621679096518
type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym5 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 xs6989586621679096516 y6989586621679096517 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679096518 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym5 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 xs6989586621679096516 y6989586621679096517 :: TyFun [a] (Maybe (IList a)) -> Type) (ys6989586621679096518 :: [a]) = Let6989586621679096542Scrutinee_6989586621679091409Sym6 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 xs6989586621679096516 y6989586621679096517 ys6989586621679096518
type Apply (Lambda_6989586621679096653Sym3 xs6989586621679096650 ys6989586621679096651 xs'6989586621679096652 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679096655 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096653Sym3 xs6989586621679096650 ys6989586621679096651 xs'6989586621679096652 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679096655 :: NonEmpty a) = Lambda_6989586621679096653Sym4 xs6989586621679096650 ys6989586621679096651 xs'6989586621679096652 xs''6989586621679096655
type Apply (Lambda_6989586621679096660Sym3 xs6989586621679096657 ys6989586621679096658 ys'6989586621679096659 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679096662 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096660Sym3 xs6989586621679096657 ys6989586621679096658 ys'6989586621679096659 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679096662 :: NonEmpty a) = Lambda_6989586621679096660Sym4 xs6989586621679096657 ys6989586621679096658 ys'6989586621679096659 ys''6989586621679096662
type Apply (Lambda_6989586621679096667Sym3 xs6989586621679096664 xs'6989586621679096665 ys6989586621679096666 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679096669 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096667Sym3 xs6989586621679096664 xs'6989586621679096665 ys6989586621679096666 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679096669 :: NonEmpty a) = Lambda_6989586621679096667Sym4 xs6989586621679096664 xs'6989586621679096665 ys6989586621679096666 xs''6989586621679096669
type Apply (Lambda_6989586621679096678Sym3 ys6989586621679096675 xs6989586621679096676 ys'6989586621679096677 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679096680 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096678Sym3 ys6989586621679096675 xs6989586621679096676 ys'6989586621679096677 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679096680 :: NonEmpty a) = Lambda_6989586621679096678Sym4 ys6989586621679096675 xs6989586621679096676 ys'6989586621679096677 ys''6989586621679096680
type Apply (Lambda_6989586621679096642Sym4 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 ys'6989586621679096641 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679096644 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096642Sym4 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 ys'6989586621679096641 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (xs''6989586621679096644 :: NonEmpty a) = Lambda_6989586621679096642Sym5 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 ys'6989586621679096641 xs''6989586621679096644
type Apply (Lambda_6989586621679096703Sym6 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 ys6989586621679096698 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679096705 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym6 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 ys6989586621679096698 :: TyFun (IList s) (Maybe [(VSpace s n, IList s)]) -> Type) (xl'6989586621679096705 :: IList s) = Lambda_6989586621679096703Sym7 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 ys6989586621679096698 xl'6989586621679096705
type Apply (Lambda_6989586621679096022Sym4 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 js6989586621679096018 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (js'6989586621679096024 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096022Sym4 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 js6989586621679096018 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (js'6989586621679096024 :: NonEmpty a) = Lambda_6989586621679096022Sym5 is'6989586621679096021 rl6989586621679096016 is6989586621679096017 js6989586621679096018 js'6989586621679096024
type Apply (Lambda_6989586621679096645Sym5 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 ys'6989586621679096641 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679096647 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096645Sym5 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 ys'6989586621679096641 :: TyFun (NonEmpty a) (Maybe (IList a)) -> Type) (ys''6989586621679096647 :: NonEmpty a) = Lambda_6989586621679096645Sym6 xs''6989586621679096644 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 ys'6989586621679096641 ys''6989586621679096647
type Apply (MergeILSym0 :: TyFun (IList a) (IList a ~> Maybe (IList a)) -> Type) (a6989586621679096636 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeILSym0 :: TyFun (IList a) (IList a ~> Maybe (IList a)) -> Type) (a6989586621679096636 :: IList a) = MergeILSym1 a6989586621679096636
type Apply (Compare_6989586621679100129Sym0 :: TyFun (IList a) (IList a ~> Ordering) -> Type) (a6989586621679100134 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679100129Sym0 :: TyFun (IList a) (IList a ~> Ordering) -> Type) (a6989586621679100134 :: IList a) = Compare_6989586621679100129Sym1 a6989586621679100134
type Apply (RelabelIL'Sym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList (a, a))) -> Type) (a6989586621679095992 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelIL'Sym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList (a, a))) -> Type) (a6989586621679095992 :: NonEmpty (a, a)) = RelabelIL'Sym1 a6989586621679095992
type Apply (RelabelILSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList a)) -> Type) (a6989586621679096037 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelILSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe (IList a)) -> Type) (a6989586621679096037 :: NonEmpty (a, a)) = RelabelILSym1 a6989586621679096037
type Apply (Let6989586621679096041Scrutinee_6989586621679091531Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679096039 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096041Scrutinee_6989586621679091531Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679096039 :: NonEmpty (a, a)) = Let6989586621679096041Scrutinee_6989586621679091531Sym1 rl6989586621679096039
type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) (a6989586621679095976 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) (a6989586621679095976 :: NonEmpty (a, a)) = RelabelTranspositionsSym1 a6989586621679095976
type Apply (Let6989586621679095980Scrutinee_6989586621679091547Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679095978 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095980Scrutinee_6989586621679091547Sym0 :: TyFun (NonEmpty (a, a)) (TyFun (IList a) (Maybe (IList (a, a))) -> Type) -> Type) (rl6989586621679095978 :: NonEmpty (a, a)) = Let6989586621679095980Scrutinee_6989586621679091547Sym1 rl6989586621679095978
type Apply (ConCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> IList a) -> Type) (a6989586621679095883 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ConCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> IList a) -> Type) (a6989586621679095883 :: NonEmpty a) = ConCovSym1 a6989586621679095883
type Apply (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096689 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (MergeRSym0 :: TyFun [(VSpace s n, IList s)] ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096689 :: [(VSpace s n, IList s)]) = MergeRSym1 a6989586621679096689
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679096769 :: [(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) (a6989586621679096769 :: [(VSpace s n, IList s)]) = HeadRSym1 a6989586621679096769
type Apply (Let6989586621679096553Scrutinee_6989586621679091399Sym1 y'6989586621679096551 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (ys'6989586621679096552 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096553Scrutinee_6989586621679091399Sym1 y'6989586621679096551 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (ys'6989586621679096552 :: [a]) = Let6989586621679096553Scrutinee_6989586621679091399Sym2 y'6989586621679096551 ys'6989586621679096552
type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym1 x'6989586621679096540 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs'6989586621679096541 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym1 x'6989586621679096540 :: TyFun [a] (TyFun a (TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (xs'6989586621679096541 :: [a]) = Let6989586621679096542Scrutinee_6989586621679091409Sym2 x'6989586621679096540 xs'6989586621679096541
type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679096330 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679096330 :: Ix s) = RemoveUntilSym1 a6989586621679096330 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (ShowsPrec_6989586621679100102Sym1 a6989586621679100114 :: TyFun (IList a) (Symbol ~> Symbol) -> Type) (a6989586621679100115 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679100102Sym1 a6989586621679100114 :: TyFun (IList a) (Symbol ~> Symbol) -> Type) (a6989586621679100115 :: IList a) = ShowsPrec_6989586621679100102Sym2 a6989586621679100114 a6989586621679100115
type Apply (Lambda_6989586621679096019Sym0 :: TyFun (NonEmpty (a, a)) (TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) -> Type) (rl6989586621679096016 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096019Sym0 :: TyFun (NonEmpty (a, a)) (TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type) -> Type) (rl6989586621679096016 :: NonEmpty (a, a)) = Lambda_6989586621679096019Sym1 rl6989586621679096016 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) -> Type
type Apply (CanTransposeSym1 a6989586621679096353 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096354 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679096353 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096354 :: Ix s) = CanTransposeSym2 a6989586621679096353 a6989586621679096354
type Apply (Let6989586621679096334GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679096332 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096334GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679096332 :: Ix s) = Let6989586621679096334GoSym1 i6989586621679096332 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type
type Apply (Lambda_6989586621679096703Sym1 xv6989586621679096693 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))))) -> Type) (xl6989586621679096694 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym1 xv6989586621679096693 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))))) -> Type) (xl6989586621679096694 :: IList s) = Lambda_6989586621679096703Sym2 xv6989586621679096693 xl6989586621679096694
type Apply (Let6989586621679096010Scrutinee_6989586621679091543Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679096009 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096010Scrutinee_6989586621679091543Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679096009 :: IList a) = Let6989586621679096010Scrutinee_6989586621679091543Sym1 is'6989586621679096009 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type
type Apply (Let6989586621679095999Scrutinee_6989586621679091545Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679095998 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095999Scrutinee_6989586621679091545Sym0 :: TyFun (IList a) (TyFun k1 (TyFun k2 Bool -> Type) -> Type) -> Type) (is'6989586621679095998 :: IList a) = Let6989586621679095999Scrutinee_6989586621679091545Sym1 is'6989586621679095998 :: TyFun k1 (TyFun k2 Bool -> Type) -> Type
type Apply (TranspositionsSym1 a6989586621679096259 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679096260 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679096259 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679096260 :: TransRule s) = TranspositionsSym2 a6989586621679096259 a6989586621679096260
type Apply (CanTransposeMultSym1 a6989586621679096305 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096306 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679096305 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096306 :: TransRule s) = CanTransposeMultSym2 a6989586621679096305 a6989586621679096306
type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679096309 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679096309 :: TransRule s) = Let6989586621679096311Scrutinee_6989586621679091469Sym2 vs6989586621679096308 tl6989586621679096309
type Apply (RelabelRSym1 a6989586621679096054 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096055 :: NonEmpty (s, s)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelRSym1 a6989586621679096054 :: TyFun (NonEmpty (s, s)) ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)]) -> Type) (a6989586621679096055 :: NonEmpty (s, s)) = RelabelRSym2 a6989586621679096054 a6989586621679096055
type Apply (Lambda_6989586621679096660Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679096657 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096660Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (xs6989586621679096657 :: NonEmpty a) = Lambda_6989586621679096660Sym1 xs6989586621679096657 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096703Sym2 xv6989586621679096693 xl6989586621679096694 :: TyFun [(VSpace s n, IList s)] (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))) -> Type) (xs6989586621679096695 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym2 xv6989586621679096693 xl6989586621679096694 :: TyFun [(VSpace s n, IList s)] (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))) -> Type) (xs6989586621679096695 :: [(VSpace s n, IList s)]) = Lambda_6989586621679096703Sym3 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695
type Apply (Let6989586621679096553Scrutinee_6989586621679091399Sym3 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679096516 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096553Scrutinee_6989586621679091399Sym3 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679096516 :: [a]) = Let6989586621679096553Scrutinee_6989586621679091399Sym4 y'6989586621679096551 ys'6989586621679096552 x6989586621679096515 xs6989586621679096516
type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym3 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679096516 :: [a]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096542Scrutinee_6989586621679091409Sym3 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 :: TyFun [a] (TyFun a (TyFun [a] (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679096516 :: [a]) = Let6989586621679096542Scrutinee_6989586621679091409Sym4 x'6989586621679096540 xs'6989586621679096541 x6989586621679096515 xs6989586621679096516
type Apply (CanTransposeSym2 a6989586621679096353 a6989586621679096354 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096355 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679096353 a6989586621679096354 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096355 :: Ix s) = CanTransposeSym3 a6989586621679096353 a6989586621679096354 a6989586621679096355
type Apply (Let6989586621679096718L'Sym1 v6989586621679096715 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (l6989586621679096716 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096718L'Sym1 v6989586621679096715 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (l6989586621679096716 :: IList a) = Let6989586621679096718L'Sym2 v6989586621679096715 l6989586621679096716 :: TyFun k2 (Maybe (IList a)) -> Type
type Apply (Let6989586621679096597Scrutinee_6989586621679091391Sym1 v6989586621679096594 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (is6989586621679096595 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096597Scrutinee_6989586621679091391Sym1 v6989586621679096594 :: TyFun (IList a) (TyFun k2 (Maybe (IList a)) -> Type) -> Type) (is6989586621679096595 :: IList a) = Let6989586621679096597Scrutinee_6989586621679091391Sym2 v6989586621679096594 is6989586621679096595 :: TyFun k2 (Maybe (IList a)) -> Type
type Apply (Let6989586621679096025L'Sym0 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) -> Type) (js'6989586621679096024 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096025L'Sym0 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) -> Type) (js'6989586621679096024 :: NonEmpty a) = Let6989586621679096025L'Sym1 js'6989586621679096024 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096653Sym1 xs6989586621679096650 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679096651 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096653Sym1 xs6989586621679096650 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (ys6989586621679096651 :: NonEmpty a) = Lambda_6989586621679096653Sym2 xs6989586621679096650 ys6989586621679096651 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679096678Sym1 ys6989586621679096675 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679096676 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096678Sym1 ys6989586621679096675 :: TyFun (NonEmpty a) (TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) (xs6989586621679096676 :: NonEmpty a) = Lambda_6989586621679096678Sym2 ys6989586621679096675 xs6989586621679096676 :: TyFun k2 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type
type Apply (Lambda_6989586621679096642Sym1 xs6989586621679096638 :: TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679096639 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096642Sym1 xs6989586621679096638 :: TyFun (NonEmpty a) (TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) (ys6989586621679096639 :: NonEmpty a) = Lambda_6989586621679096642Sym2 xs6989586621679096638 ys6989586621679096639 :: TyFun k3 (TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096022Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (is'6989586621679096021 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096022Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) (is'6989586621679096021 :: NonEmpty a) = Lambda_6989586621679096022Sym1 is'6989586621679096021 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096019Sym2 rl6989586621679096016 is6989586621679096017 :: TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) (js6989586621679096018 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096019Sym2 rl6989586621679096016 is6989586621679096017 :: TyFun (NonEmpty a) (TyFun (NonEmpty (a, a)) (Maybe (IList (a, a))) -> Type) -> Type) (js6989586621679096018 :: NonEmpty a) = Lambda_6989586621679096019Sym3 rl6989586621679096016 is6989586621679096017 js6989586621679096018
type Apply (Let6989586621679096334GoSym2 i6989586621679096332 r6989586621679096333 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679096335 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096334GoSym2 i6989586621679096332 r6989586621679096333 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679096335 :: Ix s) = Let6989586621679096334GoSym3 i6989586621679096332 r6989586621679096333 a6989586621679096335 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (Let6989586621679096025L'Sym1 js'6989586621679096024 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) (is'6989586621679096021 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096025L'Sym1 js'6989586621679096024 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type) -> Type) (is'6989586621679096021 :: NonEmpty a) = Let6989586621679096025L'Sym2 js'6989586621679096024 is'6989586621679096021 :: TyFun k1 (TyFun k2 (TyFun k3 (IList a) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096645Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (xs''6989586621679096644 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096645Sym0 :: TyFun (NonEmpty a) (TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type) -> Type) (xs''6989586621679096644 :: NonEmpty a) = Lambda_6989586621679096645Sym1 xs''6989586621679096644 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun k4 (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096667Sym2 xs6989586621679096664 xs'6989586621679096665 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys6989586621679096666 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096667Sym2 xs6989586621679096664 xs'6989586621679096665 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys6989586621679096666 :: NonEmpty a) = Lambda_6989586621679096667Sym3 xs6989586621679096664 xs'6989586621679096665 ys6989586621679096666
type Apply (Lambda_6989586621679096703Sym4 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679096697 :: IList s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym4 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 :: TyFun (IList s) ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])) -> Type) (yl6989586621679096697 :: IList s) = Lambda_6989586621679096703Sym5 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697
type Apply (Lambda_6989586621679096642Sym3 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679096641 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096642Sym3 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 :: TyFun (NonEmpty a) (TyFun (NonEmpty a) (Maybe (IList a)) -> Type) -> Type) (ys'6989586621679096641 :: NonEmpty a) = Lambda_6989586621679096642Sym4 xs6989586621679096638 ys6989586621679096639 xs'6989586621679096640 ys'6989586621679096641
type Apply (Lambda_6989586621679096703Sym5 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679096698 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym5 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 :: TyFun [(VSpace s n, IList s)] (IList s ~> Maybe [(VSpace s n, IList s)]) -> Type) (ys6989586621679096698 :: [(VSpace s n, IList s)]) = Lambda_6989586621679096703Sym6 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696 yl6989586621679096697 ys6989586621679096698
type Apply (CanTransposeConSym0 :: TyFun (VSpace s n) (s ~> (s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679096435 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym0 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (VSpace s n ~> (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)])))))) -> Type) (xv6989586621679096693 :: VSpace s n) = Lambda_6989586621679096703Sym1 xv6989586621679096693
type Apply (RelabelRSym0 :: TyFun (VSpace s n) (NonEmpty (s, s) ~> ([(VSpace s n, IList s)] ~> Maybe [(VSpace s n, IList s)])) -> Type) (a6989586621679096054 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679096308 :: VSpace s n) = Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308
type Apply (Lambda_6989586621679096703Sym3 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679096696 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096703Sym3 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 :: TyFun (VSpace s n) (IList s ~> ([(VSpace s n, IList s)] ~> (IList s ~> Maybe [(VSpace s n, IList s)]))) -> Type) (yv6989586621679096696 :: VSpace s n) = Lambda_6989586621679096703Sym4 xv6989586621679096693 xl6989586621679096694 xs6989586621679096695 yv6989586621679096696

The generalized tensor rank is a list of vector spaces and associated index lists. Sane generalized ranks have their vector spaces in ascending order.

type GRank s n = [(VSpace s n, IList s)] Source #

The specialisation used for the parameterisation of the tensor type.

As explained above, the contravariant or covariant indices for each vector space must be unique. They must also be sorted for more efficiency. The same applies for the vector spaces: Each distinct vector space must have a unique representation, generalized ranks are sorted by the vector spaces. This is checked by the function sane.

sane :: (Ord a, Ord b) => [(VSpace a b, IList a)] -> Bool Source #

The function headR extracts the first index within a generalized rank. The first index is always referring to the first vector space within the rank. If the rank is purely covariant or purley contravariant, the first index ist the first element of the respective index list. For mixed ranks, the first index is the one which compares less. If they compare equal, it is always the contravariant index. This defines an order where contractible indices always appear next to each other, which greatly facilitates contraction.

headR :: Ord s => GRank s n -> (VSpace s n, Ix s) Source #

The remaining rank after popping the headR is obtained by the function tailR.

tailR :: Ord s => GRank s n -> GRank s n Source #

The total number of indices.

lengthR :: GRank s n -> N Source #

A generalized rank is contracted by considering each vector space separately. Indices appearing in both upper and lower position are removed from the rank. If that leaves a vector space without indices, it is also discarded.

contractR :: Ord s => GRank s n -> GRank s n Source #

Merging two generalized ranks in order to obtain the generalized rank of the tensor product. Returns Nothing for incompatible ranks.

mergeR :: (Ord s, Ord n) => GRank s n -> GRank s n -> Maybe (GRank s n) Source #

To perform transpositions of two indices, single contravariant or covariant indices have to be specified. A representation for single indices is provided by the sum type Ix.

data Ix a Source #

Constructors

ICon a 
ICov a 

Instances

Instances details
NFData1 Ix Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

compare :: Ix a -> Ix a -> Ordering #

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

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

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

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

max :: Ix a -> Ix a -> Ix a #

min :: Ix a -> Ix a -> Ix a #

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

Defined in Math.Tensor.Safe.TH

Methods

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

show :: Ix a -> String #

showList :: [Ix a] -> ShowS #

Generic (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

rnf :: Ix a -> () #

PShow (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

POrd (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

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

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

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

PEq (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

Generic1 Ix Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Rep1 Ix :: k -> Type #

Methods

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

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

SDecide a => TestCoercion (SIx :: Ix a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

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

SDecide a => TestEquality (SIx :: Ix a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

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

SingI n => SingI ('ICon n :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('ICon n) #

SingI n => SingI ('ICov n :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('ICov n) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679100088Sym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ICovSym0 :: TyFun a (Ix a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (IxCompareSym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (ICovSym0 :: TyFun a (Ix a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ICovSym0 #

SingI (IConSym0 :: TyFun a (Ix a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing IConSym0 #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (IxCompareSym1 a6989586621679096840 :: TyFun (Ix a) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Compare_6989586621679100088Sym1 a6989586621679100093 :: TyFun (Ix a) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing HeadRSym0 #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

(SOrd a, SingI d) => SingI (IxCompareSym1 d :: TyFun (Ix a) Ordering -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (IxCompareSym1 d) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym1 d) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (CanTransposeSym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

type Apply (IConSym0 :: TyFun a (Ix a) -> Type) (a6989586621679095879 :: a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (ICovSym0 :: TyFun a (Ix a) -> Type) (a6989586621679095881 :: a) = ICovSym1 a6989586621679095881
type Apply (ShowsPrec_6989586621679100067Sym0 :: TyFun Nat (Ix a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679100077 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679100067Sym0 :: TyFun Nat (Ix a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679100077 :: Nat) = ShowsPrec_6989586621679100067Sym1 a6989586621679100077 :: TyFun (Ix a) (Symbol ~> Symbol) -> Type
type Apply (Let6989586621679096334GoSym1 i6989586621679096332 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679096333 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096334GoSym1 i6989586621679096332 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) (r6989586621679096333 :: k) = Let6989586621679096334GoSym2 i6989586621679096332 r6989586621679096333 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type
type Rep (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep (Ix a) = D1 ('MetaData "Ix" "Math.Tensor.Safe.TH" "safe-tensor-0.2.1.1-HV6XtoU04VwKCpzbN3KLoQ" 'False) (C1 ('MetaCons "ICon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)) :+: C1 ('MetaCons "ICov" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))
type Sing Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing = SIx :: Ix a -> Type
type Demote (Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Demote (Ix a) = Ix (Demote a)
type Rep1 Ix Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep1 Ix = D1 ('MetaData "Ix" "Math.Tensor.Safe.TH" "safe-tensor-0.2.1.1-HV6XtoU04VwKCpzbN3KLoQ" 'False) (C1 ('MetaCons "ICon" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1) :+: C1 ('MetaCons "ICov" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) Par1))
type Show_ (arg :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: Ix a) = Apply (Show__6989586621680289856Sym0 :: 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_6989586621680289864Sym0 :: 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_6989586621679392900Sym0 :: 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_6989586621679392884Sym0 :: 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_6989586621679392868Sym0 :: 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_6989586621679392852Sym0 :: 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_6989586621679392836Sym0 :: 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_6989586621679392820Sym0 :: 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_6989586621679100088Sym0 :: 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_6989586621679100182 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_6989586621679100067Sym0 :: TyFun Nat (Ix a1 ~> (Symbol ~> Symbol)) -> Type) a2) a3) a4
type Apply (IxCompareSym1 a6989586621679096840 :: TyFun (Ix a) Ordering -> Type) (a6989586621679096841 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IxCompareSym1 a6989586621679096840 :: TyFun (Ix a) Ordering -> Type) (a6989586621679096841 :: Ix a) = IxCompareSym2 a6989586621679096840 a6989586621679096841
type Apply (Compare_6989586621679100088Sym1 a6989586621679100093 :: TyFun (Ix a) Ordering -> Type) (a6989586621679100094 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679100088Sym1 a6989586621679100093 :: TyFun (Ix a) Ordering -> Type) (a6989586621679100094 :: Ix a) = Compare_6989586621679100088Sym2 a6989586621679100093 a6989586621679100094
type Apply (IxCompareSym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679096840 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (IxCompareSym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679096840 :: Ix a) = IxCompareSym1 a6989586621679096840
type Apply (Compare_6989586621679100088Sym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679100093 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Compare_6989586621679100088Sym0 :: TyFun (Ix a) (Ix a ~> Ordering) -> Type) (a6989586621679100093 :: Ix a) = Compare_6989586621679100088Sym1 a6989586621679100093
type Apply (HeadRSym0 :: TyFun [(VSpace s n, IList s)] (VSpace s n, Ix s) -> Type) (a6989586621679096769 :: [(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) (a6989586621679096769 :: [(VSpace s n, IList s)]) = HeadRSym1 a6989586621679096769
type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679096330 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RemoveUntilSym0 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679096330 :: Ix s) = RemoveUntilSym1 a6989586621679096330 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (ShowsPrec_6989586621679100067Sym1 a6989586621679100077 :: TyFun (Ix a) (Symbol ~> Symbol) -> Type) (a6989586621679100078 :: Ix a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679100067Sym1 a6989586621679100077 :: TyFun (Ix a) (Symbol ~> Symbol) -> Type) (a6989586621679100078 :: Ix a) = ShowsPrec_6989586621679100067Sym2 a6989586621679100077 a6989586621679100078
type Apply (CanTransposeSym1 a6989586621679096353 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096354 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym1 a6989586621679096353 :: TyFun (Ix s) (Ix s ~> ([(VSpace s n, IList s)] ~> Bool)) -> Type) (a6989586621679096354 :: Ix s) = CanTransposeSym2 a6989586621679096353 a6989586621679096354
type Apply (Let6989586621679096334GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679096332 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096334GoSym0 :: TyFun (Ix s) (TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type) -> Type) (i6989586621679096332 :: Ix s) = Let6989586621679096334GoSym1 i6989586621679096332 :: TyFun k (TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) -> Type
type Apply (CanTransposeSym2 a6989586621679096353 a6989586621679096354 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096355 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym2 a6989586621679096353 a6989586621679096354 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096355 :: Ix s) = CanTransposeSym3 a6989586621679096353 a6989586621679096354 a6989586621679096355
type Apply (Let6989586621679096334GoSym2 i6989586621679096332 r6989586621679096333 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679096335 :: Ix s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096334GoSym2 i6989586621679096332 r6989586621679096333 :: TyFun (Ix s) ([(VSpace s n, IList s)] ~> [(VSpace s n, IList s)]) -> Type) (a6989586621679096335 :: Ix s) = Let6989586621679096334GoSym3 i6989586621679096332 r6989586621679096333 a6989586621679096335 :: TyFun [(VSpace s n, IList s)] [(VSpace s n, IList s)] -> Type
type Apply (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679096353 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeSym0 :: TyFun (VSpace s n) (Ix s ~> (Ix s ~> ([(VSpace s n, IList s)] ~> Bool))) -> Type) (a6989586621679096353 :: VSpace s n) = CanTransposeSym1 a6989586621679096353

To perform transpositions of multiple indices at once, a list of source and a list of target indices has to be provided. Both lists must be permutations of each other. A suitable representation is provided by the sum type TransRule.

Note that transposing indices in a tensor does not change its generalized rank.

data TransRule a Source #

Constructors

TransCon (NonEmpty a) (NonEmpty a) 
TransCov (NonEmpty a) (NonEmpty a) 

Instances

Instances details
NFData1 TransRule Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Generic (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

rnf :: TransRule a -> () #

PShow (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

PEq (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

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

Defined in Math.Tensor.Safe.TH

Methods

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

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

Defined in Math.Tensor.Safe.TH

Associated Types

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

Methods

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

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

Generic1 TransRule Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Rep1 TransRule :: k -> Type #

Methods

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

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

SDecide (NonEmpty a) => TestCoercion (STransRule :: TransRule a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

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

SDecide (NonEmpty a) => TestEquality (STransRule :: TransRule a -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

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

(SingI n1, SingI n2) => SingI ('TransCon n1 n2 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('TransCon n1 n2) #

(SingI n1, SingI n2) => SingI ('TransCov n1 n2 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('TransCov n1 n2) #

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (SaneTransRuleSym0 :: TyFun (TransRule a) Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransConSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SingI (TransCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (TransConSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679100147Sym1 a6989586621679100157 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TransCovSym1 a6989586621679095893 :: TyFun (NonEmpty a) (TransRule a) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TransCovSym1 d) #

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

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (TransConSym1 d) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096267Scrutinee_6989586621679091475Sym0 :: TyFun k1 (TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096267Scrutinee_6989586621679091475Sym1 vs6989586621679096262 :: TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679100147Sym0 :: TyFun Nat (TransRule a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679100157 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679100147Sym0 :: TyFun Nat (TransRule a ~> (Symbol ~> Symbol)) -> Type) (a6989586621679100157 :: Nat) = ShowsPrec_6989586621679100147Sym1 a6989586621679100157 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type
type Apply (Let6989586621679096267Scrutinee_6989586621679091475Sym0 :: TyFun k1 (TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (vs6989586621679096262 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096267Scrutinee_6989586621679091475Sym0 :: TyFun k1 (TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) -> Type) (vs6989586621679096262 :: k1) = Let6989586621679096267Scrutinee_6989586621679091475Sym1 vs6989586621679096262 :: TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type
type Rep (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing = STransRule :: TransRule a -> Type
type Demote (TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep1 TransRule Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: TransRule a) = Apply (Show__6989586621680289856Sym0 :: 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_6989586621680289864Sym0 :: 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_6989586621679100202 a2 b
type ShowsPrec a2 (a3 :: TransRule a1) a4 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (SaneTransRuleSym0 :: TyFun (TransRule a) Bool -> Type) (a6989586621679096318 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (SaneTransRuleSym0 :: TyFun (TransRule a) Bool -> Type) (a6989586621679096318 :: TransRule a) = SaneTransRuleSym1 a6989586621679096318
type Apply (TransConSym1 a6989586621679095890 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679095891 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransConSym1 a6989586621679095890 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679095891 :: NonEmpty a) = TransConSym2 a6989586621679095890 a6989586621679095891
type Apply (TransCovSym1 a6989586621679095893 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679095894 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TransCovSym1 a6989586621679095893 :: TyFun (NonEmpty a) (TransRule a) -> Type) (a6989586621679095894 :: NonEmpty a) = TransCovSym2 a6989586621679095893 a6989586621679095894
type Apply (TransConSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) (a6989586621679095890 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (TransCovSym0 :: TyFun (NonEmpty a) (NonEmpty a ~> TransRule a) -> Type) (a6989586621679095893 :: NonEmpty a) = TransCovSym1 a6989586621679095893
type Apply (ShowsPrec_6989586621679100147Sym1 a6989586621679100157 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type) (a6989586621679100158 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679100147Sym1 a6989586621679100157 :: TyFun (TransRule a) (Symbol ~> Symbol) -> Type) (a6989586621679100158 :: TransRule a) = ShowsPrec_6989586621679100147Sym2 a6989586621679100157 a6989586621679100158
type Apply (TranspositionsSym1 a6989586621679096259 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679096260 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679096259 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679096260 :: TransRule s) = TranspositionsSym2 a6989586621679096259 a6989586621679096260
type Apply (CanTransposeMultSym1 a6989586621679096305 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096306 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (CanTransposeMultSym1 a6989586621679096305 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Bool) -> Type) (a6989586621679096306 :: TransRule s) = CanTransposeMultSym2 a6989586621679096305 a6989586621679096306
type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679096309 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679096309 :: TransRule s) = Let6989586621679096311Scrutinee_6989586621679091469Sym2 vs6989586621679096308 tl6989586621679096309
type Apply (Let6989586621679096267Scrutinee_6989586621679091475Sym1 vs6989586621679096262 :: TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (tl6989586621679096263 :: TransRule a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096267Scrutinee_6989586621679091475Sym1 vs6989586621679096262 :: TyFun (TransRule a) (TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type) -> Type) (tl6989586621679096263 :: TransRule a) = Let6989586621679096267Scrutinee_6989586621679091475Sym2 vs6989586621679096262 tl6989586621679096263 :: TyFun k2 (TyFun k3 (TyFun k4 Bool -> Type) -> Type) -> Type
type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679096259 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679096308 :: VSpace s n) = Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308

To relabel a tensor, a list of source-target pairs has to be provided. Relabelling affects each index regardless of upper or lower position, so it suffices to have the type synonym RelabelRule.

type RelabelRule s = NonEmpty (s, s) Source #

Relabelling a tensor changes its generalized rank. If tensor indices corresponding to a given vector space can be relabelled using a given RelabelRule, relabelR returns the new generalized rank. Otherwise, it returns Nothing.

relabelR :: (Ord s, Ord n) => VSpace s n -> RelabelRule s -> GRank s n -> Maybe (GRank s n) Source #

The Tensor GADT

The Tensor type parameterised by a generalized rank r and a value type v is a recursive container for tensor components of value v.

  • The base case is a Scalar, which represents a tensor with empty rank. A scalar holds a single value of type v.
  • For non-empty ranks, a tensor is represented of as a mapping from all possible index values for the first index headR r to tensors of lower rank tailR r, implemented as sparse ascending assocs list (omitting zero values).
  • There is a shortcut for zero tensors, which are represented as ZeroTensor regardless of the generalized rank.

Generalized ranks must be Sane. The empty rank '[] is always sane.

data Tensor :: Rank -> Type -> Type where Source #

The Tensor type parameterized by its generalized rank r and arbitrary value type v.

Constructors

ZeroTensor :: forall (r :: Rank) v. Sane r ~ 'True => Tensor r v 
Scalar :: forall v. !v -> Tensor '[] v 
Tensor :: forall (r :: Rank) (r' :: Rank) v. (Sane r ~ 'True, TailR r ~ r') => [(Int, Tensor r' v)] -> Tensor r v 

Instances

Instances details
Functor (Tensor r) Source # 
Instance details

Defined in Math.Tensor.Safe

Methods

fmap :: (a -> b) -> Tensor r a -> Tensor r b #

(<$) :: a -> Tensor r b -> Tensor r a #

Eq v => Eq (Tensor r v) Source # 
Instance details

Defined in Math.Tensor.Safe

Methods

(==) :: Tensor r v -> Tensor r v -> Bool #

(/=) :: Tensor r v -> Tensor r v -> Bool #

Show v => Show (Tensor r v) Source # 
Instance details

Defined in Math.Tensor.Safe

Methods

showsPrec :: Int -> Tensor r v -> ShowS #

show :: Tensor r v -> String #

showList :: [Tensor r v] -> ShowS #

NFData v => NFData (Tensor r v) Source # 
Instance details

Defined in Math.Tensor.Safe

Methods

rnf :: Tensor r v -> () #

Conversion from and to lists

A Tensor r v can be constructed from a list of key-value pairs, where keys are length-typed vectors Vec of n = lengthR r indices and values are the corresponding components.

The index values must be given in the order defined by repeatedly applying headR to the rank.

Given a value, such an assocs list is obtained by toList.

fromList :: forall r v n. (SingI r, Sane r ~ 'True, LengthR r ~ n) => [(Vec n Int, v)] -> Tensor r v Source #

Construct Tensor from assocs list. Keys are length-typed vectors of indices.

fromList' :: forall r v n. (Sane r ~ 'True, LengthR r ~ n) => Sing r -> [(Vec n Int, v)] -> Tensor r v Source #

Construct Tensor from assocs list. Keys are length-typed vectors of indices. Generalized rank is passed explicitly as singleton.

toList :: forall r v n. (SingI r, SingI n, LengthR r ~ n) => Tensor r v -> [(Vec n Int, v)] Source #

Get assocs list from Tensor. Keys are length-typed vectors of indices.

Basic operations

We have now everything at our disposal to define basic tensor operations using the rank-parameterised Tensor type. These operations (algebra, contraction, transposition, relabelling) are safe in the sense that they can only be performed between tensors of matching type and the type of the resulting tensor is predetermined. There is also an existentially quantified variant of these operations available from Math.Tensor.

Tensor algebra

(&+) :: forall (r :: Rank) (r' :: Rank) v. (r ~ r', Num v, Eq v) => Tensor r v -> Tensor r' v -> Tensor r v infixl 6 Source #

Tensor addition. Generalized ranks of summands and sum coincide. Zero values are removed from the result.

(&-) :: forall (r :: Rank) (r' :: Rank) v. (r ~ r', Num v, Eq v) => Tensor r v -> Tensor r' v -> Tensor r v infixl 6 Source #

Tensor subtraction. Generalized ranks of operands and difference coincide. Zero values are removed from the result.

(&*) :: forall (r :: Rank) (r' :: Rank) (r'' :: Rank) v. (Num v, 'Just r'' ~ MergeR r r', SingI r, SingI r') => Tensor r v -> Tensor r' v -> Tensor r'' v infixl 7 Source #

Tensor multiplication. Generalized anks r, r' of factors must not overlap. The product rank is the merged rank MergeR r r' of the factor ranks.

removeZeros :: (Num v, Eq v) => Tensor r v -> Tensor r v Source #

Given a Num and Eq instance, remove all zero values from the tensor, eventually replacing a zero Scalar or an empty Tensor with ZeroTensor.

Contraction

contract :: forall (r :: Rank) (r' :: Rank) v. (r' ~ ContractR r, SingI r, Num v, Eq v) => Tensor r v -> Tensor r' v Source #

Tensor contraction. Contracting a tensor is the identity function on non-contractible tensors. Otherwise, the result is the contracted tensor with the contracted labels removed from the generalized rank.

Transpositions

transpose :: forall (vs :: VSpace Symbol Nat) (a :: Ix Symbol) (b :: Ix Symbol) (r :: Rank) v. (CanTranspose vs a b r ~ 'True, SingI r) => Sing vs -> Sing a -> Sing b -> Tensor r v -> Tensor r v Source #

Tensor transposition. Given a vector space and two index labels, the result is a tensor with the corresponding entries swapped. Only possible if the indices are part of the rank. The generalized rank remains untouched.

transposeMult :: forall (vs :: VSpace Symbol Nat) (tl :: TransRule Symbol) (r :: Rank) v. (IsJust (Transpositions vs tl r) ~ 'True, SingI r) => Sing vs -> Sing tl -> Tensor r v -> Tensor r v Source #

Transposition of multiple labels. Given a vector space and a transposition rule, the result is a tensor with the corresponding entries swapped. Only possible if the indices are part of the generalized rank. The generalized rank remains untouched.

Relabelling

relabel :: forall (vs :: VSpace Symbol Nat) (rl :: RelabelRule Symbol) (r1 :: Rank) (r2 :: Rank) v. (RelabelR vs rl r1 ~ 'Just r2, Sane r2 ~ 'True, SingI r1, SingI r2) => Sing vs -> Sing rl -> Tensor r1 v -> Tensor r2 v Source #

Tensor relabelling. Given a vector space and a relabelling rule, the result is a tensor with the resulting generalized rank after relabelling. Only possible if labels to be renamed are part of the generalized rank and if uniqueness of labels after relabelling is preserved.

Length-typed vectors

Type-level naturals used for tensor construction and also internally.

data N where Source #

Constructors

Z :: N 
S :: N -> N 

Instances

Instances details
Eq N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(==) :: N -> N -> Bool #

(/=) :: N -> N -> Bool #

Num N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(+) :: N -> N -> N #

(-) :: N -> N -> N #

(*) :: N -> N -> N #

negate :: N -> N #

abs :: N -> N #

signum :: N -> N #

fromInteger :: Integer -> N #

Ord N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

compare :: N -> N -> Ordering #

(<) :: N -> N -> Bool #

(<=) :: N -> N -> Bool #

(>) :: N -> N -> Bool #

(>=) :: N -> N -> Bool #

max :: N -> N -> N #

min :: N -> N -> N #

Show N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

showsPrec :: Int -> N -> ShowS #

show :: N -> String #

showList :: [N] -> ShowS #

Generic N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Rep N :: Type -> Type #

Methods

from :: N -> Rep N x #

to :: Rep N x -> N #

NFData N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

rnf :: N -> () #

PShow N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type ShowsPrec arg arg1 arg2 :: Symbol #

type Show_ arg :: Symbol #

type ShowList arg arg1 :: Symbol #

SShow N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

PNum N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type arg + arg1 :: a #

type arg - arg1 :: a #

type arg * arg1 :: a #

type Negate arg :: a #

type Abs arg :: a #

type Signum arg :: a #

type FromInteger arg :: a #

SNum N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

(%+) :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply (+@#@$) t1) t2) #

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

(%*) :: forall (t1 :: N) (t2 :: N). Sing t1 -> Sing t2 -> Sing (Apply (Apply (*@#@$) t1) t2) #

sNegate :: forall (t :: N). Sing t -> Sing (Apply NegateSym0 t) #

sAbs :: forall (t :: N). Sing t -> Sing (Apply AbsSym0 t) #

sSignum :: forall (t :: N). Sing t -> Sing (Apply SignumSym0 t) #

sFromInteger :: forall (t :: Nat). Sing t -> Sing (Apply FromIntegerSym0 t) #

POrd N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Compare arg arg1 :: Ordering #

type arg < arg1 :: Bool #

type arg <= arg1 :: Bool #

type arg > arg1 :: Bool #

type arg >= arg1 :: Bool #

type Max arg arg1 :: a #

type Min arg arg1 :: a #

SOrd N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

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

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

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

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

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

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

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

SEq N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

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

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

PEq N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type x == y :: Bool #

type x /= y :: Bool #

SDecide N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

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

SingKind N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Associated Types

type Demote N = (r :: Type) #

Methods

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

toSing :: Demote N -> SomeSing N #

TestCoercion SN Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testCoercion :: forall (a :: k) (b :: k). SN a -> SN b -> Maybe (Coercion a b) #

TestEquality SN Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

testEquality :: forall (a :: k) (b :: k). SN a -> SN b -> Maybe (a :~: b) #

SingI 'Z Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing 'Z #

SingI n => SingI ('S n :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing ('S n) #

SuppressUnusedWarnings FromInteger_6989586621679100020Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings FromNatSym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings ShowsPrec_6989586621679098253Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Signum_6989586621679100013Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Abs_6989586621679100006Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings Negate_6989586621679099989Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings SSym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679099555Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679099996Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679099978Sym0 Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings TFHelper_6989586621679099966Sym0 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_6989586621679099555Sym1 a6989586621679099560 :: TyFun N Bool -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679099996Sym1 a6989586621679100001 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679099978Sym1 a6989586621679099983 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (TFHelper_6989586621679099966Sym1 a6989586621679099971 :: TyFun N N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (ShowsPrec_6989586621679098253Sym1 a6989586621679098263 :: TyFun N (Symbol ~> Symbol) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (RelabelTranspositions'Sym0 :: TyFun (NonEmpty (a, a)) [(N, N)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (LengthNESym0 :: TyFun (NonEmpty a) N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SOrd a => SingI (RelabelTranspositions'Sym0 :: TyFun (NonEmpty (a, a)) [(N, N)] -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SEq a => SingI (Transpositions'Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> (NonEmpty (Maybe a) ~> Maybe [(N, N)])) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SingI (LengthNESym0 :: TyFun (NonEmpty a) N -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679095899Is'''Sym0 :: TyFun (NonEmpty (a6989586621679091332, b6989586621679091335)) (NonEmpty (N, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679095899Is'Sym0 :: TyFun (NonEmpty (a6989586621679091332, b6989586621679091333)) (NonEmpty (N, b6989586621679091333)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Transpositions'Sym1 a6989586621679096143 :: TyFun (NonEmpty a) (NonEmpty (Maybe a) ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

(SEq a, SingI d) => SingI (Transpositions'Sym1 d :: TyFun (NonEmpty a) (NonEmpty (Maybe a) ~> Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679095899Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679091334, b6989586621679091335) ~> NonEmpty (a6989586621679091334, N)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679095899GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679091332, b6989586621679091333) ~> NonEmpty (N, b6989586621679091333)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Transpositions'Sym2 a6989586621679096143 a6989586621679096144 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

(SEq a, SingI d1, SingI d2) => SingI (Transpositions'Sym2 d1 d2 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

Methods

sing :: Sing (Transpositions'Sym2 d1 d2) #

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679095899Go'Sym1 is6989586621679095898 :: TyFun N (NonEmpty (a6989586621679091334, b6989586621679091335) ~> NonEmpty (a6989586621679091334, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679095899GoSym1 is6989586621679095898 :: TyFun N (NonEmpty (a6989586621679091332, b6989586621679091333) ~> NonEmpty (N, b6989586621679091333)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096149Xs'Sym1 sources6989586621679096146 :: TyFun k2 (TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096198Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096195Sym1 sources6989586621679096146 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, 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 (Let6989586621679096149FindSym1 sources6989586621679096146 :: TyFun k2 (TyFun k3 (TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096149Go'Sym1 sources6989586621679096146 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096198Sym1 ss6989586621679096197 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096191Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096195Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679095899Go'Sym2 is6989586621679095898 a6989586621679095908 :: TyFun (NonEmpty (a6989586621679091334, b6989586621679091335)) (NonEmpty (a6989586621679091334, N)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679095899GoSym2 is6989586621679095898 a6989586621679095917 :: TyFun (NonEmpty (a6989586621679091332, b6989586621679091333)) (NonEmpty (N, b6989586621679091333)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096149Xs'Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096149FindSym2 sources6989586621679096146 targets6989586621679096147 :: TyFun k3 (TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096149Go'Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun k3 (TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096191Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun k3 (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096198Sym2 ss6989586621679096197 sources6989586621679096146 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096195Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096149Go'Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096149FindSym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096198Sym3 ss6989586621679096197 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Lambda_6989586621679096198Sym4 ss6989586621679096197 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun k4 (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096149FindSym4 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 a6989586621679096161 :: TyFun (NonEmpty (N, Maybe a6989586621679091235)) (Maybe N) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

SuppressUnusedWarnings (Let6989586621679096149Go'Sym4 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 a6989586621679096181 :: TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Rep N = D1 ('MetaData "N" "Math.Tensor.Safe.TH" "safe-tensor-0.2.1.1-HV6XtoU04VwKCpzbN3KLoQ" 'False) (C1 ('MetaCons "Z" 'PrefixI 'False) (U1 :: Type -> Type) :+: C1 ('MetaCons "S" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 N)))
type Sing Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Sing = SN
type Demote N Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Demote N = N
type Show_ (arg :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Show_ (arg :: N) = Apply (Show__6989586621680289856Sym0 :: 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_6989586621680289864Sym0 :: 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_6989586621679099996Sym0 a1) a2
type (a1 :: N) - (a2 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type (a1 :: N) + (a2 :: N) = Apply (Apply TFHelper_6989586621679099966Sym0 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_6989586621679392900Sym0 :: 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_6989586621679392884Sym0 :: 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_6989586621679392868Sym0 :: 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_6989586621679392852Sym0 :: 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_6989586621679099555Sym0 a1) a2
type (arg :: N) < (arg1 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type (arg :: N) < (arg1 :: N) = Apply (Apply (TFHelper_6989586621679392820Sym0 :: 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_6989586621679392799Sym0 :: 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_6989586621679100168 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_6989586621679098253Sym0 a1) a2) a3
type Apply FromInteger_6989586621679100020Sym0 (a6989586621679100024 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply FromInteger_6989586621679100020Sym0 (a6989586621679100024 :: Nat) = FromInteger_6989586621679100020Sym1 a6989586621679100024
type Apply FromNatSym0 (a6989586621679096862 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply FromNatSym0 (a6989586621679096862 :: Nat) = FromNatSym1 a6989586621679096862
type Apply Signum_6989586621679100013Sym0 (a6989586621679100017 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Signum_6989586621679100013Sym0 (a6989586621679100017 :: N) = Signum_6989586621679100013Sym1 a6989586621679100017
type Apply Abs_6989586621679100006Sym0 (a6989586621679100010 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Abs_6989586621679100006Sym0 (a6989586621679100010 :: N) = Abs_6989586621679100006Sym1 a6989586621679100010
type Apply Negate_6989586621679099989Sym0 (a6989586621679099993 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply Negate_6989586621679099989Sym0 (a6989586621679099993 :: N) = Negate_6989586621679099989Sym1 a6989586621679099993
type Apply SSym0 (a6989586621679095873 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply SSym0 (a6989586621679095873 :: N) = SSym1 a6989586621679095873
type Apply (TFHelper_6989586621679099555Sym1 a6989586621679099560 :: TyFun N Bool -> Type) (a6989586621679099561 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679099555Sym1 a6989586621679099560 :: TyFun N Bool -> Type) (a6989586621679099561 :: N) = TFHelper_6989586621679099555Sym2 a6989586621679099560 a6989586621679099561
type Apply (TFHelper_6989586621679099996Sym1 a6989586621679100001 :: TyFun N N -> Type) (a6989586621679100002 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679099996Sym1 a6989586621679100001 :: TyFun N N -> Type) (a6989586621679100002 :: N) = TFHelper_6989586621679099996Sym2 a6989586621679100001 a6989586621679100002
type Apply (TFHelper_6989586621679099978Sym1 a6989586621679099983 :: TyFun N N -> Type) (a6989586621679099984 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679099978Sym1 a6989586621679099983 :: TyFun N N -> Type) (a6989586621679099984 :: N) = TFHelper_6989586621679099978Sym2 a6989586621679099983 a6989586621679099984
type Apply (TFHelper_6989586621679099966Sym1 a6989586621679099971 :: TyFun N N -> Type) (a6989586621679099972 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TFHelper_6989586621679099966Sym1 a6989586621679099971 :: TyFun N N -> Type) (a6989586621679099972 :: N) = TFHelper_6989586621679099966Sym2 a6989586621679099971 a6989586621679099972
type Apply (Lambda_6989586621679096191Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun k3 (Maybe N) -> Type) (lhs_69895866216790915016989586621679096193 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096191Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun k3 (Maybe N) -> Type) (lhs_69895866216790915016989586621679096193 :: k3) = Lambda_6989586621679096191Sym4 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 lhs_69895866216790915016989586621679096193
type Apply (Lambda_6989586621679096198Sym4 ss6989586621679096197 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun k4 (Maybe N) -> Type) (lhs_69895866216790914996989586621679096200 :: k4) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096198Sym4 ss6989586621679096197 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun k4 (Maybe N) -> Type) (lhs_69895866216790914996989586621679096200 :: k4) = Lambda_6989586621679096198Sym5 ss6989586621679096197 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 lhs_69895866216790914996989586621679096200
type Apply ShowsPrec_6989586621679098253Sym0 (a6989586621679098263 :: Nat) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply ShowsPrec_6989586621679098253Sym0 (a6989586621679098263 :: Nat) = ShowsPrec_6989586621679098253Sym1 a6989586621679098263
type Apply TFHelper_6989586621679099555Sym0 (a6989586621679099560 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679099555Sym0 (a6989586621679099560 :: N) = TFHelper_6989586621679099555Sym1 a6989586621679099560
type Apply TFHelper_6989586621679099996Sym0 (a6989586621679100001 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679099996Sym0 (a6989586621679100001 :: N) = TFHelper_6989586621679099996Sym1 a6989586621679100001
type Apply TFHelper_6989586621679099978Sym0 (a6989586621679099983 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679099978Sym0 (a6989586621679099983 :: N) = TFHelper_6989586621679099978Sym1 a6989586621679099983
type Apply TFHelper_6989586621679099966Sym0 (a6989586621679099971 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply TFHelper_6989586621679099966Sym0 (a6989586621679099971 :: N) = TFHelper_6989586621679099966Sym1 a6989586621679099971
type Apply (ShowsPrec_6989586621679098253Sym1 a6989586621679098263 :: TyFun N (Symbol ~> Symbol) -> Type) (a6989586621679098264 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (ShowsPrec_6989586621679098253Sym1 a6989586621679098263 :: TyFun N (Symbol ~> Symbol) -> Type) (a6989586621679098264 :: N) = ShowsPrec_6989586621679098253Sym2 a6989586621679098263 a6989586621679098264
type Apply (Let6989586621679095899Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679091334, b6989586621679091335) ~> NonEmpty (a6989586621679091334, N)) -> Type) -> Type) (is6989586621679095898 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095899Go'Sym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679091334, b6989586621679091335) ~> NonEmpty (a6989586621679091334, N)) -> Type) -> Type) (is6989586621679095898 :: k) = Let6989586621679095899Go'Sym1 is6989586621679095898 :: TyFun N (NonEmpty (a6989586621679091334, b6989586621679091335) ~> NonEmpty (a6989586621679091334, N)) -> Type
type Apply (Let6989586621679095899GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679091332, b6989586621679091333) ~> NonEmpty (N, b6989586621679091333)) -> Type) -> Type) (is6989586621679095898 :: k) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095899GoSym0 :: TyFun k (TyFun N (NonEmpty (a6989586621679091332, b6989586621679091333) ~> NonEmpty (N, b6989586621679091333)) -> Type) -> Type) (is6989586621679095898 :: k) = Let6989586621679095899GoSym1 is6989586621679095898 :: TyFun N (NonEmpty (a6989586621679091332, b6989586621679091333) ~> NonEmpty (N, b6989586621679091333)) -> Type
type Apply (Let6989586621679096149Xs'Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149Xs'Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k1) = Let6989586621679096149Xs'Sym1 sources6989586621679096146 :: TyFun k2 (TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) -> Type
type Apply (Lambda_6989586621679096191Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096191Sym0 :: TyFun k1 (TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k1) = Lambda_6989586621679096191Sym1 sources6989586621679096146 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type
type Apply (Lambda_6989586621679096195Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096195Sym0 :: TyFun k1 (TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k1) = Lambda_6989586621679096195Sym1 sources6989586621679096146 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) -> Type) -> Type
type Apply (Let6989586621679095899Go'Sym1 is6989586621679095898 :: TyFun N (NonEmpty (a6989586621679091334, b6989586621679091335) ~> NonEmpty (a6989586621679091334, N)) -> Type) (a6989586621679095908 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095899Go'Sym1 is6989586621679095898 :: TyFun N (NonEmpty (a6989586621679091334, b6989586621679091335) ~> NonEmpty (a6989586621679091334, N)) -> Type) (a6989586621679095908 :: N) = Let6989586621679095899Go'Sym2 is6989586621679095898 a6989586621679095908 :: TyFun (NonEmpty (a6989586621679091334, b6989586621679091335)) (NonEmpty (a6989586621679091334, N)) -> Type
type Apply (Let6989586621679095899GoSym1 is6989586621679095898 :: TyFun N (NonEmpty (a6989586621679091332, b6989586621679091333) ~> NonEmpty (N, b6989586621679091333)) -> Type) (a6989586621679095917 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095899GoSym1 is6989586621679095898 :: TyFun N (NonEmpty (a6989586621679091332, b6989586621679091333) ~> NonEmpty (N, b6989586621679091333)) -> Type) (a6989586621679095917 :: N) = Let6989586621679095899GoSym2 is6989586621679095898 a6989586621679095917 :: TyFun (NonEmpty (a6989586621679091332, b6989586621679091333)) (NonEmpty (N, b6989586621679091333)) -> Type
type Apply (Let6989586621679096149FindSym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149FindSym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k1) = Let6989586621679096149FindSym1 sources6989586621679096146 :: TyFun k2 (TyFun k3 (TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) -> Type) -> Type
type Apply (Let6989586621679096149Go'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149Go'Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k1) = Let6989586621679096149Go'Sym1 sources6989586621679096146 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) -> Type) -> Type
type Apply (Let6989586621679096149Xs'Sym1 sources6989586621679096146 :: TyFun k2 (TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) -> Type) (targets6989586621679096147 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149Xs'Sym1 sources6989586621679096146 :: TyFun k2 (TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) -> Type) (targets6989586621679096147 :: k2) = Let6989586621679096149Xs'Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type
type Apply (Lambda_6989586621679096191Sym1 sources6989586621679096146 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679096147 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096191Sym1 sources6989586621679096146 :: TyFun k2 (TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679096147 :: k2) = Lambda_6989586621679096191Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type
type Apply (Lambda_6989586621679096198Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) -> Type) (ss6989586621679096197 :: k1) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096198Sym0 :: TyFun k1 (TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) -> Type) (ss6989586621679096197 :: k1) = Lambda_6989586621679096198Sym1 ss6989586621679096197 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type
type Apply (Let6989586621679096149FindSym1 sources6989586621679096146 :: TyFun k2 (TyFun k3 (TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) -> Type) -> Type) (targets6989586621679096147 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149FindSym1 sources6989586621679096146 :: TyFun k2 (TyFun k3 (TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) -> Type) -> Type) (targets6989586621679096147 :: k2) = Let6989586621679096149FindSym2 sources6989586621679096146 targets6989586621679096147 :: TyFun k3 (TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) -> Type
type Apply (Let6989586621679096149Go'Sym1 sources6989586621679096146 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) -> Type) -> Type) (targets6989586621679096147 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149Go'Sym1 sources6989586621679096146 :: TyFun k2 (TyFun k3 (TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) -> Type) -> Type) (targets6989586621679096147 :: k2) = Let6989586621679096149Go'Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun k3 (TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) -> Type
type Apply (Lambda_6989586621679096198Sym1 ss6989586621679096197 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k2) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096198Sym1 ss6989586621679096197 :: TyFun k2 (TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) -> Type) (sources6989586621679096146 :: k2) = Lambda_6989586621679096198Sym2 ss6989586621679096197 sources6989586621679096146 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type
type Apply (Let6989586621679096149FindSym2 sources6989586621679096146 targets6989586621679096147 :: TyFun k3 (TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) -> Type) (xs6989586621679096148 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149FindSym2 sources6989586621679096146 targets6989586621679096147 :: TyFun k3 (TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) -> Type) (xs6989586621679096148 :: k3) = Let6989586621679096149FindSym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type
type Apply (Let6989586621679096149Go'Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun k3 (TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) -> Type) (xs6989586621679096148 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149Go'Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun k3 (TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) -> Type) (xs6989586621679096148 :: k3) = Let6989586621679096149Go'Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type
type Apply (Lambda_6989586621679096198Sym2 ss6989586621679096197 sources6989586621679096146 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679096147 :: k3) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096198Sym2 ss6989586621679096197 sources6989586621679096146 :: TyFun k3 (TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) -> Type) (targets6989586621679096147 :: k3) = Lambda_6989586621679096198Sym3 ss6989586621679096197 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type
type Apply (Let6989586621679096149Go'Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) (a6989586621679096181 :: N) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149Go'Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun N (NonEmpty a6989586621679091234 ~> NonEmpty (N, a6989586621679091234)) -> Type) (a6989586621679096181 :: N) = Let6989586621679096149Go'Sym4 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 a6989586621679096181 :: TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type
type Apply (Let6989586621679096149FindSym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) (a6989586621679096161 :: a6989586621679091235) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149FindSym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun a6989586621679091235 (NonEmpty (N, Maybe a6989586621679091235) ~> Maybe N) -> Type) (a6989586621679096161 :: a6989586621679091235) = Let6989586621679096149FindSym4 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 a6989586621679096161
type Apply (LengthILSym0 :: TyFun (IList a) N -> Type) (a6989586621679096800 :: IList a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym1 a6989586621679095976 :: TyFun (IList a) (Maybe [(N, N)]) -> Type) (a6989586621679095977 :: IList a) = RelabelTranspositionsSym2 a6989586621679095976 a6989586621679095977
type Apply (Let6989586621679095899Is'''Sym0 :: TyFun (NonEmpty (a6989586621679091332, b6989586621679091335)) (NonEmpty (N, N)) -> Type) (is6989586621679095898 :: NonEmpty (a6989586621679091332, b6989586621679091335)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095899Is'''Sym0 :: TyFun (NonEmpty (a6989586621679091332, b6989586621679091335)) (NonEmpty (N, N)) -> Type) (is6989586621679095898 :: NonEmpty (a6989586621679091332, b6989586621679091335)) = Let6989586621679095899Is'''Sym1 is6989586621679095898
type Apply (Let6989586621679095899Is''Sym0 :: TyFun (NonEmpty (a6989586621679091332, k1)) (NonEmpty (N, k1)) -> Type) (is6989586621679095898 :: NonEmpty (a6989586621679091332, k1)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095899Is''Sym0 :: TyFun (NonEmpty (a6989586621679091332, k1)) (NonEmpty (N, k1)) -> Type) (is6989586621679095898 :: NonEmpty (a6989586621679091332, k1)) = Let6989586621679095899Is''Sym1 is6989586621679095898
type Apply (Let6989586621679095899Is'Sym0 :: TyFun (NonEmpty (a6989586621679091332, b6989586621679091333)) (NonEmpty (N, b6989586621679091333)) -> Type) (is6989586621679095898 :: NonEmpty (a6989586621679091332, b6989586621679091333)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095899Is'Sym0 :: TyFun (NonEmpty (a6989586621679091332, b6989586621679091333)) (NonEmpty (N, b6989586621679091333)) -> Type) (is6989586621679095898 :: NonEmpty (a6989586621679091332, b6989586621679091333)) = Let6989586621679095899Is'Sym1 is6989586621679095898
type Apply (Transpositions'Sym2 a6989586621679096143 a6989586621679096144 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) (a6989586621679096145 :: NonEmpty (Maybe a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Transpositions'Sym2 a6989586621679096143 a6989586621679096144 :: TyFun (NonEmpty (Maybe a)) (Maybe [(N, N)]) -> Type) (a6989586621679096145 :: NonEmpty (Maybe a)) = Transpositions'Sym3 a6989586621679096143 a6989586621679096144 a6989586621679096145
type Apply (TranspositionsSym2 a6989586621679096259 a6989586621679096260 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679096261 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym2 a6989586621679096259 a6989586621679096260 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (a6989586621679096261 :: [(VSpace s n, IList s)]) = TranspositionsSym3 a6989586621679096259 a6989586621679096260 a6989586621679096261
type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym2 vs6989586621679096308 tl6989586621679096309 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679096310 :: [(VSpace s n, IList s)]) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym2 vs6989586621679096308 tl6989586621679096309 :: TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) (r6989586621679096310 :: [(VSpace s n, IList s)]) = Let6989586621679096311Scrutinee_6989586621679091469Sym3 vs6989586621679096308 tl6989586621679096309 r6989586621679096310
type Apply (Let6989586621679095899Go'Sym2 is6989586621679095898 a6989586621679095908 :: TyFun (NonEmpty (a6989586621679091334, b6989586621679091335)) (NonEmpty (a6989586621679091334, N)) -> Type) (a6989586621679095909 :: NonEmpty (a6989586621679091334, b6989586621679091335)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095899Go'Sym2 is6989586621679095898 a6989586621679095908 :: TyFun (NonEmpty (a6989586621679091334, b6989586621679091335)) (NonEmpty (a6989586621679091334, N)) -> Type) (a6989586621679095909 :: NonEmpty (a6989586621679091334, b6989586621679091335)) = Let6989586621679095899Go'Sym3 is6989586621679095898 a6989586621679095908 a6989586621679095909
type Apply (Let6989586621679095899GoSym2 is6989586621679095898 a6989586621679095917 :: TyFun (NonEmpty (a6989586621679091332, b6989586621679091333)) (NonEmpty (N, b6989586621679091333)) -> Type) (a6989586621679095918 :: NonEmpty (a6989586621679091332, b6989586621679091333)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679095899GoSym2 is6989586621679095898 a6989586621679095917 :: TyFun (NonEmpty (a6989586621679091332, b6989586621679091333)) (NonEmpty (N, b6989586621679091333)) -> Type) (a6989586621679095918 :: NonEmpty (a6989586621679091332, b6989586621679091333)) = Let6989586621679095899GoSym3 is6989586621679095898 a6989586621679095917 a6989586621679095918
type Apply (Let6989586621679096149Xs'Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) (xs6989586621679096148 :: NonEmpty a6989586621679091234) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149Xs'Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) (xs6989586621679096148 :: NonEmpty a6989586621679091234) = Let6989586621679096149Xs'Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148
type Apply (Lambda_6989586621679096195Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) (ss6989586621679096197 :: NonEmpty a6989586621679091236) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096195Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) (ss6989586621679096197 :: NonEmpty a6989586621679091236) = Lambda_6989586621679096195Sym4 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 ss6989586621679096197
type Apply (Let6989586621679096149FindSym4 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 a6989586621679096161 :: TyFun (NonEmpty (N, Maybe a6989586621679091235)) (Maybe N) -> Type) (a6989586621679096162 :: NonEmpty (N, Maybe a6989586621679091235)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149FindSym4 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 a6989586621679096161 :: TyFun (NonEmpty (N, Maybe a6989586621679091235)) (Maybe N) -> Type) (a6989586621679096162 :: NonEmpty (N, Maybe a6989586621679091235)) = Let6989586621679096149FindSym5 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 a6989586621679096161 a6989586621679096162
type Apply (Let6989586621679096149Go'Sym4 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 a6989586621679096181 :: TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) (a6989586621679096182 :: NonEmpty a6989586621679091234) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096149Go'Sym4 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 a6989586621679096181 :: TyFun (NonEmpty a6989586621679091234) (NonEmpty (N, a6989586621679091234)) -> Type) (a6989586621679096182 :: NonEmpty a6989586621679091234) = Let6989586621679096149Go'Sym5 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 a6989586621679096181 a6989586621679096182
type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) (a6989586621679095976 :: NonEmpty (a, a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (RelabelTranspositionsSym0 :: TyFun (NonEmpty (a, a)) (IList a ~> Maybe [(N, N)]) -> Type) (a6989586621679095976 :: NonEmpty (a, a)) = RelabelTranspositionsSym1 a6989586621679095976
type Apply (Transpositions'Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> (NonEmpty (Maybe a) ~> Maybe [(N, N)])) -> Type) (a6989586621679096143 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Transpositions'Sym0 :: TyFun (NonEmpty a) (NonEmpty a ~> (NonEmpty (Maybe a) ~> Maybe [(N, N)])) -> Type) (a6989586621679096143 :: NonEmpty a) = Transpositions'Sym1 a6989586621679096143
type Apply (Transpositions'Sym1 a6989586621679096143 :: TyFun (NonEmpty a) (NonEmpty (Maybe a) ~> Maybe [(N, N)]) -> Type) (a6989586621679096144 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

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

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym1 a6989586621679096259 :: TyFun (TransRule s) ([(VSpace s n, IList s)] ~> Maybe [(N, N)]) -> Type) (a6989586621679096260 :: TransRule s) = TranspositionsSym2 a6989586621679096259 a6989586621679096260
type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679096309 :: TransRule s) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308 :: TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) (tl6989586621679096309 :: TransRule s) = Let6989586621679096311Scrutinee_6989586621679091469Sym2 vs6989586621679096308 tl6989586621679096309
type Apply (Lambda_6989586621679096195Sym1 sources6989586621679096146 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) -> Type) -> Type) (targets6989586621679096147 :: NonEmpty a) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096195Sym1 sources6989586621679096146 :: TyFun (NonEmpty a) (TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) -> Type) -> Type) (targets6989586621679096147 :: NonEmpty a) = Lambda_6989586621679096195Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) -> Type
type Apply (Lambda_6989586621679096191Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) (xs6989586621679096148 :: NonEmpty (Maybe k3)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096191Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe k3)) (TyFun k3 (Maybe N) -> Type) -> Type) (xs6989586621679096148 :: NonEmpty (Maybe k3)) = Lambda_6989586621679096191Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148
type Apply (Lambda_6989586621679096195Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) -> Type) (xs6989586621679096148 :: NonEmpty (Maybe a)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096195Sym2 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe a)) (TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type) -> Type) (xs6989586621679096148 :: NonEmpty (Maybe a)) = Lambda_6989586621679096195Sym3 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148 :: TyFun (NonEmpty a6989586621679091236) (Maybe [(a6989586621679091236, N)]) -> Type
type Apply (Lambda_6989586621679096198Sym3 ss6989586621679096197 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) (xs6989586621679096148 :: NonEmpty (Maybe k4)) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Lambda_6989586621679096198Sym3 ss6989586621679096197 sources6989586621679096146 targets6989586621679096147 :: TyFun (NonEmpty (Maybe k4)) (TyFun k4 (Maybe N) -> Type) -> Type) (xs6989586621679096148 :: NonEmpty (Maybe k4)) = Lambda_6989586621679096198Sym4 ss6989586621679096197 sources6989586621679096146 targets6989586621679096147 xs6989586621679096148
type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679096259 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (TranspositionsSym0 :: TyFun (VSpace s n) (TransRule s ~> ([(VSpace s n, IList s)] ~> Maybe [(N, N)])) -> Type) (a6989586621679096259 :: VSpace s n) = TranspositionsSym1 a6989586621679096259
type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679096308 :: VSpace s n) Source # 
Instance details

Defined in Math.Tensor.Safe.TH

type Apply (Let6989586621679096311Scrutinee_6989586621679091469Sym0 :: TyFun (VSpace s n) (TyFun (TransRule s) (TyFun [(VSpace s n, IList s)] (Maybe [(N, N)]) -> Type) -> Type) -> Type) (vs6989586621679096308 :: VSpace s n) = Let6989586621679096311Scrutinee_6989586621679091469Sym1 vs6989586621679096308

Length-typed vector used for tensor construction and also internally.

data Vec :: N -> Type -> Type where Source #

Constructors

VNil :: Vec 'Z a 
VCons :: a -> Vec n a -> Vec ('S n) a 

Instances

Instances details
Eq a => Eq (Vec n a) Source # 
Instance details

Defined in Math.Tensor.Safe.Vector

Methods

(==) :: Vec n a -> Vec n a -> Bool #

(/=) :: Vec n a -> Vec n a -> Bool #

Ord a => Ord (Vec n a) Source # 
Instance details

Defined in Math.Tensor.Safe.Vector

Methods

compare :: Vec n a -> Vec n a -> Ordering #

(<) :: Vec n a -> Vec n a -> Bool #

(<=) :: Vec n a -> Vec n a -> Bool #

(>) :: Vec n a -> Vec n a -> Bool #

(>=) :: Vec n a -> Vec n a -> Bool #

max :: Vec n a -> Vec n a -> Vec n a #

min :: Vec n a -> Vec n a -> Vec n a #

Show a => Show (Vec n a) Source # 
Instance details

Defined in Math.Tensor.Safe.Vector

Methods

showsPrec :: Int -> Vec n a -> ShowS #

show :: Vec n a -> String #

showList :: [Vec n a] -> ShowS #

NFData a => NFData (Vec n a) Source # 
Instance details

Defined in Math.Tensor.Safe.Vector

Methods

rnf :: Vec n a -> () #

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