TensorSpace Rational Source # | |
Instance detailsDefined in Math.LinearMap.Category.Instances Methods scalarSpaceWitness :: ScalarSpaceWitness Rational Source # linearManifoldWitness :: LinearManifoldWitness Rational Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar Rational) => Rational ⊗ w Source # toFlatTensor :: Rational -+> (Rational ⊗ Scalar Rational) Source # fromFlatTensor :: (Rational ⊗ Scalar Rational) -+> Rational Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar Rational) => (Rational ⊗ w) -> (Rational ⊗ w) -> Rational ⊗ w Source # subtractTensors :: (TensorSpace Rational, TensorSpace w, Scalar w ~ Scalar Rational) => (Rational ⊗ w) -> (Rational ⊗ w) -> Rational ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar Rational) => Bilinear (Scalar Rational) (Rational ⊗ w) (Rational ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar Rational) => (Rational ⊗ w) -+> (Rational ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar Rational) => Bilinear Rational w (Rational ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar Rational) => [(Rational, w)] -> Rational ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar Rational) => (Rational ⊗ w) -+> (w ⊗ Rational) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar Rational, Scalar x ~ Scalar Rational) => Bilinear (w -+> x) (Rational ⊗ w) (Rational ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar Rational, Scalar w ~ Scalar Rational, Scalar x ~ Scalar Rational) => Bilinear ((w, x) -+> u) (Rational ⊗ w, Rational ⊗ x) (Rational ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n Rational, TensorSpace w, Dimensional m w, Scalar w ~ Scalar Rational, Vector α (Scalar Rational)) => Int -> α (Scalar Rational) -> Rational ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n Rational, TensorSpace w, Dimensional m w, Scalar w ~ Scalar Rational, Vector α (Scalar Rational)) => Mutable α σ (Scalar Rational) -> Int -> (Rational ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar Rational, TensorSpace b, Scalar b ~ Scalar Rational) => p Rational -> VSCCoercion (Scalar Rational) a b -> Coercion (TensorProduct Rational a) (TensorProduct Rational b) Source # wellDefinedVector :: Rational -> Maybe Rational Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar Rational) => (Rational ⊗ w) -> Maybe (Rational ⊗ w) Source # |
TensorSpace Float Source # | |
Instance detailsDefined in Math.LinearMap.Category.Instances Methods scalarSpaceWitness :: ScalarSpaceWitness Float Source # linearManifoldWitness :: LinearManifoldWitness Float Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar Float) => Float ⊗ w Source # toFlatTensor :: Float -+> (Float ⊗ Scalar Float) Source # fromFlatTensor :: (Float ⊗ Scalar Float) -+> Float Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar Float) => (Float ⊗ w) -> (Float ⊗ w) -> Float ⊗ w Source # subtractTensors :: (TensorSpace Float, TensorSpace w, Scalar w ~ Scalar Float) => (Float ⊗ w) -> (Float ⊗ w) -> Float ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar Float) => Bilinear (Scalar Float) (Float ⊗ w) (Float ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar Float) => (Float ⊗ w) -+> (Float ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar Float) => Bilinear Float w (Float ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar Float) => [(Float, w)] -> Float ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar Float) => (Float ⊗ w) -+> (w ⊗ Float) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar Float, Scalar x ~ Scalar Float) => Bilinear (w -+> x) (Float ⊗ w) (Float ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar Float, Scalar w ~ Scalar Float, Scalar x ~ Scalar Float) => Bilinear ((w, x) -+> u) (Float ⊗ w, Float ⊗ x) (Float ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n Float, TensorSpace w, Dimensional m w, Scalar w ~ Scalar Float, Vector α (Scalar Float)) => Int -> α (Scalar Float) -> Float ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n Float, TensorSpace w, Dimensional m w, Scalar w ~ Scalar Float, Vector α (Scalar Float)) => Mutable α σ (Scalar Float) -> Int -> (Float ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar Float, TensorSpace b, Scalar b ~ Scalar Float) => p Float -> VSCCoercion (Scalar Float) a b -> Coercion (TensorProduct Float a) (TensorProduct Float b) Source # wellDefinedVector :: Float -> Maybe Float Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar Float) => (Float ⊗ w) -> Maybe (Float ⊗ w) Source # |
(Num' n, Unbox n) => TensorSpace (FinSuppSeq n) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Instances Methods scalarSpaceWitness :: ScalarSpaceWitness (FinSuppSeq n) Source # linearManifoldWitness :: LinearManifoldWitness (FinSuppSeq n) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (FinSuppSeq n)) => FinSuppSeq n ⊗ w Source # toFlatTensor :: FinSuppSeq n -+> (FinSuppSeq n ⊗ Scalar (FinSuppSeq n)) Source # fromFlatTensor :: (FinSuppSeq n ⊗ Scalar (FinSuppSeq n)) -+> FinSuppSeq n Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (FinSuppSeq n)) => (FinSuppSeq n ⊗ w) -> (FinSuppSeq n ⊗ w) -> FinSuppSeq n ⊗ w Source # subtractTensors :: (TensorSpace (FinSuppSeq n), TensorSpace w, Scalar w ~ Scalar (FinSuppSeq n)) => (FinSuppSeq n ⊗ w) -> (FinSuppSeq n ⊗ w) -> FinSuppSeq n ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (FinSuppSeq n)) => Bilinear (Scalar (FinSuppSeq n)) (FinSuppSeq n ⊗ w) (FinSuppSeq n ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (FinSuppSeq n)) => (FinSuppSeq n ⊗ w) -+> (FinSuppSeq n ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (FinSuppSeq n)) => Bilinear (FinSuppSeq n) w (FinSuppSeq n ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (FinSuppSeq n)) => [(FinSuppSeq n, w)] -> FinSuppSeq n ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (FinSuppSeq n)) => (FinSuppSeq n ⊗ w) -+> (w ⊗ FinSuppSeq n) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (FinSuppSeq n), Scalar x ~ Scalar (FinSuppSeq n)) => Bilinear (w -+> x) (FinSuppSeq n ⊗ w) (FinSuppSeq n ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (FinSuppSeq n), Scalar w ~ Scalar (FinSuppSeq n), Scalar x ~ Scalar (FinSuppSeq n)) => Bilinear ((w, x) -+> u) (FinSuppSeq n ⊗ w, FinSuppSeq n ⊗ x) (FinSuppSeq n ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n0 :: Nat) (m :: Nat). (Dimensional n0 (FinSuppSeq n), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (FinSuppSeq n), Vector α (Scalar (FinSuppSeq n))) => Int -> α (Scalar (FinSuppSeq n)) -> FinSuppSeq n ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n0 :: Nat) (m :: Nat). (Dimensional n0 (FinSuppSeq n), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (FinSuppSeq n), Vector α (Scalar (FinSuppSeq n))) => Mutable α σ (Scalar (FinSuppSeq n)) -> Int -> (FinSuppSeq n ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (FinSuppSeq n), TensorSpace b, Scalar b ~ Scalar (FinSuppSeq n)) => p (FinSuppSeq n) -> VSCCoercion (Scalar (FinSuppSeq n)) a b -> Coercion (TensorProduct (FinSuppSeq n) a) (TensorProduct (FinSuppSeq n) b) Source # wellDefinedVector :: FinSuppSeq n -> Maybe (FinSuppSeq n) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (FinSuppSeq n)) => (FinSuppSeq n ⊗ w) -> Maybe (FinSuppSeq n ⊗ w) Source # |
(Num' n, Unbox n) => TensorSpace (Sequence n) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Instances Methods scalarSpaceWitness :: ScalarSpaceWitness (Sequence n) Source # linearManifoldWitness :: LinearManifoldWitness (Sequence n) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (Sequence n)) => Sequence n ⊗ w Source # toFlatTensor :: Sequence n -+> (Sequence n ⊗ Scalar (Sequence n)) Source # fromFlatTensor :: (Sequence n ⊗ Scalar (Sequence n)) -+> Sequence n Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (Sequence n)) => (Sequence n ⊗ w) -> (Sequence n ⊗ w) -> Sequence n ⊗ w Source # subtractTensors :: (TensorSpace (Sequence n), TensorSpace w, Scalar w ~ Scalar (Sequence n)) => (Sequence n ⊗ w) -> (Sequence n ⊗ w) -> Sequence n ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (Sequence n)) => Bilinear (Scalar (Sequence n)) (Sequence n ⊗ w) (Sequence n ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (Sequence n)) => (Sequence n ⊗ w) -+> (Sequence n ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (Sequence n)) => Bilinear (Sequence n) w (Sequence n ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (Sequence n)) => [(Sequence n, w)] -> Sequence n ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (Sequence n)) => (Sequence n ⊗ w) -+> (w ⊗ Sequence n) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (Sequence n), Scalar x ~ Scalar (Sequence n)) => Bilinear (w -+> x) (Sequence n ⊗ w) (Sequence n ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (Sequence n), Scalar w ~ Scalar (Sequence n), Scalar x ~ Scalar (Sequence n)) => Bilinear ((w, x) -+> u) (Sequence n ⊗ w, Sequence n ⊗ x) (Sequence n ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n0 :: Nat) (m :: Nat). (Dimensional n0 (Sequence n), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (Sequence n), Vector α (Scalar (Sequence n))) => Int -> α (Scalar (Sequence n)) -> Sequence n ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n0 :: Nat) (m :: Nat). (Dimensional n0 (Sequence n), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (Sequence n), Vector α (Scalar (Sequence n))) => Mutable α σ (Scalar (Sequence n)) -> Int -> (Sequence n ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (Sequence n), TensorSpace b, Scalar b ~ Scalar (Sequence n)) => p (Sequence n) -> VSCCoercion (Scalar (Sequence n)) a b -> Coercion (TensorProduct (Sequence n) a) (TensorProduct (Sequence n) b) Source # wellDefinedVector :: Sequence n -> Maybe (Sequence n) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (Sequence n)) => (Sequence n ⊗ w) -> Maybe (Sequence n ⊗ w) Source # |
(Num' s, Eq s) => TensorSpace (V0 s) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Instances Methods scalarSpaceWitness :: ScalarSpaceWitness (V0 s) Source # linearManifoldWitness :: LinearManifoldWitness (V0 s) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (V0 s)) => V0 s ⊗ w Source # toFlatTensor :: V0 s -+> (V0 s ⊗ Scalar (V0 s)) Source # fromFlatTensor :: (V0 s ⊗ Scalar (V0 s)) -+> V0 s Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (V0 s)) => (V0 s ⊗ w) -> (V0 s ⊗ w) -> V0 s ⊗ w Source # subtractTensors :: (TensorSpace (V0 s), TensorSpace w, Scalar w ~ Scalar (V0 s)) => (V0 s ⊗ w) -> (V0 s ⊗ w) -> V0 s ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (V0 s)) => Bilinear (Scalar (V0 s)) (V0 s ⊗ w) (V0 s ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (V0 s)) => (V0 s ⊗ w) -+> (V0 s ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (V0 s)) => Bilinear (V0 s) w (V0 s ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (V0 s)) => [(V0 s, w)] -> V0 s ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (V0 s)) => (V0 s ⊗ w) -+> (w ⊗ V0 s) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (V0 s), Scalar x ~ Scalar (V0 s)) => Bilinear (w -+> x) (V0 s ⊗ w) (V0 s ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (V0 s), Scalar w ~ Scalar (V0 s), Scalar x ~ Scalar (V0 s)) => Bilinear ((w, x) -+> u) (V0 s ⊗ w, V0 s ⊗ x) (V0 s ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (V0 s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (V0 s), Vector α (Scalar (V0 s))) => Int -> α (Scalar (V0 s)) -> V0 s ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (V0 s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (V0 s), Vector α (Scalar (V0 s))) => Mutable α σ (Scalar (V0 s)) -> Int -> (V0 s ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (V0 s), TensorSpace b, Scalar b ~ Scalar (V0 s)) => p (V0 s) -> VSCCoercion (Scalar (V0 s)) a b -> Coercion (TensorProduct (V0 s) a) (TensorProduct (V0 s) b) Source # wellDefinedVector :: V0 s -> Maybe (V0 s) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (V0 s)) => (V0 s ⊗ w) -> Maybe (V0 s ⊗ w) Source # |
(Num' s, Eq s) => TensorSpace (V1 s) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Instances Methods scalarSpaceWitness :: ScalarSpaceWitness (V1 s) Source # linearManifoldWitness :: LinearManifoldWitness (V1 s) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (V1 s)) => V1 s ⊗ w Source # toFlatTensor :: V1 s -+> (V1 s ⊗ Scalar (V1 s)) Source # fromFlatTensor :: (V1 s ⊗ Scalar (V1 s)) -+> V1 s Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (V1 s)) => (V1 s ⊗ w) -> (V1 s ⊗ w) -> V1 s ⊗ w Source # subtractTensors :: (TensorSpace (V1 s), TensorSpace w, Scalar w ~ Scalar (V1 s)) => (V1 s ⊗ w) -> (V1 s ⊗ w) -> V1 s ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (V1 s)) => Bilinear (Scalar (V1 s)) (V1 s ⊗ w) (V1 s ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (V1 s)) => (V1 s ⊗ w) -+> (V1 s ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (V1 s)) => Bilinear (V1 s) w (V1 s ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (V1 s)) => [(V1 s, w)] -> V1 s ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (V1 s)) => (V1 s ⊗ w) -+> (w ⊗ V1 s) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (V1 s), Scalar x ~ Scalar (V1 s)) => Bilinear (w -+> x) (V1 s ⊗ w) (V1 s ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (V1 s), Scalar w ~ Scalar (V1 s), Scalar x ~ Scalar (V1 s)) => Bilinear ((w, x) -+> u) (V1 s ⊗ w, V1 s ⊗ x) (V1 s ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (V1 s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (V1 s), Vector α (Scalar (V1 s))) => Int -> α (Scalar (V1 s)) -> V1 s ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (V1 s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (V1 s), Vector α (Scalar (V1 s))) => Mutable α σ (Scalar (V1 s)) -> Int -> (V1 s ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (V1 s), TensorSpace b, Scalar b ~ Scalar (V1 s)) => p (V1 s) -> VSCCoercion (Scalar (V1 s)) a b -> Coercion (TensorProduct (V1 s) a) (TensorProduct (V1 s) b) Source # wellDefinedVector :: V1 s -> Maybe (V1 s) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (V1 s)) => (V1 s ⊗ w) -> Maybe (V1 s ⊗ w) Source # |
(Num' s, Eq s) => TensorSpace (V2 s) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Instances Methods scalarSpaceWitness :: ScalarSpaceWitness (V2 s) Source # linearManifoldWitness :: LinearManifoldWitness (V2 s) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (V2 s)) => V2 s ⊗ w Source # toFlatTensor :: V2 s -+> (V2 s ⊗ Scalar (V2 s)) Source # fromFlatTensor :: (V2 s ⊗ Scalar (V2 s)) -+> V2 s Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (V2 s)) => (V2 s ⊗ w) -> (V2 s ⊗ w) -> V2 s ⊗ w Source # subtractTensors :: (TensorSpace (V2 s), TensorSpace w, Scalar w ~ Scalar (V2 s)) => (V2 s ⊗ w) -> (V2 s ⊗ w) -> V2 s ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (V2 s)) => Bilinear (Scalar (V2 s)) (V2 s ⊗ w) (V2 s ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (V2 s)) => (V2 s ⊗ w) -+> (V2 s ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (V2 s)) => Bilinear (V2 s) w (V2 s ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (V2 s)) => [(V2 s, w)] -> V2 s ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (V2 s)) => (V2 s ⊗ w) -+> (w ⊗ V2 s) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (V2 s), Scalar x ~ Scalar (V2 s)) => Bilinear (w -+> x) (V2 s ⊗ w) (V2 s ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (V2 s), Scalar w ~ Scalar (V2 s), Scalar x ~ Scalar (V2 s)) => Bilinear ((w, x) -+> u) (V2 s ⊗ w, V2 s ⊗ x) (V2 s ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (V2 s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (V2 s), Vector α (Scalar (V2 s))) => Int -> α (Scalar (V2 s)) -> V2 s ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (V2 s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (V2 s), Vector α (Scalar (V2 s))) => Mutable α σ (Scalar (V2 s)) -> Int -> (V2 s ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (V2 s), TensorSpace b, Scalar b ~ Scalar (V2 s)) => p (V2 s) -> VSCCoercion (Scalar (V2 s)) a b -> Coercion (TensorProduct (V2 s) a) (TensorProduct (V2 s) b) Source # wellDefinedVector :: V2 s -> Maybe (V2 s) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (V2 s)) => (V2 s ⊗ w) -> Maybe (V2 s ⊗ w) Source # |
(Num' s, Eq s) => TensorSpace (V3 s) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Instances Methods scalarSpaceWitness :: ScalarSpaceWitness (V3 s) Source # linearManifoldWitness :: LinearManifoldWitness (V3 s) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (V3 s)) => V3 s ⊗ w Source # toFlatTensor :: V3 s -+> (V3 s ⊗ Scalar (V3 s)) Source # fromFlatTensor :: (V3 s ⊗ Scalar (V3 s)) -+> V3 s Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (V3 s)) => (V3 s ⊗ w) -> (V3 s ⊗ w) -> V3 s ⊗ w Source # subtractTensors :: (TensorSpace (V3 s), TensorSpace w, Scalar w ~ Scalar (V3 s)) => (V3 s ⊗ w) -> (V3 s ⊗ w) -> V3 s ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (V3 s)) => Bilinear (Scalar (V3 s)) (V3 s ⊗ w) (V3 s ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (V3 s)) => (V3 s ⊗ w) -+> (V3 s ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (V3 s)) => Bilinear (V3 s) w (V3 s ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (V3 s)) => [(V3 s, w)] -> V3 s ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (V3 s)) => (V3 s ⊗ w) -+> (w ⊗ V3 s) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (V3 s), Scalar x ~ Scalar (V3 s)) => Bilinear (w -+> x) (V3 s ⊗ w) (V3 s ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (V3 s), Scalar w ~ Scalar (V3 s), Scalar x ~ Scalar (V3 s)) => Bilinear ((w, x) -+> u) (V3 s ⊗ w, V3 s ⊗ x) (V3 s ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (V3 s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (V3 s), Vector α (Scalar (V3 s))) => Int -> α (Scalar (V3 s)) -> V3 s ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (V3 s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (V3 s), Vector α (Scalar (V3 s))) => Mutable α σ (Scalar (V3 s)) -> Int -> (V3 s ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (V3 s), TensorSpace b, Scalar b ~ Scalar (V3 s)) => p (V3 s) -> VSCCoercion (Scalar (V3 s)) a b -> Coercion (TensorProduct (V3 s) a) (TensorProduct (V3 s) b) Source # wellDefinedVector :: V3 s -> Maybe (V3 s) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (V3 s)) => (V3 s ⊗ w) -> Maybe (V3 s ⊗ w) Source # |
(Num' s, Eq s) => TensorSpace (V4 s) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Instances Methods scalarSpaceWitness :: ScalarSpaceWitness (V4 s) Source # linearManifoldWitness :: LinearManifoldWitness (V4 s) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (V4 s)) => V4 s ⊗ w Source # toFlatTensor :: V4 s -+> (V4 s ⊗ Scalar (V4 s)) Source # fromFlatTensor :: (V4 s ⊗ Scalar (V4 s)) -+> V4 s Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (V4 s)) => (V4 s ⊗ w) -> (V4 s ⊗ w) -> V4 s ⊗ w Source # subtractTensors :: (TensorSpace (V4 s), TensorSpace w, Scalar w ~ Scalar (V4 s)) => (V4 s ⊗ w) -> (V4 s ⊗ w) -> V4 s ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (V4 s)) => Bilinear (Scalar (V4 s)) (V4 s ⊗ w) (V4 s ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (V4 s)) => (V4 s ⊗ w) -+> (V4 s ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (V4 s)) => Bilinear (V4 s) w (V4 s ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (V4 s)) => [(V4 s, w)] -> V4 s ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (V4 s)) => (V4 s ⊗ w) -+> (w ⊗ V4 s) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (V4 s), Scalar x ~ Scalar (V4 s)) => Bilinear (w -+> x) (V4 s ⊗ w) (V4 s ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (V4 s), Scalar w ~ Scalar (V4 s), Scalar x ~ Scalar (V4 s)) => Bilinear ((w, x) -+> u) (V4 s ⊗ w, V4 s ⊗ x) (V4 s ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (V4 s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (V4 s), Vector α (Scalar (V4 s))) => Int -> α (Scalar (V4 s)) -> V4 s ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (V4 s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (V4 s), Vector α (Scalar (V4 s))) => Mutable α σ (Scalar (V4 s)) -> Int -> (V4 s ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (V4 s), TensorSpace b, Scalar b ~ Scalar (V4 s)) => p (V4 s) -> VSCCoercion (Scalar (V4 s)) a b -> Coercion (TensorProduct (V4 s) a) (TensorProduct (V4 s) b) Source # wellDefinedVector :: V4 s -> Maybe (V4 s) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (V4 s)) => (V4 s ⊗ w) -> Maybe (V4 s ⊗ w) Source # |
(Semimanifold m, TensorSpace (Needle (VRep m)), Scalar (Needle m) ~ Scalar (Needle (VRep m))) => TensorSpace (GenericNeedle m) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Class Methods scalarSpaceWitness :: ScalarSpaceWitness (GenericNeedle m) Source # linearManifoldWitness :: LinearManifoldWitness (GenericNeedle m) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (GenericNeedle m)) => GenericNeedle m ⊗ w Source # toFlatTensor :: GenericNeedle m -+> (GenericNeedle m ⊗ Scalar (GenericNeedle m)) Source # fromFlatTensor :: (GenericNeedle m ⊗ Scalar (GenericNeedle m)) -+> GenericNeedle m Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (GenericNeedle m)) => (GenericNeedle m ⊗ w) -> (GenericNeedle m ⊗ w) -> GenericNeedle m ⊗ w Source # subtractTensors :: (TensorSpace (GenericNeedle m), TensorSpace w, Scalar w ~ Scalar (GenericNeedle m)) => (GenericNeedle m ⊗ w) -> (GenericNeedle m ⊗ w) -> GenericNeedle m ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (GenericNeedle m)) => Bilinear (Scalar (GenericNeedle m)) (GenericNeedle m ⊗ w) (GenericNeedle m ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (GenericNeedle m)) => (GenericNeedle m ⊗ w) -+> (GenericNeedle m ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (GenericNeedle m)) => Bilinear (GenericNeedle m) w (GenericNeedle m ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (GenericNeedle m)) => [(GenericNeedle m, w)] -> GenericNeedle m ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (GenericNeedle m)) => (GenericNeedle m ⊗ w) -+> (w ⊗ GenericNeedle m) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (GenericNeedle m), Scalar x ~ Scalar (GenericNeedle m)) => Bilinear (w -+> x) (GenericNeedle m ⊗ w) (GenericNeedle m ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (GenericNeedle m), Scalar w ~ Scalar (GenericNeedle m), Scalar x ~ Scalar (GenericNeedle m)) => Bilinear ((w, x) -+> u) (GenericNeedle m ⊗ w, GenericNeedle m ⊗ x) (GenericNeedle m ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m0 :: Nat). (Dimensional n (GenericNeedle m), TensorSpace w, Dimensional m0 w, Scalar w ~ Scalar (GenericNeedle m), Vector α (Scalar (GenericNeedle m))) => Int -> α (Scalar (GenericNeedle m)) -> GenericNeedle m ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m0 :: Nat). (Dimensional n (GenericNeedle m), TensorSpace w, Dimensional m0 w, Scalar w ~ Scalar (GenericNeedle m), Vector α (Scalar (GenericNeedle m))) => Mutable α σ (Scalar (GenericNeedle m)) -> Int -> (GenericNeedle m ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (GenericNeedle m), TensorSpace b, Scalar b ~ Scalar (GenericNeedle m)) => p (GenericNeedle m) -> VSCCoercion (Scalar (GenericNeedle m)) a b -> Coercion (TensorProduct (GenericNeedle m) a) (TensorProduct (GenericNeedle m) b) Source # wellDefinedVector :: GenericNeedle m -> Maybe (GenericNeedle m) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (GenericNeedle m)) => (GenericNeedle m ⊗ w) -> Maybe (GenericNeedle m ⊗ w) Source # |
Num' s => TensorSpace (ZeroDim s) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Class Methods scalarSpaceWitness :: ScalarSpaceWitness (ZeroDim s) Source # linearManifoldWitness :: LinearManifoldWitness (ZeroDim s) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (ZeroDim s)) => ZeroDim s ⊗ w Source # toFlatTensor :: ZeroDim s -+> (ZeroDim s ⊗ Scalar (ZeroDim s)) Source # fromFlatTensor :: (ZeroDim s ⊗ Scalar (ZeroDim s)) -+> ZeroDim s Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (ZeroDim s)) => (ZeroDim s ⊗ w) -> (ZeroDim s ⊗ w) -> ZeroDim s ⊗ w Source # subtractTensors :: (TensorSpace (ZeroDim s), TensorSpace w, Scalar w ~ Scalar (ZeroDim s)) => (ZeroDim s ⊗ w) -> (ZeroDim s ⊗ w) -> ZeroDim s ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (ZeroDim s)) => Bilinear (Scalar (ZeroDim s)) (ZeroDim s ⊗ w) (ZeroDim s ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (ZeroDim s)) => (ZeroDim s ⊗ w) -+> (ZeroDim s ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (ZeroDim s)) => Bilinear (ZeroDim s) w (ZeroDim s ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (ZeroDim s)) => [(ZeroDim s, w)] -> ZeroDim s ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (ZeroDim s)) => (ZeroDim s ⊗ w) -+> (w ⊗ ZeroDim s) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (ZeroDim s), Scalar x ~ Scalar (ZeroDim s)) => Bilinear (w -+> x) (ZeroDim s ⊗ w) (ZeroDim s ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (ZeroDim s), Scalar w ~ Scalar (ZeroDim s), Scalar x ~ Scalar (ZeroDim s)) => Bilinear ((w, x) -+> u) (ZeroDim s ⊗ w, ZeroDim s ⊗ x) (ZeroDim s ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (ZeroDim s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (ZeroDim s), Vector α (Scalar (ZeroDim s))) => Int -> α (Scalar (ZeroDim s)) -> ZeroDim s ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (ZeroDim s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (ZeroDim s), Vector α (Scalar (ZeroDim s))) => Mutable α σ (Scalar (ZeroDim s)) -> Int -> (ZeroDim s ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (ZeroDim s), TensorSpace b, Scalar b ~ Scalar (ZeroDim s)) => p (ZeroDim s) -> VSCCoercion (Scalar (ZeroDim s)) a b -> Coercion (TensorProduct (ZeroDim s) a) (TensorProduct (ZeroDim s) b) Source # wellDefinedVector :: ZeroDim s -> Maybe (ZeroDim s) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (ZeroDim s)) => (ZeroDim s ⊗ w) -> Maybe (ZeroDim s ⊗ w) Source # |
(Num' s, TensorSpace v, Scalar v ~ s) => TensorSpace (SymmetricTensor s v) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Instances Methods scalarSpaceWitness :: ScalarSpaceWitness (SymmetricTensor s v) Source # linearManifoldWitness :: LinearManifoldWitness (SymmetricTensor s v) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (SymmetricTensor s v)) => SymmetricTensor s v ⊗ w Source # toFlatTensor :: SymmetricTensor s v -+> (SymmetricTensor s v ⊗ Scalar (SymmetricTensor s v)) Source # fromFlatTensor :: (SymmetricTensor s v ⊗ Scalar (SymmetricTensor s v)) -+> SymmetricTensor s v Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (SymmetricTensor s v)) => (SymmetricTensor s v ⊗ w) -> (SymmetricTensor s v ⊗ w) -> SymmetricTensor s v ⊗ w Source # subtractTensors :: (TensorSpace (SymmetricTensor s v), TensorSpace w, Scalar w ~ Scalar (SymmetricTensor s v)) => (SymmetricTensor s v ⊗ w) -> (SymmetricTensor s v ⊗ w) -> SymmetricTensor s v ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (SymmetricTensor s v)) => Bilinear (Scalar (SymmetricTensor s v)) (SymmetricTensor s v ⊗ w) (SymmetricTensor s v ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (SymmetricTensor s v)) => (SymmetricTensor s v ⊗ w) -+> (SymmetricTensor s v ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (SymmetricTensor s v)) => Bilinear (SymmetricTensor s v) w (SymmetricTensor s v ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (SymmetricTensor s v)) => [(SymmetricTensor s v, w)] -> SymmetricTensor s v ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (SymmetricTensor s v)) => (SymmetricTensor s v ⊗ w) -+> (w ⊗ SymmetricTensor s v) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (SymmetricTensor s v), Scalar x ~ Scalar (SymmetricTensor s v)) => Bilinear (w -+> x) (SymmetricTensor s v ⊗ w) (SymmetricTensor s v ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (SymmetricTensor s v), Scalar w ~ Scalar (SymmetricTensor s v), Scalar x ~ Scalar (SymmetricTensor s v)) => Bilinear ((w, x) -+> u) (SymmetricTensor s v ⊗ w, SymmetricTensor s v ⊗ x) (SymmetricTensor s v ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (SymmetricTensor s v), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (SymmetricTensor s v), Vector α (Scalar (SymmetricTensor s v))) => Int -> α (Scalar (SymmetricTensor s v)) -> SymmetricTensor s v ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (SymmetricTensor s v), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (SymmetricTensor s v), Vector α (Scalar (SymmetricTensor s v))) => Mutable α σ (Scalar (SymmetricTensor s v)) -> Int -> (SymmetricTensor s v ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (SymmetricTensor s v), TensorSpace b, Scalar b ~ Scalar (SymmetricTensor s v)) => p (SymmetricTensor s v) -> VSCCoercion (Scalar (SymmetricTensor s v)) a b -> Coercion (TensorProduct (SymmetricTensor s v) a) (TensorProduct (SymmetricTensor s v) b) Source # wellDefinedVector :: SymmetricTensor s v -> Maybe (SymmetricTensor s v) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (SymmetricTensor s v)) => (SymmetricTensor s v ⊗ w) -> Maybe (SymmetricTensor s v ⊗ w) Source # |
(TensorSpace u, TensorSpace v, Scalar u ~ Scalar v) => TensorSpace (u, v) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Class Methods scalarSpaceWitness :: ScalarSpaceWitness (u, v) Source # linearManifoldWitness :: LinearManifoldWitness (u, v) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (u, v)) => (u, v) ⊗ w Source # toFlatTensor :: (u, v) -+> ((u, v) ⊗ Scalar (u, v)) Source # fromFlatTensor :: ((u, v) ⊗ Scalar (u, v)) -+> (u, v) Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (u, v)) => ((u, v) ⊗ w) -> ((u, v) ⊗ w) -> (u, v) ⊗ w Source # subtractTensors :: (TensorSpace (u, v), TensorSpace w, Scalar w ~ Scalar (u, v)) => ((u, v) ⊗ w) -> ((u, v) ⊗ w) -> (u, v) ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (u, v)) => Bilinear (Scalar (u, v)) ((u, v) ⊗ w) ((u, v) ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (u, v)) => ((u, v) ⊗ w) -+> ((u, v) ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (u, v)) => Bilinear (u, v) w ((u, v) ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (u, v)) => [((u, v), w)] -> (u, v) ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (u, v)) => ((u, v) ⊗ w) -+> (w ⊗ (u, v)) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (u, v), Scalar x ~ Scalar (u, v)) => Bilinear (w -+> x) ((u, v) ⊗ w) ((u, v) ⊗ x) Source # fzipTensorWith :: (TensorSpace u0, TensorSpace w, TensorSpace x, Scalar u0 ~ Scalar (u, v), Scalar w ~ Scalar (u, v), Scalar x ~ Scalar (u, v)) => Bilinear ((w, x) -+> u0) ((u, v) ⊗ w, (u, v) ⊗ x) ((u, v) ⊗ u0) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (u, v), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (u, v), Vector α (Scalar (u, v))) => Int -> α (Scalar (u, v)) -> (u, v) ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (u, v), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (u, v), Vector α (Scalar (u, v))) => Mutable α σ (Scalar (u, v)) -> Int -> ((u, v) ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (u, v), TensorSpace b, Scalar b ~ Scalar (u, v)) => p (u, v) -> VSCCoercion (Scalar (u, v)) a b -> Coercion (TensorProduct (u, v) a) (TensorProduct (u, v) b) Source # wellDefinedVector :: (u, v) -> Maybe (u, v) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (u, v)) => ((u, v) ⊗ w) -> Maybe ((u, v) ⊗ w) Source # |
TensorSpace v => TensorSpace (Rec0 v s) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Class Methods scalarSpaceWitness :: ScalarSpaceWitness (Rec0 v s) Source # linearManifoldWitness :: LinearManifoldWitness (Rec0 v s) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (Rec0 v s)) => Rec0 v s ⊗ w Source # toFlatTensor :: Rec0 v s -+> (Rec0 v s ⊗ Scalar (Rec0 v s)) Source # fromFlatTensor :: (Rec0 v s ⊗ Scalar (Rec0 v s)) -+> Rec0 v s Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (Rec0 v s)) => (Rec0 v s ⊗ w) -> (Rec0 v s ⊗ w) -> Rec0 v s ⊗ w Source # subtractTensors :: (TensorSpace (Rec0 v s), TensorSpace w, Scalar w ~ Scalar (Rec0 v s)) => (Rec0 v s ⊗ w) -> (Rec0 v s ⊗ w) -> Rec0 v s ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (Rec0 v s)) => Bilinear (Scalar (Rec0 v s)) (Rec0 v s ⊗ w) (Rec0 v s ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (Rec0 v s)) => (Rec0 v s ⊗ w) -+> (Rec0 v s ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (Rec0 v s)) => Bilinear (Rec0 v s) w (Rec0 v s ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (Rec0 v s)) => [(Rec0 v s, w)] -> Rec0 v s ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (Rec0 v s)) => (Rec0 v s ⊗ w) -+> (w ⊗ Rec0 v s) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (Rec0 v s), Scalar x ~ Scalar (Rec0 v s)) => Bilinear (w -+> x) (Rec0 v s ⊗ w) (Rec0 v s ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (Rec0 v s), Scalar w ~ Scalar (Rec0 v s), Scalar x ~ Scalar (Rec0 v s)) => Bilinear ((w, x) -+> u) (Rec0 v s ⊗ w, Rec0 v s ⊗ x) (Rec0 v s ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (Rec0 v s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (Rec0 v s), Vector α (Scalar (Rec0 v s))) => Int -> α (Scalar (Rec0 v s)) -> Rec0 v s ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (Rec0 v s), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (Rec0 v s), Vector α (Scalar (Rec0 v s))) => Mutable α σ (Scalar (Rec0 v s)) -> Int -> (Rec0 v s ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (Rec0 v s), TensorSpace b, Scalar b ~ Scalar (Rec0 v s)) => p (Rec0 v s) -> VSCCoercion (Scalar (Rec0 v s)) a b -> Coercion (TensorProduct (Rec0 v s) a) (TensorProduct (Rec0 v s) b) Source # wellDefinedVector :: Rec0 v s -> Maybe (Rec0 v s) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (Rec0 v s)) => (Rec0 v s ⊗ w) -> Maybe (Rec0 v s ⊗ w) Source # |
(LinearSpace u, LinearSpace v, Scalar u ~ s, Scalar v ~ s) => TensorSpace (LinearFunction s u v) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Class Methods scalarSpaceWitness :: ScalarSpaceWitness (LinearFunction s u v) Source # linearManifoldWitness :: LinearManifoldWitness (LinearFunction s u v) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (LinearFunction s u v)) => LinearFunction s u v ⊗ w Source # toFlatTensor :: LinearFunction s u v -+> (LinearFunction s u v ⊗ Scalar (LinearFunction s u v)) Source # fromFlatTensor :: (LinearFunction s u v ⊗ Scalar (LinearFunction s u v)) -+> LinearFunction s u v Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (LinearFunction s u v)) => (LinearFunction s u v ⊗ w) -> (LinearFunction s u v ⊗ w) -> LinearFunction s u v ⊗ w Source # subtractTensors :: (TensorSpace (LinearFunction s u v), TensorSpace w, Scalar w ~ Scalar (LinearFunction s u v)) => (LinearFunction s u v ⊗ w) -> (LinearFunction s u v ⊗ w) -> LinearFunction s u v ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (LinearFunction s u v)) => Bilinear (Scalar (LinearFunction s u v)) (LinearFunction s u v ⊗ w) (LinearFunction s u v ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (LinearFunction s u v)) => (LinearFunction s u v ⊗ w) -+> (LinearFunction s u v ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (LinearFunction s u v)) => Bilinear (LinearFunction s u v) w (LinearFunction s u v ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (LinearFunction s u v)) => [(LinearFunction s u v, w)] -> LinearFunction s u v ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (LinearFunction s u v)) => (LinearFunction s u v ⊗ w) -+> (w ⊗ LinearFunction s u v) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (LinearFunction s u v), Scalar x ~ Scalar (LinearFunction s u v)) => Bilinear (w -+> x) (LinearFunction s u v ⊗ w) (LinearFunction s u v ⊗ x) Source # fzipTensorWith :: (TensorSpace u0, TensorSpace w, TensorSpace x, Scalar u0 ~ Scalar (LinearFunction s u v), Scalar w ~ Scalar (LinearFunction s u v), Scalar x ~ Scalar (LinearFunction s u v)) => Bilinear ((w, x) -+> u0) (LinearFunction s u v ⊗ w, LinearFunction s u v ⊗ x) (LinearFunction s u v ⊗ u0) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (LinearFunction s u v), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (LinearFunction s u v), Vector α (Scalar (LinearFunction s u v))) => Int -> α (Scalar (LinearFunction s u v)) -> LinearFunction s u v ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (LinearFunction s u v), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (LinearFunction s u v), Vector α (Scalar (LinearFunction s u v))) => Mutable α σ (Scalar (LinearFunction s u v)) -> Int -> (LinearFunction s u v ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (LinearFunction s u v), TensorSpace b, Scalar b ~ Scalar (LinearFunction s u v)) => p (LinearFunction s u v) -> VSCCoercion (Scalar (LinearFunction s u v)) a b -> Coercion (TensorProduct (LinearFunction s u v) a) (TensorProduct (LinearFunction s u v) b) Source # wellDefinedVector :: LinearFunction s u v -> Maybe (LinearFunction s u v) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (LinearFunction s u v)) => (LinearFunction s u v ⊗ w) -> Maybe (LinearFunction s u v ⊗ w) Source # |
(LinearSpace u, TensorSpace v, Scalar u ~ s, Scalar v ~ s) => TensorSpace (LinearMap s u v) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Class Methods scalarSpaceWitness :: ScalarSpaceWitness (LinearMap s u v) Source # linearManifoldWitness :: LinearManifoldWitness (LinearMap s u v) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (LinearMap s u v)) => LinearMap s u v ⊗ w Source # toFlatTensor :: LinearMap s u v -+> (LinearMap s u v ⊗ Scalar (LinearMap s u v)) Source # fromFlatTensor :: (LinearMap s u v ⊗ Scalar (LinearMap s u v)) -+> LinearMap s u v Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (LinearMap s u v)) => (LinearMap s u v ⊗ w) -> (LinearMap s u v ⊗ w) -> LinearMap s u v ⊗ w Source # subtractTensors :: (TensorSpace (LinearMap s u v), TensorSpace w, Scalar w ~ Scalar (LinearMap s u v)) => (LinearMap s u v ⊗ w) -> (LinearMap s u v ⊗ w) -> LinearMap s u v ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (LinearMap s u v)) => Bilinear (Scalar (LinearMap s u v)) (LinearMap s u v ⊗ w) (LinearMap s u v ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (LinearMap s u v)) => (LinearMap s u v ⊗ w) -+> (LinearMap s u v ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (LinearMap s u v)) => Bilinear (LinearMap s u v) w (LinearMap s u v ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (LinearMap s u v)) => [(LinearMap s u v, w)] -> LinearMap s u v ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (LinearMap s u v)) => (LinearMap s u v ⊗ w) -+> (w ⊗ LinearMap s u v) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (LinearMap s u v), Scalar x ~ Scalar (LinearMap s u v)) => Bilinear (w -+> x) (LinearMap s u v ⊗ w) (LinearMap s u v ⊗ x) Source # fzipTensorWith :: (TensorSpace u0, TensorSpace w, TensorSpace x, Scalar u0 ~ Scalar (LinearMap s u v), Scalar w ~ Scalar (LinearMap s u v), Scalar x ~ Scalar (LinearMap s u v)) => Bilinear ((w, x) -+> u0) (LinearMap s u v ⊗ w, LinearMap s u v ⊗ x) (LinearMap s u v ⊗ u0) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (LinearMap s u v), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (LinearMap s u v), Vector α (Scalar (LinearMap s u v))) => Int -> α (Scalar (LinearMap s u v)) -> LinearMap s u v ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (LinearMap s u v), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (LinearMap s u v), Vector α (Scalar (LinearMap s u v))) => Mutable α σ (Scalar (LinearMap s u v)) -> Int -> (LinearMap s u v ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (LinearMap s u v), TensorSpace b, Scalar b ~ Scalar (LinearMap s u v)) => p (LinearMap s u v) -> VSCCoercion (Scalar (LinearMap s u v)) a b -> Coercion (TensorProduct (LinearMap s u v) a) (TensorProduct (LinearMap s u v) b) Source # wellDefinedVector :: LinearMap s u v -> Maybe (LinearMap s u v) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (LinearMap s u v)) => (LinearMap s u v ⊗ w) -> Maybe (LinearMap s u v ⊗ w) Source # |
(TensorSpace u, TensorSpace v, Scalar u ~ s, Scalar v ~ s) => TensorSpace (Tensor s u v) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Class Methods scalarSpaceWitness :: ScalarSpaceWitness (Tensor s u v) Source # linearManifoldWitness :: LinearManifoldWitness (Tensor s u v) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (Tensor s u v)) => Tensor s u v ⊗ w Source # toFlatTensor :: Tensor s u v -+> (Tensor s u v ⊗ Scalar (Tensor s u v)) Source # fromFlatTensor :: (Tensor s u v ⊗ Scalar (Tensor s u v)) -+> Tensor s u v Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (Tensor s u v)) => (Tensor s u v ⊗ w) -> (Tensor s u v ⊗ w) -> Tensor s u v ⊗ w Source # subtractTensors :: (TensorSpace (Tensor s u v), TensorSpace w, Scalar w ~ Scalar (Tensor s u v)) => (Tensor s u v ⊗ w) -> (Tensor s u v ⊗ w) -> Tensor s u v ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (Tensor s u v)) => Bilinear (Scalar (Tensor s u v)) (Tensor s u v ⊗ w) (Tensor s u v ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (Tensor s u v)) => (Tensor s u v ⊗ w) -+> (Tensor s u v ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (Tensor s u v)) => Bilinear (Tensor s u v) w (Tensor s u v ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (Tensor s u v)) => [(Tensor s u v, w)] -> Tensor s u v ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (Tensor s u v)) => (Tensor s u v ⊗ w) -+> (w ⊗ Tensor s u v) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (Tensor s u v), Scalar x ~ Scalar (Tensor s u v)) => Bilinear (w -+> x) (Tensor s u v ⊗ w) (Tensor s u v ⊗ x) Source # fzipTensorWith :: (TensorSpace u0, TensorSpace w, TensorSpace x, Scalar u0 ~ Scalar (Tensor s u v), Scalar w ~ Scalar (Tensor s u v), Scalar x ~ Scalar (Tensor s u v)) => Bilinear ((w, x) -+> u0) (Tensor s u v ⊗ w, Tensor s u v ⊗ x) (Tensor s u v ⊗ u0) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (Tensor s u v), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (Tensor s u v), Vector α (Scalar (Tensor s u v))) => Int -> α (Scalar (Tensor s u v)) -> Tensor s u v ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (Tensor s u v), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (Tensor s u v), Vector α (Scalar (Tensor s u v))) => Mutable α σ (Scalar (Tensor s u v)) -> Int -> (Tensor s u v ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p, TensorSpace a, Scalar a ~ Scalar (Tensor s u v), TensorSpace b, Scalar b ~ Scalar (Tensor s u v)) => p (Tensor s u v) -> VSCCoercion (Scalar (Tensor s u v)) a b -> Coercion (TensorProduct (Tensor s u v) a) (TensorProduct (Tensor s u v) b) Source # wellDefinedVector :: Tensor s u v -> Maybe (Tensor s u v) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (Tensor s u v)) => (Tensor s u v ⊗ w) -> Maybe (Tensor s u v ⊗ w) Source # |
(TensorSpace (f p), TensorSpace (g p), Scalar (f p) ~ Scalar (g p)) => TensorSpace ((f :*: g) p) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Class Methods scalarSpaceWitness :: ScalarSpaceWitness ((f :*: g) p) Source # linearManifoldWitness :: LinearManifoldWitness ((f :*: g) p) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar ((f :*: g) p)) => (f :*: g) p ⊗ w Source # toFlatTensor :: (f :*: g) p -+> ((f :*: g) p ⊗ Scalar ((f :*: g) p)) Source # fromFlatTensor :: ((f :*: g) p ⊗ Scalar ((f :*: g) p)) -+> (f :*: g) p Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar ((f :*: g) p)) => ((f :*: g) p ⊗ w) -> ((f :*: g) p ⊗ w) -> (f :*: g) p ⊗ w Source # subtractTensors :: (TensorSpace ((f :*: g) p), TensorSpace w, Scalar w ~ Scalar ((f :*: g) p)) => ((f :*: g) p ⊗ w) -> ((f :*: g) p ⊗ w) -> (f :*: g) p ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar ((f :*: g) p)) => Bilinear (Scalar ((f :*: g) p)) ((f :*: g) p ⊗ w) ((f :*: g) p ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar ((f :*: g) p)) => ((f :*: g) p ⊗ w) -+> ((f :*: g) p ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar ((f :*: g) p)) => Bilinear ((f :*: g) p) w ((f :*: g) p ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar ((f :*: g) p)) => [((f :*: g) p, w)] -> (f :*: g) p ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar ((f :*: g) p)) => ((f :*: g) p ⊗ w) -+> (w ⊗ (f :*: g) p) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar ((f :*: g) p), Scalar x ~ Scalar ((f :*: g) p)) => Bilinear (w -+> x) ((f :*: g) p ⊗ w) ((f :*: g) p ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar ((f :*: g) p), Scalar w ~ Scalar ((f :*: g) p), Scalar x ~ Scalar ((f :*: g) p)) => Bilinear ((w, x) -+> u) ((f :*: g) p ⊗ w, (f :*: g) p ⊗ x) ((f :*: g) p ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n ((f :*: g) p), TensorSpace w, Dimensional m w, Scalar w ~ Scalar ((f :*: g) p), Vector α (Scalar ((f :*: g) p))) => Int -> α (Scalar ((f :*: g) p)) -> (f :*: g) p ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n ((f :*: g) p), TensorSpace w, Dimensional m w, Scalar w ~ Scalar ((f :*: g) p), Vector α (Scalar ((f :*: g) p))) => Mutable α σ (Scalar ((f :*: g) p)) -> Int -> ((f :*: g) p ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p0, TensorSpace a, Scalar a ~ Scalar ((f :*: g) p), TensorSpace b, Scalar b ~ Scalar ((f :*: g) p)) => p0 ((f :*: g) p) -> VSCCoercion (Scalar ((f :*: g) p)) a b -> Coercion (TensorProduct ((f :*: g) p) a) (TensorProduct ((f :*: g) p) b) Source # wellDefinedVector :: (f :*: g) p -> Maybe ((f :*: g) p) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar ((f :*: g) p)) => ((f :*: g) p ⊗ w) -> Maybe ((f :*: g) p ⊗ w) Source # |
TensorSpace (f p) => TensorSpace (M1 i c f p) Source # | |
Instance detailsDefined in Math.LinearMap.Category.Class Methods scalarSpaceWitness :: ScalarSpaceWitness (M1 i c f p) Source # linearManifoldWitness :: LinearManifoldWitness (M1 i c f p) Source # zeroTensor :: (TensorSpace w, Scalar w ~ Scalar (M1 i c f p)) => M1 i c f p ⊗ w Source # toFlatTensor :: M1 i c f p -+> (M1 i c f p ⊗ Scalar (M1 i c f p)) Source # fromFlatTensor :: (M1 i c f p ⊗ Scalar (M1 i c f p)) -+> M1 i c f p Source # addTensors :: (TensorSpace w, Scalar w ~ Scalar (M1 i c f p)) => (M1 i c f p ⊗ w) -> (M1 i c f p ⊗ w) -> M1 i c f p ⊗ w Source # subtractTensors :: (TensorSpace (M1 i c f p), TensorSpace w, Scalar w ~ Scalar (M1 i c f p)) => (M1 i c f p ⊗ w) -> (M1 i c f p ⊗ w) -> M1 i c f p ⊗ w Source # scaleTensor :: (TensorSpace w, Scalar w ~ Scalar (M1 i c f p)) => Bilinear (Scalar (M1 i c f p)) (M1 i c f p ⊗ w) (M1 i c f p ⊗ w) Source # negateTensor :: (TensorSpace w, Scalar w ~ Scalar (M1 i c f p)) => (M1 i c f p ⊗ w) -+> (M1 i c f p ⊗ w) Source # tensorProduct :: (TensorSpace w, Scalar w ~ Scalar (M1 i c f p)) => Bilinear (M1 i c f p) w (M1 i c f p ⊗ w) Source # tensorProducts :: (TensorSpace w, Scalar w ~ Scalar (M1 i c f p)) => [(M1 i c f p, w)] -> M1 i c f p ⊗ w Source # transposeTensor :: (TensorSpace w, Scalar w ~ Scalar (M1 i c f p)) => (M1 i c f p ⊗ w) -+> (w ⊗ M1 i c f p) Source # fmapTensor :: (TensorSpace w, TensorSpace x, Scalar w ~ Scalar (M1 i c f p), Scalar x ~ Scalar (M1 i c f p)) => Bilinear (w -+> x) (M1 i c f p ⊗ w) (M1 i c f p ⊗ x) Source # fzipTensorWith :: (TensorSpace u, TensorSpace w, TensorSpace x, Scalar u ~ Scalar (M1 i c f p), Scalar w ~ Scalar (M1 i c f p), Scalar x ~ Scalar (M1 i c f p)) => Bilinear ((w, x) -+> u) (M1 i c f p ⊗ w, M1 i c f p ⊗ x) (M1 i c f p ⊗ u) Source # tensorUnsafeFromArrayWithOffset :: forall w α (n :: Nat) (m :: Nat). (Dimensional n (M1 i c f p), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (M1 i c f p), Vector α (Scalar (M1 i c f p))) => Int -> α (Scalar (M1 i c f p)) -> M1 i c f p ⊗ w Source # tensorUnsafeWriteArrayWithOffset :: forall w (α :: Type -> Type) σ (n :: Nat) (m :: Nat). (Dimensional n (M1 i c f p), TensorSpace w, Dimensional m w, Scalar w ~ Scalar (M1 i c f p), Vector α (Scalar (M1 i c f p))) => Mutable α σ (Scalar (M1 i c f p)) -> Int -> (M1 i c f p ⊗ w) -> ST σ () Source # coerceFmapTensorProduct :: (Functor p0, TensorSpace a, Scalar a ~ Scalar (M1 i c f p), TensorSpace b, Scalar b ~ Scalar (M1 i c f p)) => p0 (M1 i c f p) -> VSCCoercion (Scalar (M1 i c f p)) a b -> Coercion (TensorProduct (M1 i c f p) a) (TensorProduct (M1 i c f p) b) Source # wellDefinedVector :: M1 i c f p -> Maybe (M1 i c f p) Source # wellDefinedTensor :: (TensorSpace w, Scalar w ~ Scalar (M1 i c f p)) => (M1 i c f p ⊗ w) -> Maybe (M1 i c f p ⊗ w) Source # |