Safe Haskell | None |
---|---|
Language | GHC2024 |
HordeAd.Core.Ops
Description
A collection of classes containing array operations, with some extra algebraic operations and dual numbers operations added in.
Note that Ast*
modules rarely depend on Ops*
and Carriers*
modules
(except for HordeAd.Core.AstInterpret and HordeAd.Core.AstEnv
that describe how to go from Ast*
to Ops*
). Similarly, Ops*
and Carriers*
modules rarely depend on Ast*
modules
(except for HordeAd.Core.OpsAst and HordeAd.Core.CarriersAst
that describe how to define Ops*
in terms of Ast*
).
Syntax is relatively separated from semantics and they meet
in the interpreter (HordeAd.Core.AstInterpret)
and in the semantic model constructed from syntax (HordeAd.Core.OpsAst).
(A copy of the text above is in HordeAd.Core.Ast.)
Synopsis
- class LetTensor (target :: Target) where
- ttlet :: forall (x :: TK) (z :: TK). target x -> (target x -> target z) -> target z
- ttletPrimal :: forall (x :: TK) (z :: TK). PrimalOf target x -> (PrimalOf target x -> target z) -> target z
- toShare :: forall (y :: TK). target y -> ShareOf target y
- tunshare :: forall (y :: TK). ShareOf target y -> target y
- tappend :: forall (m :: Nat) (n :: Nat) (y :: TK). BaseTensor target => SNat m -> SNat n -> SingletonTK y -> target (BuildTensorKind m y) -> target (BuildTensorKind n y) -> target (BuildTensorKind (m + n) y)
- tD :: forall (y :: TK). BaseTensor target => SingletonTK y -> PrimalOf target y -> DualOf target y -> target y
- tfold :: forall (yn :: TK) (ym :: TK) (k :: Nat). BaseTensor target => SNat k -> SingletonTK yn -> SingletonTK ym -> (forall (f :: Target). ADReady f => f yn -> f ym -> f yn) -> target yn -> target (BuildTensorKind k ym) -> target yn
- tscan :: forall (yn :: TK) (ym :: TK) (k :: Nat). BaseTensor target => SNat k -> SingletonTK yn -> SingletonTK ym -> (forall (f :: Target). ADReady f => f yn -> f ym -> f yn) -> target yn -> target (BuildTensorKind k ym) -> target (BuildTensorKind (1 + k) yn)
- class ShareTensor (target :: Target) where
- tshare :: forall (y :: TK). target y -> target y
- tunpair :: forall (x :: TK) (z :: TK). target ('TKProduct x z) -> (target x, target z)
- tunravelToListShare :: forall (y :: TK) (k :: Nat). (BaseTensor target, ConvertTensor target) => SNat k -> SingletonTK y -> target (BuildTensorKind k y) -> [target y]
- class (Num (IntOf target), IntegralH (IntOf target), TensorSupports Num Num target, TensorSupports RealFloatAndFloatElt Floating target, TensorSupports RealFloatAndFloatElt RealFloatH target, TensorSupports IntegralHAndIntElt IntegralH target, TensorSupportsR Num Num target, TensorSupportsR RealFloatAndFloatElt Floating target, TensorSupportsR RealFloatAndFloatElt RealFloatH target, TensorSupportsR IntegralHAndIntElt IntegralH target, TensorSupportsS Num Num target, TensorSupportsS RealFloatAndFloatElt Floating target, TensorSupportsS RealFloatAndFloatElt RealFloatH target, TensorSupportsS IntegralHAndIntElt IntegralH target, TensorSupportsX Num Num target, TensorSupportsX RealFloatAndFloatElt Floating target, TensorSupportsX RealFloatAndFloatElt RealFloatH target, TensorSupportsX IntegralHAndIntElt IntegralH target) => BaseTensor (target :: Target) where
- rshape :: forall (n :: Nat) (x :: TK). KnownSTK x => target ('TKR2 n x) -> IShR n
- rlength :: forall (n :: Nat) (x :: TK). KnownSTK x => target ('TKR2 n x) -> Int
- rsize :: forall (n :: Nat) (x :: TK). KnownSTK x => target ('TKR2 n x) -> Int
- rwidth :: forall (n :: Natural) (x :: TK). KnownSTK x => target ('TKR2 (1 + n) x) -> Int
- sshape :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 sh x) -> ShS sh
- slength :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 sh x) -> Int
- ssize :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 sh x) -> Int
- swidth :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 (n ': sh) x) -> Int
- xshape :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 sh x) -> IShX sh
- xlength :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 sh x) -> Int
- xsize :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 sh x) -> Int
- xwidth :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 (mn ': sh) x) -> Int
- tsize :: forall (y :: TK). SingletonTK y -> target y -> Int
- tftk :: forall (y :: TK). SingletonTK y -> target y -> FullShapeTK y
- tpair :: forall (x :: TK) (z :: TK). target x -> target z -> target ('TKProduct x z)
- tproject1 :: forall (x :: TK) (z :: TK). target ('TKProduct x z) -> target x
- tproject2 :: forall (x :: TK) (z :: TK). target ('TKProduct x z) -> target z
- tcond :: forall (y :: TK). Boolean (BoolOf target) => SingletonTK y -> BoolOf target -> target y -> target y -> target y
- trconcrete :: forall r (n :: Nat). GoodScalar r => Ranked n r -> target (TKR n r)
- tsconcrete :: forall r (sh :: [Nat]). GoodScalar r => Shaped sh r -> target (TKS sh r)
- txconcrete :: forall r (sh :: [Maybe Nat]). GoodScalar r => Mixed sh r -> target (TKX sh r)
- tkconcrete :: GoodScalar r => r -> target ('TKScalar r)
- tconcrete :: forall (y :: TK). FullShapeTK y -> Concrete y -> target y
- trfromVector :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Vector (target ('TKR2 n x)) -> target ('TKR2 (1 + n) x)
- trfromVector0N :: forall (n :: Nat) (x :: TK). KnownSTK x => IShR n -> Vector (target ('TKR2 0 x)) -> target ('TKR2 n x)
- trunravelToList :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => target ('TKR2 (1 + n) x) -> [target ('TKR2 n x)]
- tsfromVector :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => Vector (target ('TKS2 sh x)) -> target ('TKS2 (n ': sh) x)
- tsfromVector0N :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => Vector (target ('TKS2 ('[] :: [Nat]) x)) -> target ('TKS2 sh x)
- tsunravelToList :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => target ('TKS2 (n ': sh) x) -> [target ('TKS2 sh x)]
- txfromVector :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => Vector (target ('TKX2 sh x)) -> target ('TKX2 ('Just n ': sh) x)
- txfromVector0N :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh -> Vector (target ('TKX2 ('[] :: [Maybe Nat]) x)) -> target ('TKX2 sh x)
- txunravelToList :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => target ('TKX2 ('Just n ': sh) x) -> [target ('TKX2 sh x)]
- tfromVector :: forall (y :: TK) (k :: Nat). SNat k -> SingletonTK y -> Vector (target y) -> target (BuildTensorKind k y)
- tfromListR :: forall (y :: TK) (k :: Nat). SingletonTK y -> ListR k (target y) -> target (BuildTensorKind k y)
- trsum :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => target ('TKR2 (1 + n) x) -> target ('TKR2 n x)
- trsum0 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => target ('TKR2 n x) -> target ('TKR2 0 x)
- trdot0 :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => target (TKR n r) -> target (TKR n r) -> target (TKR 0 r)
- trdot1In :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => target (TKR (1 + n) r) -> target (TKR (1 + n) r) -> target (TKR n r)
- trmatvecmul :: GoodScalar r => target (TKR 2 r) -> target (TKR 1 r) -> target (TKR 1 r)
- trmatmul2 :: GoodScalar r => target (TKR 2 r) -> target (TKR 2 r) -> target (TKR 2 r)
- trreplicate :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> target ('TKR2 n x) -> target ('TKR2 (1 + n) x)
- trreplicate0N :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => IShR n -> target ('TKR2 0 x) -> target ('TKR2 n x)
- tssum :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => target ('TKS2 (n ': sh) x) -> target ('TKS2 sh x)
- tssum0 :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => target ('TKS2 sh x) -> target ('TKS2 ('[] :: [Nat]) x)
- tsdot0 :: forall (sh :: [Nat]) r. (KnownShS sh, GoodScalar r) => target (TKS sh r) -> target (TKS sh r) -> target (TKS ('[] :: [Nat]) r)
- tsdot1In :: forall (sh :: [Nat]) r (n :: Nat). (KnownShS sh, GoodScalar r) => SNat n -> target (TKS (sh ++ '[n]) r) -> target (TKS (sh ++ '[n]) r) -> target (TKS sh r)
- tsmatvecmul :: forall (m :: Nat) (n :: Nat) r. (KnownNat m, KnownNat n, GoodScalar r) => target (TKS '[m, n] r) -> target (TKS '[n] r) -> target (TKS '[m] r)
- tsmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r) => target (TKS '[m, n] r) -> target (TKS '[n, p] r) -> target (TKS '[m, p] r)
- tsreplicate :: forall (sh :: [Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> ShS sh -> target ('TKS2 sh x) -> target ('TKS2 (k ': sh) x)
- tsreplicate0N :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => ShS sh -> target ('TKS2 ('[] :: [Nat]) x) -> target ('TKS2 sh x)
- txsum :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => target ('TKX2 ('Just n ': sh) x) -> target ('TKX2 sh x)
- txsum0 :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x, ConvertTensor target) => target ('TKX2 sh x) -> target ('TKX2 ('[] :: [Maybe Nat]) x)
- txdot0 :: forall (sh :: [Maybe Nat]) r. (KnownShX sh, GoodScalar r, ConvertTensor target) => target (TKX sh r) -> target (TKX sh r) -> target (TKX ('[] :: [Maybe Nat]) r)
- txdot1In :: forall (sh :: [Maybe Nat]) r (n :: Nat). (KnownShX sh, GoodScalar r) => SNat n -> target (TKX (sh ++ '['Just n]) r) -> target (TKX (sh ++ '['Just n]) r) -> target (TKX sh r)
- txmatvecmul :: forall (mm :: Maybe Nat) (mn :: Maybe Nat) r. (GoodScalar r, ConvertTensor target) => SMayNat Int SNat mm -> SMayNat Int SNat mn -> target (TKX '[mm, mn] r) -> target (TKX '[mn] r) -> target (TKX '[mm] r)
- txmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r, ConvertTensor target) => target (TKX '['Just m, 'Just n] r) -> target (TKX '['Just n, 'Just p] r) -> target (TKX '['Just m, 'Just p] r)
- txreplicate :: forall (sh :: [Maybe Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> StaticShX sh -> target ('TKX2 sh x) -> target ('TKX2 ('Just k ': sh) x)
- txreplicate0N :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x) => IShX sh -> target ('TKX2 ('[] :: [Maybe Nat]) x) -> target ('TKX2 sh x)
- trindex :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x) => target ('TKR2 (m + n) x) -> IxROf target m -> target ('TKR2 n x)
- trindex0 :: forall (m :: Nat) (x :: TK). (KnownNat m, KnownSTK x) => target ('TKR2 m x) -> IxROf target m -> target ('TKR2 0 x)
- troneHot :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x, BoolOf (PrimalOf target) ~ BoolOf target, EqH (PrimalOf target) ('TKScalar Int64)) => IShR m -> target ('TKR2 n x) -> IxROf target m -> target ('TKR2 (m + n) x)
- trscatter :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> target ('TKR2 (m + n) x) -> (IxROf target m -> IxROf target p) -> target ('TKR2 (p + n) x)
- trscatter1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> target ('TKR2 (1 + n) x) -> (IntOf target -> IxROf target p) -> target ('TKR2 (p + n) x)
- trgather :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (m + n) -> target ('TKR2 (p + n) x) -> (IxROf target m -> IxROf target p) -> target ('TKR2 (m + n) x)
- trgather1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => Int -> target ('TKR2 (p + n) x) -> (IntOf target -> IxROf target p) -> target ('TKR2 (1 + n) x)
- tsindex :: forall (shm :: [Nat]) (shn :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownSTK x) => target ('TKS2 (shm ++ shn) x) -> IxSOf target shm -> target ('TKS2 shn x)
- tsindex0 :: forall (sh1 :: [Nat]) (x :: TK). (KnownShS sh1, KnownSTK x) => target ('TKS2 sh1 x) -> IxSOf target sh1 -> target ('TKS2 ('[] :: [Nat]) x)
- tsoneHot :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (x :: TK). (KnownShS sh1, KnownShS sh2, KnownSTK x, BoolOf (PrimalOf target) ~ BoolOf target, EqH (PrimalOf target) ('TKScalar Int64)) => target ('TKS2 sh2 x) -> IxSOf target sh1 -> target ('TKS2 (sh1 ++ sh2) x)
- tsscatter :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => target ('TKS2 (shm ++ shn) x) -> (IxSOf target shm -> IxSOf target shp) -> target ('TKS2 (shp ++ shn) x)
- tsscatter1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => target ('TKS2 (n2 ': shn) x) -> (IntOf target -> IxSOf target shp) -> target ('TKS2 (shp ++ shn) x)
- tsgather :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => target ('TKS2 (shp ++ shn) x) -> (IxSOf target shm -> IxSOf target shp) -> target ('TKS2 (shm ++ shn) x)
- tsgather1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => target ('TKS2 (shp ++ shn) x) -> (IntOf target -> IxSOf target shp) -> target ('TKS2 (n2 ': shn) x)
- txindex :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x) => target ('TKX2 (sh1 ++ sh2) x) -> IxXOf target sh1 -> target ('TKX2 sh2 x)
- txindex0 :: forall (sh1 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownSTK x) => target ('TKX2 sh1 x) -> IxXOf target sh1 -> target ('TKX2 ('[] :: [Maybe Nat]) x)
- txoneHot :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x, BoolOf (PrimalOf target) ~ BoolOf target, EqH (PrimalOf target) ('TKScalar Int64), ConvertTensor target) => IShX sh1 -> target ('TKX2 sh2 x) -> IxXOf target sh1 -> target ('TKX2 (sh1 ++ sh2) x)
- txscatter :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> target ('TKX2 (shm ++ shn) x) -> (IxXOf target shm -> IxXOf target shp) -> target ('TKX2 (shp ++ shn) x)
- txscatter1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> target ('TKX2 ('Just n2 ': shn) x) -> (IntOf target -> IxXOf target shp) -> target ('TKX2 (shp ++ shn) x)
- txgather :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shm ++ shn) -> target ('TKX2 (shp ++ shn) x) -> (IxXOf target shm -> IxXOf target shp) -> target ('TKX2 (shm ++ shn) x)
- txgather1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => SNat n2 -> target ('TKX2 (shp ++ shn) x) -> (IntOf target -> IxXOf target shp) -> target ('TKX2 ('Just n2 ': shn) x)
- trfloor :: forall r r2 (n :: Nat). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => target (TKR n r) -> target (TKR n r2)
- trfromIntegral :: forall r1 r2 (n :: Nat). (GoodScalar r1, Integral r1, GoodScalar r2) => target (TKR n r1) -> target (TKR n r2)
- trcast :: forall r1 r2 (n :: Nat). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => target (TKR n r1) -> target (TKR n r2)
- trminIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => target (TKR (1 + n) r) -> target (TKR n r2)
- trmaxIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => target (TKR (1 + n) r) -> target (TKR n r2)
- triota :: GoodScalar r => Int -> target (TKR 1 r)
- tsfloor :: forall r r2 (sh :: [Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => target (TKS sh r) -> target (TKS sh r2)
- tsfromIntegral :: forall r1 r2 (sh :: [Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => target (TKS sh r1) -> target (TKS sh r2)
- tscast :: forall r1 r2 (sh :: [Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => target (TKS sh r1) -> target (TKS sh r2)
- tsminIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => target (TKS (n ': sh) r) -> target (TKS (Init (n ': sh)) r2)
- tsmaxIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => target (TKS (n ': sh) r) -> target (TKS (Init (n ': sh)) r2)
- tsiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => target (TKS '[n] r)
- txfloor :: forall r r2 (sh :: [Maybe Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => target (TKX sh r) -> target (TKX sh r2)
- txfromIntegral :: forall r1 r2 (sh :: [Maybe Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => target (TKX sh r1) -> target (TKX sh r2)
- txcast :: forall r1 r2 (sh :: [Maybe Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => target (TKX sh r1) -> target (TKX sh r2)
- txminIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => target (TKX (mn ': sh) r) -> target (TKX (Init (mn ': sh)) r2)
- txmaxIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => target (TKX (mn ': sh) r) -> target (TKX (Init (mn ': sh)) r2)
- txiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => target (TKX '['Just n] r)
- tkfloor :: (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => target ('TKScalar r) -> target ('TKScalar r2)
- tkfromIntegral :: (GoodScalar r1, Integral r1, GoodScalar r2) => target ('TKScalar r1) -> target ('TKScalar r2)
- tkcast :: (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => target ('TKScalar r1) -> target ('TKScalar r2)
- trappend :: forall (n :: Natural) (x :: TK). KnownSTK x => target ('TKR2 (1 + n) x) -> target ('TKR2 (1 + n) x) -> target ('TKR2 (1 + n) x)
- trslice :: forall (n :: Natural) (x :: TK). KnownSTK x => Int -> Int -> target ('TKR2 (1 + n) x) -> target ('TKR2 (1 + n) x)
- trreverse :: forall (n :: Natural) (x :: TK). KnownSTK x => target ('TKR2 (1 + n) x) -> target ('TKR2 (1 + n) x)
- trtranspose :: forall (n :: Nat) (x :: TK). KnownSTK x => PermR -> target ('TKR2 n x) -> target ('TKR2 n x)
- trreshape :: forall (n :: Nat) (m :: Nat) (x :: TK). KnownSTK x => IShR m -> target ('TKR2 n x) -> target ('TKR2 m x)
- tsappend :: forall (m :: Nat) (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 (m ': sh) x) -> target ('TKS2 (n ': sh) x) -> target ('TKS2 ((m + n) ': sh) x)
- tsslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> target ('TKS2 (((i + n) + k) ': sh) x) -> target ('TKS2 (n ': sh) x)
- tsreverse :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 (n ': sh) x) -> target ('TKS2 (n ': sh) x)
- tstranspose :: forall (perm :: [Natural]) (sh :: [Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> target ('TKS2 sh x) -> target ('TKS2 (PermutePrefix perm sh) x)
- tsreshape :: forall (sh :: [Natural]) (sh2 :: [Natural]) (x :: TK). (Product sh ~ Product sh2, KnownSTK x) => ShS sh2 -> target ('TKS2 sh x) -> target ('TKS2 sh2 x)
- txappend :: forall (m :: Nat) (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 ('Just m ': sh) x) -> target ('TKX2 ('Just n ': sh) x) -> target ('TKX2 ('Just (m + n) ': sh) x)
- txslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Maybe Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> target ('TKX2 ('Just ((i + n) + k) ': sh) x) -> target ('TKX2 ('Just n ': sh) x)
- txreverse :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 (mn ': sh) x) -> target ('TKX2 (mn ': sh) x)
- txtranspose :: forall (perm :: [Natural]) (sh :: [Maybe Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> target ('TKX2 sh x) -> target ('TKX2 (PermutePrefix perm sh) x)
- txreshape :: forall (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh2 -> target ('TKX2 sh x) -> target ('TKX2 sh2 x)
- trbuild1 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> (IntOf target -> target ('TKR2 n x)) -> target ('TKR2 (1 + n) x)
- trmap0N :: forall (n :: Nat) (x :: TK) (x1 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1) => (target ('TKR2 0 x1) -> target ('TKR2 0 x)) -> target ('TKR2 n x1) -> target ('TKR2 n x)
- trzipWith0N :: forall (n :: Nat) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1, KnownSTK x2) => (target ('TKR2 0 x1) -> target ('TKR2 0 x2) -> target ('TKR2 0 x)) -> target ('TKR2 n x1) -> target ('TKR2 n x2) -> target ('TKR2 n x)
- tsbuild1 :: forall (k :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat k, KnownShS sh, KnownSTK x) => (IntOf target -> target ('TKS2 sh x)) -> target ('TKS2 (k ': sh) x)
- tsmap0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1) => (target ('TKS2 ('[] :: [Nat]) x1) -> target ('TKS2 ('[] :: [Nat]) x)) -> target ('TKS2 sh x1) -> target ('TKS2 sh x)
- tszipWith0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1, KnownSTK x2) => (target ('TKS2 ('[] :: [Nat]) x1) -> target ('TKS2 ('[] :: [Nat]) x2) -> target ('TKS2 ('[] :: [Nat]) x)) -> target ('TKS2 sh x1) -> target ('TKS2 sh x2) -> target ('TKS2 sh x)
- txbuild1 :: forall (k :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat k, KnownShX sh, KnownSTK x) => (IntOf target -> target ('TKX2 sh x)) -> target ('TKX2 ('Just k ': sh) x)
- tbuild1 :: forall (y :: TK) (k :: Nat). ConvertTensor target => SNat k -> SingletonTK y -> (IntOf target -> target y) -> target (BuildTensorKind k y)
- tmapAccumRDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy target -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf target ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf target ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf target ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> target accy -> target (BuildTensorKind k ey) -> target ('TKProduct accy (BuildTensorKind k by))
- tmapAccumLDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy target -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf target ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf target ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf target ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> target accy -> target (BuildTensorKind k ey) -> target ('TKProduct accy (BuildTensorKind k by))
- tApply :: forall (x :: TK) (z :: TK). HFunOf target x z -> target x -> target z
- tlambda :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf target x z
- tgrad :: forall (x :: TK) r. FullShapeTK x -> HFun x ('TKScalar r) -> HFunOf target x (ADTensorKind x)
- tvjp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf target ('TKProduct (ADTensorKind z) x) (ADTensorKind x)
- tjvp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf target ('TKProduct (ADTensorKind x) x) (ADTensorKind z)
- tprimalPart :: forall (y :: TK). target y -> PrimalOf target y
- tdualPart :: forall (y :: TK). SingletonTK y -> target y -> DualOf target y
- tfromPrimal :: forall (y :: TK). SingletonTK y -> PrimalOf target y -> target y
- tfromDual :: forall (y :: TK). DualOf target y -> target y
- tScale :: forall (y :: TK). (Num (target y), Num (PrimalOf target y)) => SingletonTK y -> PrimalOf target y -> DualOf target y -> DualOf target y
- tsum :: forall (z :: TK) (k :: Nat). ConvertTensor target => SNat k -> SingletonTK z -> target (BuildTensorKind k z) -> target z
- treplicate :: forall (z :: TK) (k :: Nat). ConvertTensor target => SNat k -> SingletonTK z -> target z -> target (BuildTensorKind k z)
- tindexBuild :: forall (z :: TK) (k :: Nat). ConvertTensor target => SNat k -> SingletonTK z -> target (BuildTensorKind k z) -> IntOf target -> target z
- treplTarget :: forall (y :: TK). (forall r. GoodScalar r => r) -> FullShapeTK y -> target y
- tdefTarget :: forall (y :: TK). FullShapeTK y -> target y
- taddTarget :: forall (y :: TK). SingletonTK y -> target y -> target y -> target y
- tmultTarget :: forall (y :: TK). SingletonTK y -> target y -> target y -> target y
- tsum0Target :: forall (y :: TK). FullShapeTK y -> target y -> target ('TKScalar Double)
- tdot0Target :: forall (y :: TK). FullShapeTK y -> target y -> target y -> target ('TKScalar Double)
- xmcast :: forall (x :: TK) (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]). (KnownSTK x, KnownShX sh, Rank sh ~ Rank sh2, ConvertTensor target) => StaticShX sh2 -> target ('TKX2 sh x) -> target ('TKX2 sh2 x)
- newtype HFun (x :: TK) (z :: TK) = HFun {}
- type ADReady (target :: Target) = (ADReadyNoLet target, LetTensor target)
- type ADReadyNoLet (target :: Target) = (ADReadyEqsClasses target, ADReadyEqsClasses (ShareOf target), ShareTensor (ShareOf target), ShareTensor (PrimalOf (ShareOf target)), ShareOf (ShareOf target) ~ ShareOf target)
- type ADReadyEqs (target :: Target) = BoolOf (PrimalOf target) ~ BoolOf target
- type ADReadyClasses (target :: Target) = (BaseTensor target, ConvertTensor target, Boolean (BoolOf target), AllTargetShow target, CommonTargetEqOrd target)
- type ADReadyEqsClasses (target :: Target) = (ADReadyEqs target, ADReadyClasses target, ADReadyClasses (PrimalOf target))
- class (forall (y :: TK). KnownSTK y => Show (target y)) => AllTargetShow (target :: Target)
- class (forall r. GoodScalar r => EqH target ('TKScalar r), forall r. GoodScalar r => OrdH target ('TKScalar r), forall r (n :: Nat). GoodScalar r => EqH target (TKR n r), forall r (n :: Nat). GoodScalar r => OrdH target (TKR n r), forall r (sh :: [Nat]). GoodScalar r => EqH target (TKS sh r), forall r (sh :: [Nat]). GoodScalar r => OrdH target (TKS sh r), forall r (sh :: [Maybe Nat]). GoodScalar r => EqH target (TKX sh r), forall r (sh :: [Maybe Nat]). GoodScalar r => OrdH target (TKX sh r)) => CommonTargetEqOrd (target :: Target)
- rtr :: forall (n :: Natural) (x :: TK) target. (KnownSTK x, BaseTensor target) => target ('TKR2 (2 + n) x) -> target ('TKR2 (2 + n) x)
- rflatten :: forall (n :: Nat) (x :: TK) target. (KnownSTK x, BaseTensor target) => target ('TKR2 n x) -> target ('TKR2 1 x)
- str :: forall (n :: Nat) (m :: Nat) (sh :: [Nat]) (x :: TK) target. (KnownSTK x, BaseTensor target) => target ('TKS2 (n ': (m ': sh)) x) -> target ('TKS2 (m ': (n ': sh)) x)
- sflatten :: forall (sh :: [Nat]) (x :: TK) target. (KnownShS sh, KnownSTK x, BaseTensor target) => target ('TKS2 sh x) -> target ('TKS2 '[Product sh] x)
- xtr :: forall (n :: Nat) (m :: Nat) (sh :: [Maybe Nat]) (x :: TK) target. (KnownSTK x, BaseTensor target) => target ('TKX2 ('Just n ': ('Just m ': sh)) x) -> target ('TKX2 ('Just m ': ('Just n ': sh)) x)
- xflatten :: forall (sh :: [Maybe Nat]) (x :: TK) target. (KnownSTK x, BaseTensor target) => target ('TKX2 sh x) -> target ('TKX2 '['Nothing :: Maybe Nat] x)
- tmapAccumR :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat) target. BaseTensor target => Proxy target -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> (forall (f :: Target). ADReady f => f accy -> f ey -> f ('TKProduct accy by)) -> target accy -> target (BuildTensorKind k ey) -> target ('TKProduct accy (BuildTensorKind k by))
- tmapAccumL :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat) target. BaseTensor target => Proxy target -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> (forall (f :: Target). ADReady f => f accy -> f ey -> f ('TKProduct accy by)) -> target accy -> target (BuildTensorKind k ey) -> target ('TKProduct accy (BuildTensorKind k by))
- rbuild :: forall (m :: Nat) (n :: Nat) (x :: TK) target. (KnownNat m, KnownNat n, KnownSTK x, BaseTensor target) => IShR (m + n) -> (IxROf target m -> target ('TKR2 n x)) -> target ('TKR2 (m + n) x)
- sbuild :: forall (m :: Nat) (sh :: [Nat]) (x :: TK) target. (KnownShS (Take m sh), KnownShS sh, KnownSTK x, BaseTensor target) => (IxSOf target (Take m sh) -> target ('TKS2 (Drop m sh) x)) -> target ('TKS2 sh x)
- xbuild :: forall (m :: Nat) (sh :: [Maybe Nat]) (x :: TK) target. (KnownShX (Take m sh), KnownSTK x, BaseTensor target, ConvertTensor target) => IShX sh -> (IxXOf target (Take m sh) -> target ('TKX2 (Drop m sh) x)) -> target ('TKX2 sh x)
- class (IntegralH r, IntElt r) => IntegralHAndIntElt r
- class (RealFloatH r, FloatElt r) => RealFloatAndFloatElt r
- type TensorSupportsX (c1 :: Type -> Constraint) (c2 :: Type -> Constraint) (f :: Target) = forall r (sh :: [Maybe Nat]). (GoodScalar r, c1 r) => c2 (f (TKX sh r))
- type TensorSupportsS (c1 :: Type -> Constraint) (c2 :: Type -> Constraint) (f :: Target) = forall r (sh :: [Nat]). (GoodScalar r, c1 r) => c2 (f (TKS sh r))
- type TensorSupportsR (c1 :: Type -> Constraint) (c2 :: Type -> Constraint) (f :: Target) = forall r (n :: Nat). (GoodScalar r, c1 r) => c2 (f (TKR n r))
- type TensorSupports (c1 :: Type -> Constraint) (c2 :: Type -> Constraint) (f :: Target) = forall r. (GoodScalar r, c1 r) => c2 (f ('TKScalar r))
The tensor classes and support datatypes
class LetTensor (target :: Target) where Source #
Minimal complete definition
Methods
ttlet :: forall (x :: TK) (z :: TK). target x -> (target x -> target z) -> target z Source #
ttletPrimal :: forall (x :: TK) (z :: TK). PrimalOf target x -> (PrimalOf target x -> target z) -> target z Source #
toShare :: forall (y :: TK). target y -> ShareOf target y Source #
tunshare :: forall (y :: TK). ShareOf target y -> target y Source #
tappend :: forall (m :: Nat) (n :: Nat) (y :: TK). BaseTensor target => SNat m -> SNat n -> SingletonTK y -> target (BuildTensorKind m y) -> target (BuildTensorKind n y) -> target (BuildTensorKind (m + n) y) Source #
tD :: forall (y :: TK). BaseTensor target => SingletonTK y -> PrimalOf target y -> DualOf target y -> target y Source #
Arguments
:: forall (yn :: TK) (ym :: TK) (k :: Nat). BaseTensor target | |
=> SNat k | length of the input |
-> SingletonTK yn | partial shape of the accumulator |
-> SingletonTK ym | partial shape of an individual input |
-> (forall (f :: Target). ADReady f => f yn -> f ym -> f yn) | the function to fold with |
-> target yn | the initial accumulator |
-> target (BuildTensorKind k ym) | the inputs |
-> target yn |
A strict left fold.
Arguments
:: forall (yn :: TK) (ym :: TK) (k :: Nat). BaseTensor target | |
=> SNat k | length of the input |
-> SingletonTK yn | partial shape of the accumulator |
-> SingletonTK ym | partial shape of an individual input |
-> (forall (f :: Target). ADReady f => f yn -> f ym -> f yn) | the function to scan with |
-> target yn | the initial accumulator |
-> target (BuildTensorKind k ym) | the inputs |
-> target (BuildTensorKind (1 + k) yn) |
A strict left scan.
Instances
class ShareTensor (target :: Target) where Source #
Methods
tshare :: forall (y :: TK). target y -> target y Source #
tunpair :: forall (x :: TK) (z :: TK). target ('TKProduct x z) -> (target x, target z) Source #
tunravelToListShare :: forall (y :: TK) (k :: Nat). (BaseTensor target, ConvertTensor target) => SNat k -> SingletonTK y -> target (BuildTensorKind k y) -> [target y] Source #
Instances
class (Num (IntOf target), IntegralH (IntOf target), TensorSupports Num Num target, TensorSupports RealFloatAndFloatElt Floating target, TensorSupports RealFloatAndFloatElt RealFloatH target, TensorSupports IntegralHAndIntElt IntegralH target, TensorSupportsR Num Num target, TensorSupportsR RealFloatAndFloatElt Floating target, TensorSupportsR RealFloatAndFloatElt RealFloatH target, TensorSupportsR IntegralHAndIntElt IntegralH target, TensorSupportsS Num Num target, TensorSupportsS RealFloatAndFloatElt Floating target, TensorSupportsS RealFloatAndFloatElt RealFloatH target, TensorSupportsS IntegralHAndIntElt IntegralH target, TensorSupportsX Num Num target, TensorSupportsX RealFloatAndFloatElt Floating target, TensorSupportsX RealFloatAndFloatElt RealFloatH target, TensorSupportsX IntegralHAndIntElt IntegralH target) => BaseTensor (target :: Target) where Source #
The superclasses indicate that it's not only a container array, but also a mathematical tensor, sporting numeric operations.
Minimal complete definition
rshape, sshape, xshape, tftk, tpair, tproject1, tproject2, tcond, trconcrete, tsconcrete, txconcrete, tkconcrete, tconcrete, tfromVector, trsum, trreplicate, tssum, tsreplicate, txsum, txreplicate, trindex, trscatter, trgather, tsindex, tsscatter, tsgather, txindex, txscatter, txgather, trfloor, trfromIntegral, trcast, trminIndex, trmaxIndex, triota, tsfloor, tsfromIntegral, tscast, tsminIndex, tsmaxIndex, tsiota, txfloor, txfromIntegral, txcast, txminIndex, txmaxIndex, txiota, tkfloor, tkfromIntegral, tkcast, trappend, trslice, trreverse, trtranspose, trreshape, tsappend, tsslice, tsreverse, tstranspose, tsreshape, txappend, txslice, txreverse, txtranspose, txreshape, trbuild1, tsbuild1, txbuild1, tmapAccumRDer, tmapAccumLDer, tApply, tlambda, tgrad, tvjp, tjvp, tprimalPart, tdualPart, tfromPrimal, tfromDual, treplTarget, tdefTarget, taddTarget, tmultTarget, tsum0Target, tdot0Target
Methods
rshape :: forall (n :: Nat) (x :: TK). KnownSTK x => target ('TKR2 n x) -> IShR n Source #
rlength :: forall (n :: Nat) (x :: TK). KnownSTK x => target ('TKR2 n x) -> Int Source #
rsize :: forall (n :: Nat) (x :: TK). KnownSTK x => target ('TKR2 n x) -> Int Source #
rwidth :: forall (n :: Natural) (x :: TK). KnownSTK x => target ('TKR2 (1 + n) x) -> Int Source #
sshape :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 sh x) -> ShS sh Source #
slength :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 sh x) -> Int Source #
ssize :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 sh x) -> Int Source #
swidth :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 (n ': sh) x) -> Int Source #
xshape :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 sh x) -> IShX sh Source #
xlength :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 sh x) -> Int Source #
xsize :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 sh x) -> Int Source #
xwidth :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 (mn ': sh) x) -> Int Source #
tsize :: forall (y :: TK). SingletonTK y -> target y -> Int Source #
tftk :: forall (y :: TK). SingletonTK y -> target y -> FullShapeTK y Source #
tpair :: forall (x :: TK) (z :: TK). target x -> target z -> target ('TKProduct x z) Source #
tproject1 :: forall (x :: TK) (z :: TK). target ('TKProduct x z) -> target x Source #
tproject2 :: forall (x :: TK) (z :: TK). target ('TKProduct x z) -> target z Source #
tcond :: forall (y :: TK). Boolean (BoolOf target) => SingletonTK y -> BoolOf target -> target y -> target y -> target y Source #
The operation is potentially strict in all arguments.
trconcrete :: forall r (n :: Nat). GoodScalar r => Ranked n r -> target (TKR n r) Source #
tsconcrete :: forall r (sh :: [Nat]). GoodScalar r => Shaped sh r -> target (TKS sh r) Source #
txconcrete :: forall r (sh :: [Maybe Nat]). GoodScalar r => Mixed sh r -> target (TKX sh r) Source #
tkconcrete :: GoodScalar r => r -> target ('TKScalar r) Source #
tconcrete :: forall (y :: TK). FullShapeTK y -> Concrete y -> target y Source #
trfromVector :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Vector (target ('TKR2 n x)) -> target ('TKR2 (1 + n) x) Source #
trfromVector0N :: forall (n :: Nat) (x :: TK). KnownSTK x => IShR n -> Vector (target ('TKR2 0 x)) -> target ('TKR2 n x) Source #
trunravelToList :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => target ('TKR2 (1 + n) x) -> [target ('TKR2 n x)] Source #
tsfromVector :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => Vector (target ('TKS2 sh x)) -> target ('TKS2 (n ': sh) x) Source #
tsfromVector0N :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => Vector (target ('TKS2 ('[] :: [Nat]) x)) -> target ('TKS2 sh x) Source #
tsunravelToList :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => target ('TKS2 (n ': sh) x) -> [target ('TKS2 sh x)] Source #
txfromVector :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => Vector (target ('TKX2 sh x)) -> target ('TKX2 ('Just n ': sh) x) Source #
txfromVector0N :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh -> Vector (target ('TKX2 ('[] :: [Maybe Nat]) x)) -> target ('TKX2 sh x) Source #
txunravelToList :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => target ('TKX2 ('Just n ': sh) x) -> [target ('TKX2 sh x)] Source #
tfromVector :: forall (y :: TK) (k :: Nat). SNat k -> SingletonTK y -> Vector (target y) -> target (BuildTensorKind k y) Source #
tfromListR :: forall (y :: TK) (k :: Nat). SingletonTK y -> ListR k (target y) -> target (BuildTensorKind k y) Source #
trsum :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => target ('TKR2 (1 + n) x) -> target ('TKR2 n x) Source #
trsum0 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => target ('TKR2 n x) -> target ('TKR2 0 x) Source #
trdot0 :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => target (TKR n r) -> target (TKR n r) -> target (TKR 0 r) Source #
trdot1In :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => target (TKR (1 + n) r) -> target (TKR (1 + n) r) -> target (TKR n r) Source #
trmatvecmul :: GoodScalar r => target (TKR 2 r) -> target (TKR 1 r) -> target (TKR 1 r) Source #
trmatmul2 :: GoodScalar r => target (TKR 2 r) -> target (TKR 2 r) -> target (TKR 2 r) Source #
trreplicate :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> target ('TKR2 n x) -> target ('TKR2 (1 + n) x) Source #
trreplicate0N :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => IShR n -> target ('TKR2 0 x) -> target ('TKR2 n x) Source #
tssum :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => target ('TKS2 (n ': sh) x) -> target ('TKS2 sh x) Source #
tssum0 :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => target ('TKS2 sh x) -> target ('TKS2 ('[] :: [Nat]) x) Source #
tsdot0 :: forall (sh :: [Nat]) r. (KnownShS sh, GoodScalar r) => target (TKS sh r) -> target (TKS sh r) -> target (TKS ('[] :: [Nat]) r) Source #
tsdot1In :: forall (sh :: [Nat]) r (n :: Nat). (KnownShS sh, GoodScalar r) => SNat n -> target (TKS (sh ++ '[n]) r) -> target (TKS (sh ++ '[n]) r) -> target (TKS sh r) Source #
tsmatvecmul :: forall (m :: Nat) (n :: Nat) r. (KnownNat m, KnownNat n, GoodScalar r) => target (TKS '[m, n] r) -> target (TKS '[n] r) -> target (TKS '[m] r) Source #
tsmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r) => target (TKS '[m, n] r) -> target (TKS '[n, p] r) -> target (TKS '[m, p] r) Source #
tsreplicate :: forall (sh :: [Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> ShS sh -> target ('TKS2 sh x) -> target ('TKS2 (k ': sh) x) Source #
tsreplicate0N :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => ShS sh -> target ('TKS2 ('[] :: [Nat]) x) -> target ('TKS2 sh x) Source #
txsum :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => target ('TKX2 ('Just n ': sh) x) -> target ('TKX2 sh x) Source #
txsum0 :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x, ConvertTensor target) => target ('TKX2 sh x) -> target ('TKX2 ('[] :: [Maybe Nat]) x) Source #
txdot0 :: forall (sh :: [Maybe Nat]) r. (KnownShX sh, GoodScalar r, ConvertTensor target) => target (TKX sh r) -> target (TKX sh r) -> target (TKX ('[] :: [Maybe Nat]) r) Source #
txdot1In :: forall (sh :: [Maybe Nat]) r (n :: Nat). (KnownShX sh, GoodScalar r) => SNat n -> target (TKX (sh ++ '['Just n]) r) -> target (TKX (sh ++ '['Just n]) r) -> target (TKX sh r) Source #
txmatvecmul :: forall (mm :: Maybe Nat) (mn :: Maybe Nat) r. (GoodScalar r, ConvertTensor target) => SMayNat Int SNat mm -> SMayNat Int SNat mn -> target (TKX '[mm, mn] r) -> target (TKX '[mn] r) -> target (TKX '[mm] r) Source #
txmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r, ConvertTensor target) => target (TKX '['Just m, 'Just n] r) -> target (TKX '['Just n, 'Just p] r) -> target (TKX '['Just m, 'Just p] r) Source #
txreplicate :: forall (sh :: [Maybe Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> StaticShX sh -> target ('TKX2 sh x) -> target ('TKX2 ('Just k ': sh) x) Source #
txreplicate0N :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x) => IShX sh -> target ('TKX2 ('[] :: [Maybe Nat]) x) -> target ('TKX2 sh x) Source #
trindex :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x) => target ('TKR2 (m + n) x) -> IxROf target m -> target ('TKR2 n x) Source #
trindex0 :: forall (m :: Nat) (x :: TK). (KnownNat m, KnownSTK x) => target ('TKR2 m x) -> IxROf target m -> target ('TKR2 0 x) Source #
troneHot :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x, BoolOf (PrimalOf target) ~ BoolOf target, EqH (PrimalOf target) ('TKScalar Int64)) => IShR m -> target ('TKR2 n x) -> IxROf target m -> target ('TKR2 (m + n) x) Source #
trscatter :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> target ('TKR2 (m + n) x) -> (IxROf target m -> IxROf target p) -> target ('TKR2 (p + n) x) Source #
trscatter1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> target ('TKR2 (1 + n) x) -> (IntOf target -> IxROf target p) -> target ('TKR2 (p + n) x) Source #
trgather :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (m + n) -> target ('TKR2 (p + n) x) -> (IxROf target m -> IxROf target p) -> target ('TKR2 (m + n) x) Source #
trgather1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => Int -> target ('TKR2 (p + n) x) -> (IntOf target -> IxROf target p) -> target ('TKR2 (1 + n) x) Source #
tsindex :: forall (shm :: [Nat]) (shn :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownSTK x) => target ('TKS2 (shm ++ shn) x) -> IxSOf target shm -> target ('TKS2 shn x) Source #
tsindex0 :: forall (sh1 :: [Nat]) (x :: TK). (KnownShS sh1, KnownSTK x) => target ('TKS2 sh1 x) -> IxSOf target sh1 -> target ('TKS2 ('[] :: [Nat]) x) Source #
tsoneHot :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (x :: TK). (KnownShS sh1, KnownShS sh2, KnownSTK x, BoolOf (PrimalOf target) ~ BoolOf target, EqH (PrimalOf target) ('TKScalar Int64)) => target ('TKS2 sh2 x) -> IxSOf target sh1 -> target ('TKS2 (sh1 ++ sh2) x) Source #
tsscatter :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => target ('TKS2 (shm ++ shn) x) -> (IxSOf target shm -> IxSOf target shp) -> target ('TKS2 (shp ++ shn) x) Source #
tsscatter1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => target ('TKS2 (n2 ': shn) x) -> (IntOf target -> IxSOf target shp) -> target ('TKS2 (shp ++ shn) x) Source #
tsgather :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => target ('TKS2 (shp ++ shn) x) -> (IxSOf target shm -> IxSOf target shp) -> target ('TKS2 (shm ++ shn) x) Source #
tsgather1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => target ('TKS2 (shp ++ shn) x) -> (IntOf target -> IxSOf target shp) -> target ('TKS2 (n2 ': shn) x) Source #
txindex :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x) => target ('TKX2 (sh1 ++ sh2) x) -> IxXOf target sh1 -> target ('TKX2 sh2 x) Source #
txindex0 :: forall (sh1 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownSTK x) => target ('TKX2 sh1 x) -> IxXOf target sh1 -> target ('TKX2 ('[] :: [Maybe Nat]) x) Source #
txoneHot :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x, BoolOf (PrimalOf target) ~ BoolOf target, EqH (PrimalOf target) ('TKScalar Int64), ConvertTensor target) => IShX sh1 -> target ('TKX2 sh2 x) -> IxXOf target sh1 -> target ('TKX2 (sh1 ++ sh2) x) Source #
txscatter :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> target ('TKX2 (shm ++ shn) x) -> (IxXOf target shm -> IxXOf target shp) -> target ('TKX2 (shp ++ shn) x) Source #
txscatter1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> target ('TKX2 ('Just n2 ': shn) x) -> (IntOf target -> IxXOf target shp) -> target ('TKX2 (shp ++ shn) x) Source #
txgather :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shm ++ shn) -> target ('TKX2 (shp ++ shn) x) -> (IxXOf target shm -> IxXOf target shp) -> target ('TKX2 (shm ++ shn) x) Source #
txgather1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => SNat n2 -> target ('TKX2 (shp ++ shn) x) -> (IntOf target -> IxXOf target shp) -> target ('TKX2 ('Just n2 ': shn) x) Source #
trfloor :: forall r r2 (n :: Nat). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => target (TKR n r) -> target (TKR n r2) Source #
trfromIntegral :: forall r1 r2 (n :: Nat). (GoodScalar r1, Integral r1, GoodScalar r2) => target (TKR n r1) -> target (TKR n r2) Source #
trcast :: forall r1 r2 (n :: Nat). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => target (TKR n r1) -> target (TKR n r2) Source #
trminIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => target (TKR (1 + n) r) -> target (TKR n r2) Source #
trmaxIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => target (TKR (1 + n) r) -> target (TKR n r2) Source #
triota :: GoodScalar r => Int -> target (TKR 1 r) Source #
tsfloor :: forall r r2 (sh :: [Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => target (TKS sh r) -> target (TKS sh r2) Source #
tsfromIntegral :: forall r1 r2 (sh :: [Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => target (TKS sh r1) -> target (TKS sh r2) Source #
tscast :: forall r1 r2 (sh :: [Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => target (TKS sh r1) -> target (TKS sh r2) Source #
tsminIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => target (TKS (n ': sh) r) -> target (TKS (Init (n ': sh)) r2) Source #
tsmaxIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => target (TKS (n ': sh) r) -> target (TKS (Init (n ': sh)) r2) Source #
tsiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => target (TKS '[n] r) Source #
txfloor :: forall r r2 (sh :: [Maybe Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => target (TKX sh r) -> target (TKX sh r2) Source #
txfromIntegral :: forall r1 r2 (sh :: [Maybe Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => target (TKX sh r1) -> target (TKX sh r2) Source #
txcast :: forall r1 r2 (sh :: [Maybe Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => target (TKX sh r1) -> target (TKX sh r2) Source #
txminIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => target (TKX (mn ': sh) r) -> target (TKX (Init (mn ': sh)) r2) Source #
txmaxIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => target (TKX (mn ': sh) r) -> target (TKX (Init (mn ': sh)) r2) Source #
txiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => target (TKX '['Just n] r) Source #
tkfloor :: (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => target ('TKScalar r) -> target ('TKScalar r2) Source #
tkfromIntegral :: (GoodScalar r1, Integral r1, GoodScalar r2) => target ('TKScalar r1) -> target ('TKScalar r2) Source #
tkcast :: (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => target ('TKScalar r1) -> target ('TKScalar r2) Source #
trappend :: forall (n :: Natural) (x :: TK). KnownSTK x => target ('TKR2 (1 + n) x) -> target ('TKR2 (1 + n) x) -> target ('TKR2 (1 + n) x) Source #
trslice :: forall (n :: Natural) (x :: TK). KnownSTK x => Int -> Int -> target ('TKR2 (1 + n) x) -> target ('TKR2 (1 + n) x) Source #
trreverse :: forall (n :: Natural) (x :: TK). KnownSTK x => target ('TKR2 (1 + n) x) -> target ('TKR2 (1 + n) x) Source #
trtranspose :: forall (n :: Nat) (x :: TK). KnownSTK x => PermR -> target ('TKR2 n x) -> target ('TKR2 n x) Source #
trreshape :: forall (n :: Nat) (m :: Nat) (x :: TK). KnownSTK x => IShR m -> target ('TKR2 n x) -> target ('TKR2 m x) Source #
tsappend :: forall (m :: Nat) (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 (m ': sh) x) -> target ('TKS2 (n ': sh) x) -> target ('TKS2 ((m + n) ': sh) x) Source #
tsslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> target ('TKS2 (((i + n) + k) ': sh) x) -> target ('TKS2 (n ': sh) x) Source #
tsreverse :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => target ('TKS2 (n ': sh) x) -> target ('TKS2 (n ': sh) x) Source #
tstranspose :: forall (perm :: [Natural]) (sh :: [Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> target ('TKS2 sh x) -> target ('TKS2 (PermutePrefix perm sh) x) Source #
tsreshape :: forall (sh :: [Natural]) (sh2 :: [Natural]) (x :: TK). (Product sh ~ Product sh2, KnownSTK x) => ShS sh2 -> target ('TKS2 sh x) -> target ('TKS2 sh2 x) Source #
txappend :: forall (m :: Nat) (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 ('Just m ': sh) x) -> target ('TKX2 ('Just n ': sh) x) -> target ('TKX2 ('Just (m + n) ': sh) x) Source #
txslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Maybe Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> target ('TKX2 ('Just ((i + n) + k) ': sh) x) -> target ('TKX2 ('Just n ': sh) x) Source #
txreverse :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => target ('TKX2 (mn ': sh) x) -> target ('TKX2 (mn ': sh) x) Source #
txtranspose :: forall (perm :: [Natural]) (sh :: [Maybe Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> target ('TKX2 sh x) -> target ('TKX2 (PermutePrefix perm sh) x) Source #
txreshape :: forall (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh2 -> target ('TKX2 sh x) -> target ('TKX2 sh2 x) Source #
trbuild1 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> (IntOf target -> target ('TKR2 n x)) -> target ('TKR2 (1 + n) x) Source #
trmap0N :: forall (n :: Nat) (x :: TK) (x1 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1) => (target ('TKR2 0 x1) -> target ('TKR2 0 x)) -> target ('TKR2 n x1) -> target ('TKR2 n x) Source #
trzipWith0N :: forall (n :: Nat) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1, KnownSTK x2) => (target ('TKR2 0 x1) -> target ('TKR2 0 x2) -> target ('TKR2 0 x)) -> target ('TKR2 n x1) -> target ('TKR2 n x2) -> target ('TKR2 n x) Source #
tsbuild1 :: forall (k :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat k, KnownShS sh, KnownSTK x) => (IntOf target -> target ('TKS2 sh x)) -> target ('TKS2 (k ': sh) x) Source #
tsmap0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1) => (target ('TKS2 ('[] :: [Nat]) x1) -> target ('TKS2 ('[] :: [Nat]) x)) -> target ('TKS2 sh x1) -> target ('TKS2 sh x) Source #
tszipWith0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1, KnownSTK x2) => (target ('TKS2 ('[] :: [Nat]) x1) -> target ('TKS2 ('[] :: [Nat]) x2) -> target ('TKS2 ('[] :: [Nat]) x)) -> target ('TKS2 sh x1) -> target ('TKS2 sh x2) -> target ('TKS2 sh x) Source #
txbuild1 :: forall (k :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat k, KnownShX sh, KnownSTK x) => (IntOf target -> target ('TKX2 sh x)) -> target ('TKX2 ('Just k ': sh) x) Source #
tbuild1 :: forall (y :: TK) (k :: Nat). ConvertTensor target => SNat k -> SingletonTK y -> (IntOf target -> target y) -> target (BuildTensorKind k y) Source #
Arguments
:: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy target | |
-> SNat k | length of the input |
-> FullShapeTK accy | shape of the accumulator |
-> FullShapeTK by | shape of the output |
-> FullShapeTK ey | shape of an individual input |
-> HFunOf target ('TKProduct accy ey) ('TKProduct accy by) | the function to mapAccum with |
-> HFunOf target ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) | the derivative of the function to mapAccum with |
-> HFunOf target ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) | the reverse derivative of the function to mapAccum with |
-> target accy | the initial accumulator |
-> target (BuildTensorKind k ey) | the inputs |
-> target ('TKProduct accy (BuildTensorKind k by)) |
A strict right mapAccum.
The applications of tjvp
and tvjp
performed already at this point
ensure that the computation of a derivative is not repeated
and that its result is shared. However, most of the time
the computation is unnneeded, so the AST instance uses a non-strict
constructor AstLambda
for it's instance of HFunOf
.
If the same argument functions are passed to many mapAccum calls, as in > let f = ... in ... (tmapAccumR ... f ...) ... (tmapAccumL ... f ...) extra care is needed to prevent double derivative computation. One needs to use tmapAccumRDer manually as in (simplified) > let f = ...; df = tjvp f; rf = tgrad f > in ... (tmapAccumRDer f df rf ...) ... (tmapAccumLDer f df rf ...)
Arguments
:: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy target | |
-> SNat k | length of the input |
-> FullShapeTK accy | shape of the accumulator |
-> FullShapeTK by | shape of the output |
-> FullShapeTK ey | shape of an individual input |
-> HFunOf target ('TKProduct accy ey) ('TKProduct accy by) | the function to mapAccum with |
-> HFunOf target ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) | the derivative of the function to mapAccum with |
-> HFunOf target ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) | the reverse derivative of the function to mapAccum with |
-> target accy | the initial accumulator |
-> target (BuildTensorKind k ey) | the inputs |
-> target ('TKProduct accy (BuildTensorKind k by)) |
A strict left mapAccum.
tApply :: forall (x :: TK) (z :: TK). HFunOf target x z -> target x -> target z Source #
tlambda :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf target x z Source #
Arguments
:: forall (x :: TK) r. FullShapeTK x | shape of x and dx |
-> HFun x ('TKScalar r) | x |-> TKScalar r |
-> HFunOf target x (ADTensorKind x) | x |-> dx |
Reverse derivative.
The followign methods (and tlambda) are exactly what is needed as arguments of tmapAccumRDer.
Arguments
:: forall (x :: TK) (z :: TK). FullShapeTK x | shape of x and dx |
-> HFun x z | x |-> z |
-> HFunOf target ('TKProduct (ADTensorKind z) x) (ADTensorKind x) | (dz, x) |-> dx |
Arguments
:: forall (x :: TK) (z :: TK). FullShapeTK x | shape of x and dx |
-> HFun x z | x |-> z |
-> HFunOf target ('TKProduct (ADTensorKind x) x) (ADTensorKind z) | (dx, x) |-> dz |
tprimalPart :: forall (y :: TK). target y -> PrimalOf target y Source #
tdualPart :: forall (y :: TK). SingletonTK y -> target y -> DualOf target y Source #
tfromPrimal :: forall (y :: TK). SingletonTK y -> PrimalOf target y -> target y Source #
tfromDual :: forall (y :: TK). DualOf target y -> target y Source #
tScale :: forall (y :: TK). (Num (target y), Num (PrimalOf target y)) => SingletonTK y -> PrimalOf target y -> DualOf target y -> DualOf target y Source #
tsum :: forall (z :: TK) (k :: Nat). ConvertTensor target => SNat k -> SingletonTK z -> target (BuildTensorKind k z) -> target z Source #
default tsum :: forall (z :: TK) (k :: Nat). (ShareTensor target, ConvertTensor target) => SNat k -> SingletonTK z -> target (BuildTensorKind k z) -> target z Source #
treplicate :: forall (z :: TK) (k :: Nat). ConvertTensor target => SNat k -> SingletonTK z -> target z -> target (BuildTensorKind k z) Source #
default treplicate :: forall (z :: TK) (k :: Nat). (ShareTensor target, ConvertTensor target) => SNat k -> SingletonTK z -> target z -> target (BuildTensorKind k z) Source #
tindexBuild :: forall (z :: TK) (k :: Nat). ConvertTensor target => SNat k -> SingletonTK z -> target (BuildTensorKind k z) -> IntOf target -> target z Source #
default tindexBuild :: forall (z :: TK) (k :: Nat). (ShareTensor target, ConvertTensor target) => SNat k -> SingletonTK z -> target (BuildTensorKind k z) -> IntOf target -> target z Source #
treplTarget :: forall (y :: TK). (forall r. GoodScalar r => r) -> FullShapeTK y -> target y Source #
Construct tensors with the given constant in each cell.
tdefTarget :: forall (y :: TK). FullShapeTK y -> target y Source #
Construct tensors with def
in each cell.
taddTarget :: forall (y :: TK). SingletonTK y -> target y -> target y -> target y Source #
Add pointwise all corresponding tensors within nested product, if any.
Requires duplicable arguments or a ShareTensor instance.
tmultTarget :: forall (y :: TK). SingletonTK y -> target y -> target y -> target y Source #
Multiply pointwise all corresponding tensors within nested products, if any.
Requires duplicable arguments or a ShareTensor instance.
tsum0Target :: forall (y :: TK). FullShapeTK y -> target y -> target ('TKScalar Double) Source #
Sum all dimensions of each component and then sum it all. Ignore all tensors with non-differentiable elements.
Requires duplicable arguments or a ShareTensor instance.
tdot0Target :: forall (y :: TK). FullShapeTK y -> target y -> target y -> target ('TKScalar Double) Source #
Dot product each component and then sum it all. Ignore all tensors with non-differentiable elements.
Requires duplicable arguments or a ShareTensor instance.
xmcast :: forall (x :: TK) (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]). (KnownSTK x, KnownShX sh, Rank sh ~ Rank sh2, ConvertTensor target) => StaticShX sh2 -> target ('TKX2 sh x) -> target ('TKX2 sh2 x) Source #
Instances
BaseTensor Concrete Source # | |
Defined in HordeAd.Core.OpsConcrete Methods rshape :: forall (n :: Nat) (x :: TK). KnownSTK x => Concrete ('TKR2 n x) -> IShR n Source # rlength :: forall (n :: Nat) (x :: TK). KnownSTK x => Concrete ('TKR2 n x) -> Int Source # rsize :: forall (n :: Nat) (x :: TK). KnownSTK x => Concrete ('TKR2 n x) -> Int Source # rwidth :: forall (n :: Natural) (x :: TK). KnownSTK x => Concrete ('TKR2 (1 + n) x) -> Int Source # sshape :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => Concrete ('TKS2 sh x) -> ShS sh Source # slength :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => Concrete ('TKS2 sh x) -> Int Source # ssize :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => Concrete ('TKS2 sh x) -> Int Source # swidth :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => Concrete ('TKS2 (n ': sh) x) -> Int Source # xshape :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => Concrete ('TKX2 sh x) -> IShX sh Source # xlength :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => Concrete ('TKX2 sh x) -> Int Source # xsize :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => Concrete ('TKX2 sh x) -> Int Source # xwidth :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => Concrete ('TKX2 (mn ': sh) x) -> Int Source # tsize :: forall (y :: TK). SingletonTK y -> Concrete y -> Int Source # tftk :: forall (y :: TK). SingletonTK y -> Concrete y -> FullShapeTK y Source # tpair :: forall (x :: TK) (z :: TK). Concrete x -> Concrete z -> Concrete ('TKProduct x z) Source # tproject1 :: forall (x :: TK) (z :: TK). Concrete ('TKProduct x z) -> Concrete x Source # tproject2 :: forall (x :: TK) (z :: TK). Concrete ('TKProduct x z) -> Concrete z Source # tcond :: forall (y :: TK). Boolean (BoolOf Concrete) => SingletonTK y -> BoolOf Concrete -> Concrete y -> Concrete y -> Concrete y Source # trconcrete :: forall r (n :: Nat). GoodScalar r => Ranked n r -> Concrete (TKR n r) Source # tsconcrete :: forall r (sh :: [Nat]). GoodScalar r => Shaped sh r -> Concrete (TKS sh r) Source # txconcrete :: forall r (sh :: [Maybe Nat]). GoodScalar r => Mixed sh r -> Concrete (TKX sh r) Source # tkconcrete :: GoodScalar r => r -> Concrete ('TKScalar r) Source # tconcrete :: forall (y :: TK). FullShapeTK y -> Concrete y -> Concrete y Source # trfromVector :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Vector (Concrete ('TKR2 n x)) -> Concrete ('TKR2 (1 + n) x) Source # trfromVector0N :: forall (n :: Nat) (x :: TK). KnownSTK x => IShR n -> Vector (Concrete ('TKR2 0 x)) -> Concrete ('TKR2 n x) Source # trunravelToList :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Concrete ('TKR2 (1 + n) x) -> [Concrete ('TKR2 n x)] Source # tsfromVector :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => Vector (Concrete ('TKS2 sh x)) -> Concrete ('TKS2 (n ': sh) x) Source # tsfromVector0N :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => Vector (Concrete ('TKS2 ('[] :: [Nat]) x)) -> Concrete ('TKS2 sh x) Source # tsunravelToList :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => Concrete ('TKS2 (n ': sh) x) -> [Concrete ('TKS2 sh x)] Source # txfromVector :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => Vector (Concrete ('TKX2 sh x)) -> Concrete ('TKX2 ('Just n ': sh) x) Source # txfromVector0N :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh -> Vector (Concrete ('TKX2 ('[] :: [Maybe Nat]) x)) -> Concrete ('TKX2 sh x) Source # txunravelToList :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => Concrete ('TKX2 ('Just n ': sh) x) -> [Concrete ('TKX2 sh x)] Source # tfromVector :: forall (y :: TK) (k :: Nat). SNat k -> SingletonTK y -> Vector (Concrete y) -> Concrete (BuildTensorKind k y) Source # tfromListR :: forall (y :: TK) (k :: Nat). SingletonTK y -> ListR k (Concrete y) -> Concrete (BuildTensorKind k y) Source # trsum :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Concrete ('TKR2 (1 + n) x) -> Concrete ('TKR2 n x) Source # trsum0 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Concrete ('TKR2 n x) -> Concrete ('TKR2 0 x) Source # trdot0 :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => Concrete (TKR n r) -> Concrete (TKR n r) -> Concrete (TKR 0 r) Source # trdot1In :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => Concrete (TKR (1 + n) r) -> Concrete (TKR (1 + n) r) -> Concrete (TKR n r) Source # trmatvecmul :: GoodScalar r => Concrete (TKR 2 r) -> Concrete (TKR 1 r) -> Concrete (TKR 1 r) Source # trmatmul2 :: GoodScalar r => Concrete (TKR 2 r) -> Concrete (TKR 2 r) -> Concrete (TKR 2 r) Source # trreplicate :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> Concrete ('TKR2 n x) -> Concrete ('TKR2 (1 + n) x) Source # trreplicate0N :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => IShR n -> Concrete ('TKR2 0 x) -> Concrete ('TKR2 n x) Source # tssum :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => Concrete ('TKS2 (n ': sh) x) -> Concrete ('TKS2 sh x) Source # tssum0 :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => Concrete ('TKS2 sh x) -> Concrete ('TKS2 ('[] :: [Nat]) x) Source # tsdot0 :: forall (sh :: [Nat]) r. (KnownShS sh, GoodScalar r) => Concrete (TKS sh r) -> Concrete (TKS sh r) -> Concrete (TKS ('[] :: [Nat]) r) Source # tsdot1In :: forall (sh :: [Nat]) r (n :: Nat). (KnownShS sh, GoodScalar r) => SNat n -> Concrete (TKS (sh ++ '[n]) r) -> Concrete (TKS (sh ++ '[n]) r) -> Concrete (TKS sh r) Source # tsmatvecmul :: forall (m :: Nat) (n :: Nat) r. (KnownNat m, KnownNat n, GoodScalar r) => Concrete (TKS '[m, n] r) -> Concrete (TKS '[n] r) -> Concrete (TKS '[m] r) Source # tsmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r) => Concrete (TKS '[m, n] r) -> Concrete (TKS '[n, p] r) -> Concrete (TKS '[m, p] r) Source # tsreplicate :: forall (sh :: [Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> ShS sh -> Concrete ('TKS2 sh x) -> Concrete ('TKS2 (k ': sh) x) Source # tsreplicate0N :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => ShS sh -> Concrete ('TKS2 ('[] :: [Nat]) x) -> Concrete ('TKS2 sh x) Source # txsum :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => Concrete ('TKX2 ('Just n ': sh) x) -> Concrete ('TKX2 sh x) Source # txsum0 :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x, ConvertTensor Concrete) => Concrete ('TKX2 sh x) -> Concrete ('TKX2 ('[] :: [Maybe Nat]) x) Source # txdot0 :: forall (sh :: [Maybe Nat]) r. (KnownShX sh, GoodScalar r, ConvertTensor Concrete) => Concrete (TKX sh r) -> Concrete (TKX sh r) -> Concrete (TKX ('[] :: [Maybe Nat]) r) Source # txdot1In :: forall (sh :: [Maybe Nat]) r (n :: Nat). (KnownShX sh, GoodScalar r) => SNat n -> Concrete (TKX (sh ++ '['Just n]) r) -> Concrete (TKX (sh ++ '['Just n]) r) -> Concrete (TKX sh r) Source # txmatvecmul :: forall (mm :: Maybe Nat) (mn :: Maybe Nat) r. (GoodScalar r, ConvertTensor Concrete) => SMayNat Int SNat mm -> SMayNat Int SNat mn -> Concrete (TKX '[mm, mn] r) -> Concrete (TKX '[mn] r) -> Concrete (TKX '[mm] r) Source # txmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r, ConvertTensor Concrete) => Concrete (TKX '['Just m, 'Just n] r) -> Concrete (TKX '['Just n, 'Just p] r) -> Concrete (TKX '['Just m, 'Just p] r) Source # txreplicate :: forall (sh :: [Maybe Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> StaticShX sh -> Concrete ('TKX2 sh x) -> Concrete ('TKX2 ('Just k ': sh) x) Source # txreplicate0N :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x) => IShX sh -> Concrete ('TKX2 ('[] :: [Maybe Nat]) x) -> Concrete ('TKX2 sh x) Source # trindex :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x) => Concrete ('TKR2 (m + n) x) -> IxROf Concrete m -> Concrete ('TKR2 n x) Source # trindex0 :: forall (m :: Nat) (x :: TK). (KnownNat m, KnownSTK x) => Concrete ('TKR2 m x) -> IxROf Concrete m -> Concrete ('TKR2 0 x) Source # troneHot :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x, BoolOf (PrimalOf Concrete) ~ BoolOf Concrete, EqH (PrimalOf Concrete) ('TKScalar Int64)) => IShR m -> Concrete ('TKR2 n x) -> IxROf Concrete m -> Concrete ('TKR2 (m + n) x) Source # trscatter :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> Concrete ('TKR2 (m + n) x) -> (IxROf Concrete m -> IxROf Concrete p) -> Concrete ('TKR2 (p + n) x) Source # trscatter1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> Concrete ('TKR2 (1 + n) x) -> (IntOf Concrete -> IxROf Concrete p) -> Concrete ('TKR2 (p + n) x) Source # trgather :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (m + n) -> Concrete ('TKR2 (p + n) x) -> (IxROf Concrete m -> IxROf Concrete p) -> Concrete ('TKR2 (m + n) x) Source # trgather1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => Int -> Concrete ('TKR2 (p + n) x) -> (IntOf Concrete -> IxROf Concrete p) -> Concrete ('TKR2 (1 + n) x) Source # tsindex :: forall (shm :: [Nat]) (shn :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownSTK x) => Concrete ('TKS2 (shm ++ shn) x) -> IxSOf Concrete shm -> Concrete ('TKS2 shn x) Source # tsindex0 :: forall (sh1 :: [Nat]) (x :: TK). (KnownShS sh1, KnownSTK x) => Concrete ('TKS2 sh1 x) -> IxSOf Concrete sh1 -> Concrete ('TKS2 ('[] :: [Nat]) x) Source # tsoneHot :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (x :: TK). (KnownShS sh1, KnownShS sh2, KnownSTK x, BoolOf (PrimalOf Concrete) ~ BoolOf Concrete, EqH (PrimalOf Concrete) ('TKScalar Int64)) => Concrete ('TKS2 sh2 x) -> IxSOf Concrete sh1 -> Concrete ('TKS2 (sh1 ++ sh2) x) Source # tsscatter :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => Concrete ('TKS2 (shm ++ shn) x) -> (IxSOf Concrete shm -> IxSOf Concrete shp) -> Concrete ('TKS2 (shp ++ shn) x) Source # tsscatter1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => Concrete ('TKS2 (n2 ': shn) x) -> (IntOf Concrete -> IxSOf Concrete shp) -> Concrete ('TKS2 (shp ++ shn) x) Source # tsgather :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => Concrete ('TKS2 (shp ++ shn) x) -> (IxSOf Concrete shm -> IxSOf Concrete shp) -> Concrete ('TKS2 (shm ++ shn) x) Source # tsgather1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => Concrete ('TKS2 (shp ++ shn) x) -> (IntOf Concrete -> IxSOf Concrete shp) -> Concrete ('TKS2 (n2 ': shn) x) Source # txindex :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x) => Concrete ('TKX2 (sh1 ++ sh2) x) -> IxXOf Concrete sh1 -> Concrete ('TKX2 sh2 x) Source # txindex0 :: forall (sh1 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownSTK x) => Concrete ('TKX2 sh1 x) -> IxXOf Concrete sh1 -> Concrete ('TKX2 ('[] :: [Maybe Nat]) x) Source # txoneHot :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x, BoolOf (PrimalOf Concrete) ~ BoolOf Concrete, EqH (PrimalOf Concrete) ('TKScalar Int64), ConvertTensor Concrete) => IShX sh1 -> Concrete ('TKX2 sh2 x) -> IxXOf Concrete sh1 -> Concrete ('TKX2 (sh1 ++ sh2) x) Source # txscatter :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> Concrete ('TKX2 (shm ++ shn) x) -> (IxXOf Concrete shm -> IxXOf Concrete shp) -> Concrete ('TKX2 (shp ++ shn) x) Source # txscatter1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> Concrete ('TKX2 ('Just n2 ': shn) x) -> (IntOf Concrete -> IxXOf Concrete shp) -> Concrete ('TKX2 (shp ++ shn) x) Source # txgather :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shm ++ shn) -> Concrete ('TKX2 (shp ++ shn) x) -> (IxXOf Concrete shm -> IxXOf Concrete shp) -> Concrete ('TKX2 (shm ++ shn) x) Source # txgather1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => SNat n2 -> Concrete ('TKX2 (shp ++ shn) x) -> (IntOf Concrete -> IxXOf Concrete shp) -> Concrete ('TKX2 ('Just n2 ': shn) x) Source # trfloor :: forall r r2 (n :: Nat). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => Concrete (TKR n r) -> Concrete (TKR n r2) Source # trfromIntegral :: forall r1 r2 (n :: Nat). (GoodScalar r1, Integral r1, GoodScalar r2) => Concrete (TKR n r1) -> Concrete (TKR n r2) Source # trcast :: forall r1 r2 (n :: Nat). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => Concrete (TKR n r1) -> Concrete (TKR n r2) Source # trminIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => Concrete (TKR (1 + n) r) -> Concrete (TKR n r2) Source # trmaxIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => Concrete (TKR (1 + n) r) -> Concrete (TKR n r2) Source # triota :: GoodScalar r => Int -> Concrete (TKR 1 r) Source # tsfloor :: forall r r2 (sh :: [Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => Concrete (TKS sh r) -> Concrete (TKS sh r2) Source # tsfromIntegral :: forall r1 r2 (sh :: [Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => Concrete (TKS sh r1) -> Concrete (TKS sh r2) Source # tscast :: forall r1 r2 (sh :: [Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => Concrete (TKS sh r1) -> Concrete (TKS sh r2) Source # tsminIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => Concrete (TKS (n ': sh) r) -> Concrete (TKS (Init (n ': sh)) r2) Source # tsmaxIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => Concrete (TKS (n ': sh) r) -> Concrete (TKS (Init (n ': sh)) r2) Source # tsiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => Concrete (TKS '[n] r) Source # txfloor :: forall r r2 (sh :: [Maybe Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => Concrete (TKX sh r) -> Concrete (TKX sh r2) Source # txfromIntegral :: forall r1 r2 (sh :: [Maybe Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => Concrete (TKX sh r1) -> Concrete (TKX sh r2) Source # txcast :: forall r1 r2 (sh :: [Maybe Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => Concrete (TKX sh r1) -> Concrete (TKX sh r2) Source # txminIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => Concrete (TKX (mn ': sh) r) -> Concrete (TKX (Init (mn ': sh)) r2) Source # txmaxIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => Concrete (TKX (mn ': sh) r) -> Concrete (TKX (Init (mn ': sh)) r2) Source # txiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => Concrete (TKX '['Just n] r) Source # tkfloor :: (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => Concrete ('TKScalar r) -> Concrete ('TKScalar r2) Source # tkfromIntegral :: (GoodScalar r1, Integral r1, GoodScalar r2) => Concrete ('TKScalar r1) -> Concrete ('TKScalar r2) Source # tkcast :: (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => Concrete ('TKScalar r1) -> Concrete ('TKScalar r2) Source # trappend :: forall (n :: Natural) (x :: TK). KnownSTK x => Concrete ('TKR2 (1 + n) x) -> Concrete ('TKR2 (1 + n) x) -> Concrete ('TKR2 (1 + n) x) Source # trslice :: forall (n :: Natural) (x :: TK). KnownSTK x => Int -> Int -> Concrete ('TKR2 (1 + n) x) -> Concrete ('TKR2 (1 + n) x) Source # trreverse :: forall (n :: Natural) (x :: TK). KnownSTK x => Concrete ('TKR2 (1 + n) x) -> Concrete ('TKR2 (1 + n) x) Source # trtranspose :: forall (n :: Nat) (x :: TK). KnownSTK x => PermR -> Concrete ('TKR2 n x) -> Concrete ('TKR2 n x) Source # trreshape :: forall (n :: Nat) (m :: Nat) (x :: TK). KnownSTK x => IShR m -> Concrete ('TKR2 n x) -> Concrete ('TKR2 m x) Source # tsappend :: forall (m :: Nat) (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => Concrete ('TKS2 (m ': sh) x) -> Concrete ('TKS2 (n ': sh) x) -> Concrete ('TKS2 ((m + n) ': sh) x) Source # tsslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> Concrete ('TKS2 (((i + n) + k) ': sh) x) -> Concrete ('TKS2 (n ': sh) x) Source # tsreverse :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => Concrete ('TKS2 (n ': sh) x) -> Concrete ('TKS2 (n ': sh) x) Source # tstranspose :: forall (perm :: [Natural]) (sh :: [Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> Concrete ('TKS2 sh x) -> Concrete ('TKS2 (PermutePrefix perm sh) x) Source # tsreshape :: forall (sh :: [Natural]) (sh2 :: [Natural]) (x :: TK). (Product sh ~ Product sh2, KnownSTK x) => ShS sh2 -> Concrete ('TKS2 sh x) -> Concrete ('TKS2 sh2 x) Source # txappend :: forall (m :: Nat) (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => Concrete ('TKX2 ('Just m ': sh) x) -> Concrete ('TKX2 ('Just n ': sh) x) -> Concrete ('TKX2 ('Just (m + n) ': sh) x) Source # txslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Maybe Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> Concrete ('TKX2 ('Just ((i + n) + k) ': sh) x) -> Concrete ('TKX2 ('Just n ': sh) x) Source # txreverse :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => Concrete ('TKX2 (mn ': sh) x) -> Concrete ('TKX2 (mn ': sh) x) Source # txtranspose :: forall (perm :: [Natural]) (sh :: [Maybe Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> Concrete ('TKX2 sh x) -> Concrete ('TKX2 (PermutePrefix perm sh) x) Source # txreshape :: forall (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh2 -> Concrete ('TKX2 sh x) -> Concrete ('TKX2 sh2 x) Source # trbuild1 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> (IntOf Concrete -> Concrete ('TKR2 n x)) -> Concrete ('TKR2 (1 + n) x) Source # trmap0N :: forall (n :: Nat) (x :: TK) (x1 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1) => (Concrete ('TKR2 0 x1) -> Concrete ('TKR2 0 x)) -> Concrete ('TKR2 n x1) -> Concrete ('TKR2 n x) Source # trzipWith0N :: forall (n :: Nat) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1, KnownSTK x2) => (Concrete ('TKR2 0 x1) -> Concrete ('TKR2 0 x2) -> Concrete ('TKR2 0 x)) -> Concrete ('TKR2 n x1) -> Concrete ('TKR2 n x2) -> Concrete ('TKR2 n x) Source # tsbuild1 :: forall (k :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat k, KnownShS sh, KnownSTK x) => (IntOf Concrete -> Concrete ('TKS2 sh x)) -> Concrete ('TKS2 (k ': sh) x) Source # tsmap0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1) => (Concrete ('TKS2 ('[] :: [Nat]) x1) -> Concrete ('TKS2 ('[] :: [Nat]) x)) -> Concrete ('TKS2 sh x1) -> Concrete ('TKS2 sh x) Source # tszipWith0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1, KnownSTK x2) => (Concrete ('TKS2 ('[] :: [Nat]) x1) -> Concrete ('TKS2 ('[] :: [Nat]) x2) -> Concrete ('TKS2 ('[] :: [Nat]) x)) -> Concrete ('TKS2 sh x1) -> Concrete ('TKS2 sh x2) -> Concrete ('TKS2 sh x) Source # txbuild1 :: forall (k :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat k, KnownShX sh, KnownSTK x) => (IntOf Concrete -> Concrete ('TKX2 sh x)) -> Concrete ('TKX2 ('Just k ': sh) x) Source # tbuild1 :: forall (y :: TK) (k :: Nat). ConvertTensor Concrete => SNat k -> SingletonTK y -> (IntOf Concrete -> Concrete y) -> Concrete (BuildTensorKind k y) Source # tmapAccumRDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy Concrete -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf Concrete ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf Concrete ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf Concrete ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> Concrete accy -> Concrete (BuildTensorKind k ey) -> Concrete ('TKProduct accy (BuildTensorKind k by)) Source # tmapAccumLDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy Concrete -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf Concrete ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf Concrete ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf Concrete ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> Concrete accy -> Concrete (BuildTensorKind k ey) -> Concrete ('TKProduct accy (BuildTensorKind k by)) Source # tApply :: forall (x :: TK) (z :: TK). HFunOf Concrete x z -> Concrete x -> Concrete z Source # tlambda :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf Concrete x z Source # tgrad :: forall (x :: TK) r. FullShapeTK x -> HFun x ('TKScalar r) -> HFunOf Concrete x (ADTensorKind x) Source # tvjp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf Concrete ('TKProduct (ADTensorKind z) x) (ADTensorKind x) Source # tjvp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf Concrete ('TKProduct (ADTensorKind x) x) (ADTensorKind z) Source # tprimalPart :: forall (y :: TK). Concrete y -> PrimalOf Concrete y Source # tdualPart :: forall (y :: TK). SingletonTK y -> Concrete y -> DualOf Concrete y Source # tfromPrimal :: forall (y :: TK). SingletonTK y -> PrimalOf Concrete y -> Concrete y Source # tfromDual :: forall (y :: TK). DualOf Concrete y -> Concrete y Source # tScale :: forall (y :: TK). (Num (Concrete y), Num (PrimalOf Concrete y)) => SingletonTK y -> PrimalOf Concrete y -> DualOf Concrete y -> DualOf Concrete y Source # tsum :: forall (z :: TK) (k :: Nat). ConvertTensor Concrete => SNat k -> SingletonTK z -> Concrete (BuildTensorKind k z) -> Concrete z Source # treplicate :: forall (z :: TK) (k :: Nat). ConvertTensor Concrete => SNat k -> SingletonTK z -> Concrete z -> Concrete (BuildTensorKind k z) Source # tindexBuild :: forall (z :: TK) (k :: Nat). ConvertTensor Concrete => SNat k -> SingletonTK z -> Concrete (BuildTensorKind k z) -> IntOf Concrete -> Concrete z Source # treplTarget :: forall (y :: TK). (forall r. GoodScalar r => r) -> FullShapeTK y -> Concrete y Source # tdefTarget :: forall (y :: TK). FullShapeTK y -> Concrete y Source # taddTarget :: forall (y :: TK). SingletonTK y -> Concrete y -> Concrete y -> Concrete y Source # tmultTarget :: forall (y :: TK). SingletonTK y -> Concrete y -> Concrete y -> Concrete y Source # tsum0Target :: forall (y :: TK). FullShapeTK y -> Concrete y -> Concrete ('TKScalar Double) Source # tdot0Target :: forall (y :: TK). FullShapeTK y -> Concrete y -> Concrete y -> Concrete ('TKScalar Double) Source # xmcast :: forall (x :: TK) (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]). (KnownSTK x, KnownShX sh, Rank sh ~ Rank sh2, ConvertTensor Concrete) => StaticShX sh2 -> Concrete ('TKX2 sh x) -> Concrete ('TKX2 sh2 x) Source # | |
(ADReadyNoLet target, ShareTensor target, ShareTensor (PrimalOf target)) => BaseTensor (ADVal target) Source # | |
Defined in HordeAd.Core.OpsADVal Methods rshape :: forall (n :: Nat) (x :: TK). KnownSTK x => ADVal target ('TKR2 n x) -> IShR n Source # rlength :: forall (n :: Nat) (x :: TK). KnownSTK x => ADVal target ('TKR2 n x) -> Int Source # rsize :: forall (n :: Nat) (x :: TK). KnownSTK x => ADVal target ('TKR2 n x) -> Int Source # rwidth :: forall (n :: Natural) (x :: TK). KnownSTK x => ADVal target ('TKR2 (1 + n) x) -> Int Source # sshape :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => ADVal target ('TKS2 sh x) -> ShS sh Source # slength :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => ADVal target ('TKS2 sh x) -> Int Source # ssize :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => ADVal target ('TKS2 sh x) -> Int Source # swidth :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => ADVal target ('TKS2 (n ': sh) x) -> Int Source # xshape :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => ADVal target ('TKX2 sh x) -> IShX sh Source # xlength :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => ADVal target ('TKX2 sh x) -> Int Source # xsize :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => ADVal target ('TKX2 sh x) -> Int Source # xwidth :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => ADVal target ('TKX2 (mn ': sh) x) -> Int Source # tsize :: forall (y :: TK). SingletonTK y -> ADVal target y -> Int Source # tftk :: forall (y :: TK). SingletonTK y -> ADVal target y -> FullShapeTK y Source # tpair :: forall (x :: TK) (z :: TK). ADVal target x -> ADVal target z -> ADVal target ('TKProduct x z) Source # tproject1 :: forall (x :: TK) (z :: TK). ADVal target ('TKProduct x z) -> ADVal target x Source # tproject2 :: forall (x :: TK) (z :: TK). ADVal target ('TKProduct x z) -> ADVal target z Source # tcond :: forall (y :: TK). Boolean (BoolOf (ADVal target)) => SingletonTK y -> BoolOf (ADVal target) -> ADVal target y -> ADVal target y -> ADVal target y Source # trconcrete :: forall r (n :: Nat). GoodScalar r => Ranked n r -> ADVal target (TKR n r) Source # tsconcrete :: forall r (sh :: [Nat]). GoodScalar r => Shaped sh r -> ADVal target (TKS sh r) Source # txconcrete :: forall r (sh :: [Maybe Nat]). GoodScalar r => Mixed sh r -> ADVal target (TKX sh r) Source # tkconcrete :: GoodScalar r => r -> ADVal target ('TKScalar r) Source # tconcrete :: forall (y :: TK). FullShapeTK y -> Concrete y -> ADVal target y Source # trfromVector :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Vector (ADVal target ('TKR2 n x)) -> ADVal target ('TKR2 (1 + n) x) Source # trfromVector0N :: forall (n :: Nat) (x :: TK). KnownSTK x => IShR n -> Vector (ADVal target ('TKR2 0 x)) -> ADVal target ('TKR2 n x) Source # trunravelToList :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => ADVal target ('TKR2 (1 + n) x) -> [ADVal target ('TKR2 n x)] Source # tsfromVector :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => Vector (ADVal target ('TKS2 sh x)) -> ADVal target ('TKS2 (n ': sh) x) Source # tsfromVector0N :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => Vector (ADVal target ('TKS2 ('[] :: [Nat]) x)) -> ADVal target ('TKS2 sh x) Source # tsunravelToList :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => ADVal target ('TKS2 (n ': sh) x) -> [ADVal target ('TKS2 sh x)] Source # txfromVector :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => Vector (ADVal target ('TKX2 sh x)) -> ADVal target ('TKX2 ('Just n ': sh) x) Source # txfromVector0N :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh -> Vector (ADVal target ('TKX2 ('[] :: [Maybe Nat]) x)) -> ADVal target ('TKX2 sh x) Source # txunravelToList :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => ADVal target ('TKX2 ('Just n ': sh) x) -> [ADVal target ('TKX2 sh x)] Source # tfromVector :: forall (y :: TK) (k :: Nat). SNat k -> SingletonTK y -> Vector (ADVal target y) -> ADVal target (BuildTensorKind k y) Source # tfromListR :: forall (y :: TK) (k :: Nat). SingletonTK y -> ListR k (ADVal target y) -> ADVal target (BuildTensorKind k y) Source # trsum :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => ADVal target ('TKR2 (1 + n) x) -> ADVal target ('TKR2 n x) Source # trsum0 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => ADVal target ('TKR2 n x) -> ADVal target ('TKR2 0 x) Source # trdot0 :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => ADVal target (TKR n r) -> ADVal target (TKR n r) -> ADVal target (TKR 0 r) Source # trdot1In :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => ADVal target (TKR (1 + n) r) -> ADVal target (TKR (1 + n) r) -> ADVal target (TKR n r) Source # trmatvecmul :: GoodScalar r => ADVal target (TKR 2 r) -> ADVal target (TKR 1 r) -> ADVal target (TKR 1 r) Source # trmatmul2 :: GoodScalar r => ADVal target (TKR 2 r) -> ADVal target (TKR 2 r) -> ADVal target (TKR 2 r) Source # trreplicate :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> ADVal target ('TKR2 n x) -> ADVal target ('TKR2 (1 + n) x) Source # trreplicate0N :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => IShR n -> ADVal target ('TKR2 0 x) -> ADVal target ('TKR2 n x) Source # tssum :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => ADVal target ('TKS2 (n ': sh) x) -> ADVal target ('TKS2 sh x) Source # tssum0 :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => ADVal target ('TKS2 sh x) -> ADVal target ('TKS2 ('[] :: [Nat]) x) Source # tsdot0 :: forall (sh :: [Nat]) r. (KnownShS sh, GoodScalar r) => ADVal target (TKS sh r) -> ADVal target (TKS sh r) -> ADVal target (TKS ('[] :: [Nat]) r) Source # tsdot1In :: forall (sh :: [Nat]) r (n :: Nat). (KnownShS sh, GoodScalar r) => SNat n -> ADVal target (TKS (sh ++ '[n]) r) -> ADVal target (TKS (sh ++ '[n]) r) -> ADVal target (TKS sh r) Source # tsmatvecmul :: forall (m :: Nat) (n :: Nat) r. (KnownNat m, KnownNat n, GoodScalar r) => ADVal target (TKS '[m, n] r) -> ADVal target (TKS '[n] r) -> ADVal target (TKS '[m] r) Source # tsmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r) => ADVal target (TKS '[m, n] r) -> ADVal target (TKS '[n, p] r) -> ADVal target (TKS '[m, p] r) Source # tsreplicate :: forall (sh :: [Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> ShS sh -> ADVal target ('TKS2 sh x) -> ADVal target ('TKS2 (k ': sh) x) Source # tsreplicate0N :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => ShS sh -> ADVal target ('TKS2 ('[] :: [Nat]) x) -> ADVal target ('TKS2 sh x) Source # txsum :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => ADVal target ('TKX2 ('Just n ': sh) x) -> ADVal target ('TKX2 sh x) Source # txsum0 :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x, ConvertTensor (ADVal target)) => ADVal target ('TKX2 sh x) -> ADVal target ('TKX2 ('[] :: [Maybe Nat]) x) Source # txdot0 :: forall (sh :: [Maybe Nat]) r. (KnownShX sh, GoodScalar r, ConvertTensor (ADVal target)) => ADVal target (TKX sh r) -> ADVal target (TKX sh r) -> ADVal target (TKX ('[] :: [Maybe Nat]) r) Source # txdot1In :: forall (sh :: [Maybe Nat]) r (n :: Nat). (KnownShX sh, GoodScalar r) => SNat n -> ADVal target (TKX (sh ++ '['Just n]) r) -> ADVal target (TKX (sh ++ '['Just n]) r) -> ADVal target (TKX sh r) Source # txmatvecmul :: forall (mm :: Maybe Nat) (mn :: Maybe Nat) r. (GoodScalar r, ConvertTensor (ADVal target)) => SMayNat Int SNat mm -> SMayNat Int SNat mn -> ADVal target (TKX '[mm, mn] r) -> ADVal target (TKX '[mn] r) -> ADVal target (TKX '[mm] r) Source # txmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r, ConvertTensor (ADVal target)) => ADVal target (TKX '['Just m, 'Just n] r) -> ADVal target (TKX '['Just n, 'Just p] r) -> ADVal target (TKX '['Just m, 'Just p] r) Source # txreplicate :: forall (sh :: [Maybe Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> StaticShX sh -> ADVal target ('TKX2 sh x) -> ADVal target ('TKX2 ('Just k ': sh) x) Source # txreplicate0N :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x) => IShX sh -> ADVal target ('TKX2 ('[] :: [Maybe Nat]) x) -> ADVal target ('TKX2 sh x) Source # trindex :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x) => ADVal target ('TKR2 (m + n) x) -> IxROf (ADVal target) m -> ADVal target ('TKR2 n x) Source # trindex0 :: forall (m :: Nat) (x :: TK). (KnownNat m, KnownSTK x) => ADVal target ('TKR2 m x) -> IxROf (ADVal target) m -> ADVal target ('TKR2 0 x) Source # troneHot :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x, BoolOf (PrimalOf (ADVal target)) ~ BoolOf (ADVal target), EqH (PrimalOf (ADVal target)) ('TKScalar Int64)) => IShR m -> ADVal target ('TKR2 n x) -> IxROf (ADVal target) m -> ADVal target ('TKR2 (m + n) x) Source # trscatter :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> ADVal target ('TKR2 (m + n) x) -> (IxROf (ADVal target) m -> IxROf (ADVal target) p) -> ADVal target ('TKR2 (p + n) x) Source # trscatter1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> ADVal target ('TKR2 (1 + n) x) -> (IntOf (ADVal target) -> IxROf (ADVal target) p) -> ADVal target ('TKR2 (p + n) x) Source # trgather :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (m + n) -> ADVal target ('TKR2 (p + n) x) -> (IxROf (ADVal target) m -> IxROf (ADVal target) p) -> ADVal target ('TKR2 (m + n) x) Source # trgather1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => Int -> ADVal target ('TKR2 (p + n) x) -> (IntOf (ADVal target) -> IxROf (ADVal target) p) -> ADVal target ('TKR2 (1 + n) x) Source # tsindex :: forall (shm :: [Nat]) (shn :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownSTK x) => ADVal target ('TKS2 (shm ++ shn) x) -> IxSOf (ADVal target) shm -> ADVal target ('TKS2 shn x) Source # tsindex0 :: forall (sh1 :: [Nat]) (x :: TK). (KnownShS sh1, KnownSTK x) => ADVal target ('TKS2 sh1 x) -> IxSOf (ADVal target) sh1 -> ADVal target ('TKS2 ('[] :: [Nat]) x) Source # tsoneHot :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (x :: TK). (KnownShS sh1, KnownShS sh2, KnownSTK x, BoolOf (PrimalOf (ADVal target)) ~ BoolOf (ADVal target), EqH (PrimalOf (ADVal target)) ('TKScalar Int64)) => ADVal target ('TKS2 sh2 x) -> IxSOf (ADVal target) sh1 -> ADVal target ('TKS2 (sh1 ++ sh2) x) Source # tsscatter :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => ADVal target ('TKS2 (shm ++ shn) x) -> (IxSOf (ADVal target) shm -> IxSOf (ADVal target) shp) -> ADVal target ('TKS2 (shp ++ shn) x) Source # tsscatter1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => ADVal target ('TKS2 (n2 ': shn) x) -> (IntOf (ADVal target) -> IxSOf (ADVal target) shp) -> ADVal target ('TKS2 (shp ++ shn) x) Source # tsgather :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => ADVal target ('TKS2 (shp ++ shn) x) -> (IxSOf (ADVal target) shm -> IxSOf (ADVal target) shp) -> ADVal target ('TKS2 (shm ++ shn) x) Source # tsgather1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => ADVal target ('TKS2 (shp ++ shn) x) -> (IntOf (ADVal target) -> IxSOf (ADVal target) shp) -> ADVal target ('TKS2 (n2 ': shn) x) Source # txindex :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x) => ADVal target ('TKX2 (sh1 ++ sh2) x) -> IxXOf (ADVal target) sh1 -> ADVal target ('TKX2 sh2 x) Source # txindex0 :: forall (sh1 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownSTK x) => ADVal target ('TKX2 sh1 x) -> IxXOf (ADVal target) sh1 -> ADVal target ('TKX2 ('[] :: [Maybe Nat]) x) Source # txoneHot :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x, BoolOf (PrimalOf (ADVal target)) ~ BoolOf (ADVal target), EqH (PrimalOf (ADVal target)) ('TKScalar Int64), ConvertTensor (ADVal target)) => IShX sh1 -> ADVal target ('TKX2 sh2 x) -> IxXOf (ADVal target) sh1 -> ADVal target ('TKX2 (sh1 ++ sh2) x) Source # txscatter :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> ADVal target ('TKX2 (shm ++ shn) x) -> (IxXOf (ADVal target) shm -> IxXOf (ADVal target) shp) -> ADVal target ('TKX2 (shp ++ shn) x) Source # txscatter1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> ADVal target ('TKX2 ('Just n2 ': shn) x) -> (IntOf (ADVal target) -> IxXOf (ADVal target) shp) -> ADVal target ('TKX2 (shp ++ shn) x) Source # txgather :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shm ++ shn) -> ADVal target ('TKX2 (shp ++ shn) x) -> (IxXOf (ADVal target) shm -> IxXOf (ADVal target) shp) -> ADVal target ('TKX2 (shm ++ shn) x) Source # txgather1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => SNat n2 -> ADVal target ('TKX2 (shp ++ shn) x) -> (IntOf (ADVal target) -> IxXOf (ADVal target) shp) -> ADVal target ('TKX2 ('Just n2 ': shn) x) Source # trfloor :: forall r r2 (n :: Nat). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => ADVal target (TKR n r) -> ADVal target (TKR n r2) Source # trfromIntegral :: forall r1 r2 (n :: Nat). (GoodScalar r1, Integral r1, GoodScalar r2) => ADVal target (TKR n r1) -> ADVal target (TKR n r2) Source # trcast :: forall r1 r2 (n :: Nat). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => ADVal target (TKR n r1) -> ADVal target (TKR n r2) Source # trminIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => ADVal target (TKR (1 + n) r) -> ADVal target (TKR n r2) Source # trmaxIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => ADVal target (TKR (1 + n) r) -> ADVal target (TKR n r2) Source # triota :: GoodScalar r => Int -> ADVal target (TKR 1 r) Source # tsfloor :: forall r r2 (sh :: [Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => ADVal target (TKS sh r) -> ADVal target (TKS sh r2) Source # tsfromIntegral :: forall r1 r2 (sh :: [Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => ADVal target (TKS sh r1) -> ADVal target (TKS sh r2) Source # tscast :: forall r1 r2 (sh :: [Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => ADVal target (TKS sh r1) -> ADVal target (TKS sh r2) Source # tsminIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => ADVal target (TKS (n ': sh) r) -> ADVal target (TKS (Init (n ': sh)) r2) Source # tsmaxIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => ADVal target (TKS (n ': sh) r) -> ADVal target (TKS (Init (n ': sh)) r2) Source # tsiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => ADVal target (TKS '[n] r) Source # txfloor :: forall r r2 (sh :: [Maybe Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => ADVal target (TKX sh r) -> ADVal target (TKX sh r2) Source # txfromIntegral :: forall r1 r2 (sh :: [Maybe Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => ADVal target (TKX sh r1) -> ADVal target (TKX sh r2) Source # txcast :: forall r1 r2 (sh :: [Maybe Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => ADVal target (TKX sh r1) -> ADVal target (TKX sh r2) Source # txminIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => ADVal target (TKX (mn ': sh) r) -> ADVal target (TKX (Init (mn ': sh)) r2) Source # txmaxIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => ADVal target (TKX (mn ': sh) r) -> ADVal target (TKX (Init (mn ': sh)) r2) Source # txiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => ADVal target (TKX '['Just n] r) Source # tkfloor :: (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => ADVal target ('TKScalar r) -> ADVal target ('TKScalar r2) Source # tkfromIntegral :: (GoodScalar r1, Integral r1, GoodScalar r2) => ADVal target ('TKScalar r1) -> ADVal target ('TKScalar r2) Source # tkcast :: (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => ADVal target ('TKScalar r1) -> ADVal target ('TKScalar r2) Source # trappend :: forall (n :: Natural) (x :: TK). KnownSTK x => ADVal target ('TKR2 (1 + n) x) -> ADVal target ('TKR2 (1 + n) x) -> ADVal target ('TKR2 (1 + n) x) Source # trslice :: forall (n :: Natural) (x :: TK). KnownSTK x => Int -> Int -> ADVal target ('TKR2 (1 + n) x) -> ADVal target ('TKR2 (1 + n) x) Source # trreverse :: forall (n :: Natural) (x :: TK). KnownSTK x => ADVal target ('TKR2 (1 + n) x) -> ADVal target ('TKR2 (1 + n) x) Source # trtranspose :: forall (n :: Nat) (x :: TK). KnownSTK x => PermR -> ADVal target ('TKR2 n x) -> ADVal target ('TKR2 n x) Source # trreshape :: forall (n :: Nat) (m :: Nat) (x :: TK). KnownSTK x => IShR m -> ADVal target ('TKR2 n x) -> ADVal target ('TKR2 m x) Source # tsappend :: forall (m :: Nat) (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => ADVal target ('TKS2 (m ': sh) x) -> ADVal target ('TKS2 (n ': sh) x) -> ADVal target ('TKS2 ((m + n) ': sh) x) Source # tsslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> ADVal target ('TKS2 (((i + n) + k) ': sh) x) -> ADVal target ('TKS2 (n ': sh) x) Source # tsreverse :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => ADVal target ('TKS2 (n ': sh) x) -> ADVal target ('TKS2 (n ': sh) x) Source # tstranspose :: forall (perm :: [Natural]) (sh :: [Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> ADVal target ('TKS2 sh x) -> ADVal target ('TKS2 (PermutePrefix perm sh) x) Source # tsreshape :: forall (sh :: [Natural]) (sh2 :: [Natural]) (x :: TK). (Product sh ~ Product sh2, KnownSTK x) => ShS sh2 -> ADVal target ('TKS2 sh x) -> ADVal target ('TKS2 sh2 x) Source # txappend :: forall (m :: Nat) (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => ADVal target ('TKX2 ('Just m ': sh) x) -> ADVal target ('TKX2 ('Just n ': sh) x) -> ADVal target ('TKX2 ('Just (m + n) ': sh) x) Source # txslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Maybe Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> ADVal target ('TKX2 ('Just ((i + n) + k) ': sh) x) -> ADVal target ('TKX2 ('Just n ': sh) x) Source # txreverse :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => ADVal target ('TKX2 (mn ': sh) x) -> ADVal target ('TKX2 (mn ': sh) x) Source # txtranspose :: forall (perm :: [Natural]) (sh :: [Maybe Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> ADVal target ('TKX2 sh x) -> ADVal target ('TKX2 (PermutePrefix perm sh) x) Source # txreshape :: forall (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh2 -> ADVal target ('TKX2 sh x) -> ADVal target ('TKX2 sh2 x) Source # trbuild1 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> (IntOf (ADVal target) -> ADVal target ('TKR2 n x)) -> ADVal target ('TKR2 (1 + n) x) Source # trmap0N :: forall (n :: Nat) (x :: TK) (x1 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1) => (ADVal target ('TKR2 0 x1) -> ADVal target ('TKR2 0 x)) -> ADVal target ('TKR2 n x1) -> ADVal target ('TKR2 n x) Source # trzipWith0N :: forall (n :: Nat) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1, KnownSTK x2) => (ADVal target ('TKR2 0 x1) -> ADVal target ('TKR2 0 x2) -> ADVal target ('TKR2 0 x)) -> ADVal target ('TKR2 n x1) -> ADVal target ('TKR2 n x2) -> ADVal target ('TKR2 n x) Source # tsbuild1 :: forall (k :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat k, KnownShS sh, KnownSTK x) => (IntOf (ADVal target) -> ADVal target ('TKS2 sh x)) -> ADVal target ('TKS2 (k ': sh) x) Source # tsmap0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1) => (ADVal target ('TKS2 ('[] :: [Nat]) x1) -> ADVal target ('TKS2 ('[] :: [Nat]) x)) -> ADVal target ('TKS2 sh x1) -> ADVal target ('TKS2 sh x) Source # tszipWith0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1, KnownSTK x2) => (ADVal target ('TKS2 ('[] :: [Nat]) x1) -> ADVal target ('TKS2 ('[] :: [Nat]) x2) -> ADVal target ('TKS2 ('[] :: [Nat]) x)) -> ADVal target ('TKS2 sh x1) -> ADVal target ('TKS2 sh x2) -> ADVal target ('TKS2 sh x) Source # txbuild1 :: forall (k :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat k, KnownShX sh, KnownSTK x) => (IntOf (ADVal target) -> ADVal target ('TKX2 sh x)) -> ADVal target ('TKX2 ('Just k ': sh) x) Source # tbuild1 :: forall (y :: TK) (k :: Nat). ConvertTensor (ADVal target) => SNat k -> SingletonTK y -> (IntOf (ADVal target) -> ADVal target y) -> ADVal target (BuildTensorKind k y) Source # tmapAccumRDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy (ADVal target) -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf (ADVal target) ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf (ADVal target) ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf (ADVal target) ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> ADVal target accy -> ADVal target (BuildTensorKind k ey) -> ADVal target ('TKProduct accy (BuildTensorKind k by)) Source # tmapAccumLDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy (ADVal target) -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf (ADVal target) ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf (ADVal target) ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf (ADVal target) ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> ADVal target accy -> ADVal target (BuildTensorKind k ey) -> ADVal target ('TKProduct accy (BuildTensorKind k by)) Source # tApply :: forall (x :: TK) (z :: TK). HFunOf (ADVal target) x z -> ADVal target x -> ADVal target z Source # tlambda :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (ADVal target) x z Source # tgrad :: forall (x :: TK) r. FullShapeTK x -> HFun x ('TKScalar r) -> HFunOf (ADVal target) x (ADTensorKind x) Source # tvjp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (ADVal target) ('TKProduct (ADTensorKind z) x) (ADTensorKind x) Source # tjvp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (ADVal target) ('TKProduct (ADTensorKind x) x) (ADTensorKind z) Source # tprimalPart :: forall (y :: TK). ADVal target y -> PrimalOf (ADVal target) y Source # tdualPart :: forall (y :: TK). SingletonTK y -> ADVal target y -> DualOf (ADVal target) y Source # tfromPrimal :: forall (y :: TK). SingletonTK y -> PrimalOf (ADVal target) y -> ADVal target y Source # tfromDual :: forall (y :: TK). DualOf (ADVal target) y -> ADVal target y Source # tScale :: forall (y :: TK). (Num (ADVal target y), Num (PrimalOf (ADVal target) y)) => SingletonTK y -> PrimalOf (ADVal target) y -> DualOf (ADVal target) y -> DualOf (ADVal target) y Source # tsum :: forall (z :: TK) (k :: Nat). ConvertTensor (ADVal target) => SNat k -> SingletonTK z -> ADVal target (BuildTensorKind k z) -> ADVal target z Source # treplicate :: forall (z :: TK) (k :: Nat). ConvertTensor (ADVal target) => SNat k -> SingletonTK z -> ADVal target z -> ADVal target (BuildTensorKind k z) Source # tindexBuild :: forall (z :: TK) (k :: Nat). ConvertTensor (ADVal target) => SNat k -> SingletonTK z -> ADVal target (BuildTensorKind k z) -> IntOf (ADVal target) -> ADVal target z Source # treplTarget :: forall (y :: TK). (forall r. GoodScalar r => r) -> FullShapeTK y -> ADVal target y Source # tdefTarget :: forall (y :: TK). FullShapeTK y -> ADVal target y Source # taddTarget :: forall (y :: TK). SingletonTK y -> ADVal target y -> ADVal target y -> ADVal target y Source # tmultTarget :: forall (y :: TK). SingletonTK y -> ADVal target y -> ADVal target y -> ADVal target y Source # tsum0Target :: forall (y :: TK). FullShapeTK y -> ADVal target y -> ADVal target ('TKScalar Double) Source # tdot0Target :: forall (y :: TK). FullShapeTK y -> ADVal target y -> ADVal target y -> ADVal target ('TKScalar Double) Source # xmcast :: forall (x :: TK) (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]). (KnownSTK x, KnownShX sh, Rank sh ~ Rank sh2, ConvertTensor (ADVal target)) => StaticShX sh2 -> ADVal target ('TKX2 sh x) -> ADVal target ('TKX2 sh2 x) Source # | |
AstSpan s => BaseTensor (AstNoSimplify s) Source # | |
Defined in HordeAd.Core.OpsAst Methods rshape :: forall (n :: Nat) (x :: TK). KnownSTK x => AstNoSimplify s ('TKR2 n x) -> IShR n Source # rlength :: forall (n :: Nat) (x :: TK). KnownSTK x => AstNoSimplify s ('TKR2 n x) -> Int Source # rsize :: forall (n :: Nat) (x :: TK). KnownSTK x => AstNoSimplify s ('TKR2 n x) -> Int Source # rwidth :: forall (n :: Natural) (x :: TK). KnownSTK x => AstNoSimplify s ('TKR2 (1 + n) x) -> Int Source # sshape :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKS2 sh x) -> ShS sh Source # slength :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKS2 sh x) -> Int Source # ssize :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKS2 sh x) -> Int Source # swidth :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKS2 (n ': sh) x) -> Int Source # xshape :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKX2 sh x) -> IShX sh Source # xlength :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKX2 sh x) -> Int Source # xsize :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKX2 sh x) -> Int Source # xwidth :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKX2 (mn ': sh) x) -> Int Source # tsize :: forall (y :: TK). SingletonTK y -> AstNoSimplify s y -> Int Source # tftk :: forall (y :: TK). SingletonTK y -> AstNoSimplify s y -> FullShapeTK y Source # tpair :: forall (x :: TK) (z :: TK). AstNoSimplify s x -> AstNoSimplify s z -> AstNoSimplify s ('TKProduct x z) Source # tproject1 :: forall (x :: TK) (z :: TK). AstNoSimplify s ('TKProduct x z) -> AstNoSimplify s x Source # tproject2 :: forall (x :: TK) (z :: TK). AstNoSimplify s ('TKProduct x z) -> AstNoSimplify s z Source # tcond :: forall (y :: TK). Boolean (BoolOf (AstNoSimplify s)) => SingletonTK y -> BoolOf (AstNoSimplify s) -> AstNoSimplify s y -> AstNoSimplify s y -> AstNoSimplify s y Source # trconcrete :: forall r (n :: Nat). GoodScalar r => Ranked n r -> AstNoSimplify s (TKR n r) Source # tsconcrete :: forall r (sh :: [Nat]). GoodScalar r => Shaped sh r -> AstNoSimplify s (TKS sh r) Source # txconcrete :: forall r (sh :: [Maybe Nat]). GoodScalar r => Mixed sh r -> AstNoSimplify s (TKX sh r) Source # tkconcrete :: GoodScalar r => r -> AstNoSimplify s ('TKScalar r) Source # tconcrete :: forall (y :: TK). FullShapeTK y -> Concrete y -> AstNoSimplify s y Source # trfromVector :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Vector (AstNoSimplify s ('TKR2 n x)) -> AstNoSimplify s ('TKR2 (1 + n) x) Source # trfromVector0N :: forall (n :: Nat) (x :: TK). KnownSTK x => IShR n -> Vector (AstNoSimplify s ('TKR2 0 x)) -> AstNoSimplify s ('TKR2 n x) Source # trunravelToList :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstNoSimplify s ('TKR2 (1 + n) x) -> [AstNoSimplify s ('TKR2 n x)] Source # tsfromVector :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => Vector (AstNoSimplify s ('TKS2 sh x)) -> AstNoSimplify s ('TKS2 (n ': sh) x) Source # tsfromVector0N :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => Vector (AstNoSimplify s ('TKS2 ('[] :: [Nat]) x)) -> AstNoSimplify s ('TKS2 sh x) Source # tsunravelToList :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => AstNoSimplify s ('TKS2 (n ': sh) x) -> [AstNoSimplify s ('TKS2 sh x)] Source # txfromVector :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => Vector (AstNoSimplify s ('TKX2 sh x)) -> AstNoSimplify s ('TKX2 ('Just n ': sh) x) Source # txfromVector0N :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh -> Vector (AstNoSimplify s ('TKX2 ('[] :: [Maybe Nat]) x)) -> AstNoSimplify s ('TKX2 sh x) Source # txunravelToList :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => AstNoSimplify s ('TKX2 ('Just n ': sh) x) -> [AstNoSimplify s ('TKX2 sh x)] Source # tfromVector :: forall (y :: TK) (k :: Nat). SNat k -> SingletonTK y -> Vector (AstNoSimplify s y) -> AstNoSimplify s (BuildTensorKind k y) Source # tfromListR :: forall (y :: TK) (k :: Nat). SingletonTK y -> ListR k (AstNoSimplify s y) -> AstNoSimplify s (BuildTensorKind k y) Source # trsum :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstNoSimplify s ('TKR2 (1 + n) x) -> AstNoSimplify s ('TKR2 n x) Source # trsum0 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstNoSimplify s ('TKR2 n x) -> AstNoSimplify s ('TKR2 0 x) Source # trdot0 :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstNoSimplify s (TKR n r) -> AstNoSimplify s (TKR n r) -> AstNoSimplify s (TKR 0 r) Source # trdot1In :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstNoSimplify s (TKR (1 + n) r) -> AstNoSimplify s (TKR (1 + n) r) -> AstNoSimplify s (TKR n r) Source # trmatvecmul :: GoodScalar r => AstNoSimplify s (TKR 2 r) -> AstNoSimplify s (TKR 1 r) -> AstNoSimplify s (TKR 1 r) Source # trmatmul2 :: GoodScalar r => AstNoSimplify s (TKR 2 r) -> AstNoSimplify s (TKR 2 r) -> AstNoSimplify s (TKR 2 r) Source # trreplicate :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> AstNoSimplify s ('TKR2 n x) -> AstNoSimplify s ('TKR2 (1 + n) x) Source # trreplicate0N :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => IShR n -> AstNoSimplify s ('TKR2 0 x) -> AstNoSimplify s ('TKR2 n x) Source # tssum :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => AstNoSimplify s ('TKS2 (n ': sh) x) -> AstNoSimplify s ('TKS2 sh x) Source # tssum0 :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => AstNoSimplify s ('TKS2 sh x) -> AstNoSimplify s ('TKS2 ('[] :: [Nat]) x) Source # tsdot0 :: forall (sh :: [Nat]) r. (KnownShS sh, GoodScalar r) => AstNoSimplify s (TKS sh r) -> AstNoSimplify s (TKS sh r) -> AstNoSimplify s (TKS ('[] :: [Nat]) r) Source # tsdot1In :: forall (sh :: [Nat]) r (n :: Nat). (KnownShS sh, GoodScalar r) => SNat n -> AstNoSimplify s (TKS (sh ++ '[n]) r) -> AstNoSimplify s (TKS (sh ++ '[n]) r) -> AstNoSimplify s (TKS sh r) Source # tsmatvecmul :: forall (m :: Nat) (n :: Nat) r. (KnownNat m, KnownNat n, GoodScalar r) => AstNoSimplify s (TKS '[m, n] r) -> AstNoSimplify s (TKS '[n] r) -> AstNoSimplify s (TKS '[m] r) Source # tsmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r) => AstNoSimplify s (TKS '[m, n] r) -> AstNoSimplify s (TKS '[n, p] r) -> AstNoSimplify s (TKS '[m, p] r) Source # tsreplicate :: forall (sh :: [Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> ShS sh -> AstNoSimplify s ('TKS2 sh x) -> AstNoSimplify s ('TKS2 (k ': sh) x) Source # tsreplicate0N :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => ShS sh -> AstNoSimplify s ('TKS2 ('[] :: [Nat]) x) -> AstNoSimplify s ('TKS2 sh x) Source # txsum :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => AstNoSimplify s ('TKX2 ('Just n ': sh) x) -> AstNoSimplify s ('TKX2 sh x) Source # txsum0 :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x, ConvertTensor (AstNoSimplify s)) => AstNoSimplify s ('TKX2 sh x) -> AstNoSimplify s ('TKX2 ('[] :: [Maybe Nat]) x) Source # txdot0 :: forall (sh :: [Maybe Nat]) r. (KnownShX sh, GoodScalar r, ConvertTensor (AstNoSimplify s)) => AstNoSimplify s (TKX sh r) -> AstNoSimplify s (TKX sh r) -> AstNoSimplify s (TKX ('[] :: [Maybe Nat]) r) Source # txdot1In :: forall (sh :: [Maybe Nat]) r (n :: Nat). (KnownShX sh, GoodScalar r) => SNat n -> AstNoSimplify s (TKX (sh ++ '['Just n]) r) -> AstNoSimplify s (TKX (sh ++ '['Just n]) r) -> AstNoSimplify s (TKX sh r) Source # txmatvecmul :: forall (mm :: Maybe Nat) (mn :: Maybe Nat) r. (GoodScalar r, ConvertTensor (AstNoSimplify s)) => SMayNat Int SNat mm -> SMayNat Int SNat mn -> AstNoSimplify s (TKX '[mm, mn] r) -> AstNoSimplify s (TKX '[mn] r) -> AstNoSimplify s (TKX '[mm] r) Source # txmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r, ConvertTensor (AstNoSimplify s)) => AstNoSimplify s (TKX '['Just m, 'Just n] r) -> AstNoSimplify s (TKX '['Just n, 'Just p] r) -> AstNoSimplify s (TKX '['Just m, 'Just p] r) Source # txreplicate :: forall (sh :: [Maybe Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> StaticShX sh -> AstNoSimplify s ('TKX2 sh x) -> AstNoSimplify s ('TKX2 ('Just k ': sh) x) Source # txreplicate0N :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x) => IShX sh -> AstNoSimplify s ('TKX2 ('[] :: [Maybe Nat]) x) -> AstNoSimplify s ('TKX2 sh x) Source # trindex :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x) => AstNoSimplify s ('TKR2 (m + n) x) -> IxROf (AstNoSimplify s) m -> AstNoSimplify s ('TKR2 n x) Source # trindex0 :: forall (m :: Nat) (x :: TK). (KnownNat m, KnownSTK x) => AstNoSimplify s ('TKR2 m x) -> IxROf (AstNoSimplify s) m -> AstNoSimplify s ('TKR2 0 x) Source # troneHot :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x, BoolOf (PrimalOf (AstNoSimplify s)) ~ BoolOf (AstNoSimplify s), EqH (PrimalOf (AstNoSimplify s)) ('TKScalar Int64)) => IShR m -> AstNoSimplify s ('TKR2 n x) -> IxROf (AstNoSimplify s) m -> AstNoSimplify s ('TKR2 (m + n) x) Source # trscatter :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> AstNoSimplify s ('TKR2 (m + n) x) -> (IxROf (AstNoSimplify s) m -> IxROf (AstNoSimplify s) p) -> AstNoSimplify s ('TKR2 (p + n) x) Source # trscatter1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> AstNoSimplify s ('TKR2 (1 + n) x) -> (IntOf (AstNoSimplify s) -> IxROf (AstNoSimplify s) p) -> AstNoSimplify s ('TKR2 (p + n) x) Source # trgather :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (m + n) -> AstNoSimplify s ('TKR2 (p + n) x) -> (IxROf (AstNoSimplify s) m -> IxROf (AstNoSimplify s) p) -> AstNoSimplify s ('TKR2 (m + n) x) Source # trgather1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => Int -> AstNoSimplify s ('TKR2 (p + n) x) -> (IntOf (AstNoSimplify s) -> IxROf (AstNoSimplify s) p) -> AstNoSimplify s ('TKR2 (1 + n) x) Source # tsindex :: forall (shm :: [Nat]) (shn :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownSTK x) => AstNoSimplify s ('TKS2 (shm ++ shn) x) -> IxSOf (AstNoSimplify s) shm -> AstNoSimplify s ('TKS2 shn x) Source # tsindex0 :: forall (sh1 :: [Nat]) (x :: TK). (KnownShS sh1, KnownSTK x) => AstNoSimplify s ('TKS2 sh1 x) -> IxSOf (AstNoSimplify s) sh1 -> AstNoSimplify s ('TKS2 ('[] :: [Nat]) x) Source # tsoneHot :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (x :: TK). (KnownShS sh1, KnownShS sh2, KnownSTK x, BoolOf (PrimalOf (AstNoSimplify s)) ~ BoolOf (AstNoSimplify s), EqH (PrimalOf (AstNoSimplify s)) ('TKScalar Int64)) => AstNoSimplify s ('TKS2 sh2 x) -> IxSOf (AstNoSimplify s) sh1 -> AstNoSimplify s ('TKS2 (sh1 ++ sh2) x) Source # tsscatter :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => AstNoSimplify s ('TKS2 (shm ++ shn) x) -> (IxSOf (AstNoSimplify s) shm -> IxSOf (AstNoSimplify s) shp) -> AstNoSimplify s ('TKS2 (shp ++ shn) x) Source # tsscatter1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => AstNoSimplify s ('TKS2 (n2 ': shn) x) -> (IntOf (AstNoSimplify s) -> IxSOf (AstNoSimplify s) shp) -> AstNoSimplify s ('TKS2 (shp ++ shn) x) Source # tsgather :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => AstNoSimplify s ('TKS2 (shp ++ shn) x) -> (IxSOf (AstNoSimplify s) shm -> IxSOf (AstNoSimplify s) shp) -> AstNoSimplify s ('TKS2 (shm ++ shn) x) Source # tsgather1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => AstNoSimplify s ('TKS2 (shp ++ shn) x) -> (IntOf (AstNoSimplify s) -> IxSOf (AstNoSimplify s) shp) -> AstNoSimplify s ('TKS2 (n2 ': shn) x) Source # txindex :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x) => AstNoSimplify s ('TKX2 (sh1 ++ sh2) x) -> IxXOf (AstNoSimplify s) sh1 -> AstNoSimplify s ('TKX2 sh2 x) Source # txindex0 :: forall (sh1 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownSTK x) => AstNoSimplify s ('TKX2 sh1 x) -> IxXOf (AstNoSimplify s) sh1 -> AstNoSimplify s ('TKX2 ('[] :: [Maybe Nat]) x) Source # txoneHot :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x, BoolOf (PrimalOf (AstNoSimplify s)) ~ BoolOf (AstNoSimplify s), EqH (PrimalOf (AstNoSimplify s)) ('TKScalar Int64), ConvertTensor (AstNoSimplify s)) => IShX sh1 -> AstNoSimplify s ('TKX2 sh2 x) -> IxXOf (AstNoSimplify s) sh1 -> AstNoSimplify s ('TKX2 (sh1 ++ sh2) x) Source # txscatter :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> AstNoSimplify s ('TKX2 (shm ++ shn) x) -> (IxXOf (AstNoSimplify s) shm -> IxXOf (AstNoSimplify s) shp) -> AstNoSimplify s ('TKX2 (shp ++ shn) x) Source # txscatter1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> AstNoSimplify s ('TKX2 ('Just n2 ': shn) x) -> (IntOf (AstNoSimplify s) -> IxXOf (AstNoSimplify s) shp) -> AstNoSimplify s ('TKX2 (shp ++ shn) x) Source # txgather :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shm ++ shn) -> AstNoSimplify s ('TKX2 (shp ++ shn) x) -> (IxXOf (AstNoSimplify s) shm -> IxXOf (AstNoSimplify s) shp) -> AstNoSimplify s ('TKX2 (shm ++ shn) x) Source # txgather1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => SNat n2 -> AstNoSimplify s ('TKX2 (shp ++ shn) x) -> (IntOf (AstNoSimplify s) -> IxXOf (AstNoSimplify s) shp) -> AstNoSimplify s ('TKX2 ('Just n2 ': shn) x) Source # trfloor :: forall r r2 (n :: Nat). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstNoSimplify s (TKR n r) -> AstNoSimplify s (TKR n r2) Source # trfromIntegral :: forall r1 r2 (n :: Nat). (GoodScalar r1, Integral r1, GoodScalar r2) => AstNoSimplify s (TKR n r1) -> AstNoSimplify s (TKR n r2) Source # trcast :: forall r1 r2 (n :: Nat). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstNoSimplify s (TKR n r1) -> AstNoSimplify s (TKR n r2) Source # trminIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => AstNoSimplify s (TKR (1 + n) r) -> AstNoSimplify s (TKR n r2) Source # trmaxIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => AstNoSimplify s (TKR (1 + n) r) -> AstNoSimplify s (TKR n r2) Source # triota :: GoodScalar r => Int -> AstNoSimplify s (TKR 1 r) Source # tsfloor :: forall r r2 (sh :: [Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstNoSimplify s (TKS sh r) -> AstNoSimplify s (TKS sh r2) Source # tsfromIntegral :: forall r1 r2 (sh :: [Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => AstNoSimplify s (TKS sh r1) -> AstNoSimplify s (TKS sh r2) Source # tscast :: forall r1 r2 (sh :: [Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstNoSimplify s (TKS sh r1) -> AstNoSimplify s (TKS sh r2) Source # tsminIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstNoSimplify s (TKS (n ': sh) r) -> AstNoSimplify s (TKS (Init (n ': sh)) r2) Source # tsmaxIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstNoSimplify s (TKS (n ': sh) r) -> AstNoSimplify s (TKS (Init (n ': sh)) r2) Source # tsiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstNoSimplify s (TKS '[n] r) Source # txfloor :: forall r r2 (sh :: [Maybe Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstNoSimplify s (TKX sh r) -> AstNoSimplify s (TKX sh r2) Source # txfromIntegral :: forall r1 r2 (sh :: [Maybe Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => AstNoSimplify s (TKX sh r1) -> AstNoSimplify s (TKX sh r2) Source # txcast :: forall r1 r2 (sh :: [Maybe Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstNoSimplify s (TKX sh r1) -> AstNoSimplify s (TKX sh r2) Source # txminIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstNoSimplify s (TKX (mn ': sh) r) -> AstNoSimplify s (TKX (Init (mn ': sh)) r2) Source # txmaxIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstNoSimplify s (TKX (mn ': sh) r) -> AstNoSimplify s (TKX (Init (mn ': sh)) r2) Source # txiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstNoSimplify s (TKX '['Just n] r) Source # tkfloor :: (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstNoSimplify s ('TKScalar r) -> AstNoSimplify s ('TKScalar r2) Source # tkfromIntegral :: (GoodScalar r1, Integral r1, GoodScalar r2) => AstNoSimplify s ('TKScalar r1) -> AstNoSimplify s ('TKScalar r2) Source # tkcast :: (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstNoSimplify s ('TKScalar r1) -> AstNoSimplify s ('TKScalar r2) Source # trappend :: forall (n :: Natural) (x :: TK). KnownSTK x => AstNoSimplify s ('TKR2 (1 + n) x) -> AstNoSimplify s ('TKR2 (1 + n) x) -> AstNoSimplify s ('TKR2 (1 + n) x) Source # trslice :: forall (n :: Natural) (x :: TK). KnownSTK x => Int -> Int -> AstNoSimplify s ('TKR2 (1 + n) x) -> AstNoSimplify s ('TKR2 (1 + n) x) Source # trreverse :: forall (n :: Natural) (x :: TK). KnownSTK x => AstNoSimplify s ('TKR2 (1 + n) x) -> AstNoSimplify s ('TKR2 (1 + n) x) Source # trtranspose :: forall (n :: Nat) (x :: TK). KnownSTK x => PermR -> AstNoSimplify s ('TKR2 n x) -> AstNoSimplify s ('TKR2 n x) Source # trreshape :: forall (n :: Nat) (m :: Nat) (x :: TK). KnownSTK x => IShR m -> AstNoSimplify s ('TKR2 n x) -> AstNoSimplify s ('TKR2 m x) Source # tsappend :: forall (m :: Nat) (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKS2 (m ': sh) x) -> AstNoSimplify s ('TKS2 (n ': sh) x) -> AstNoSimplify s ('TKS2 ((m + n) ': sh) x) Source # tsslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> AstNoSimplify s ('TKS2 (((i + n) + k) ': sh) x) -> AstNoSimplify s ('TKS2 (n ': sh) x) Source # tsreverse :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKS2 (n ': sh) x) -> AstNoSimplify s ('TKS2 (n ': sh) x) Source # tstranspose :: forall (perm :: [Natural]) (sh :: [Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> AstNoSimplify s ('TKS2 sh x) -> AstNoSimplify s ('TKS2 (PermutePrefix perm sh) x) Source # tsreshape :: forall (sh :: [Natural]) (sh2 :: [Natural]) (x :: TK). (Product sh ~ Product sh2, KnownSTK x) => ShS sh2 -> AstNoSimplify s ('TKS2 sh x) -> AstNoSimplify s ('TKS2 sh2 x) Source # txappend :: forall (m :: Nat) (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKX2 ('Just m ': sh) x) -> AstNoSimplify s ('TKX2 ('Just n ': sh) x) -> AstNoSimplify s ('TKX2 ('Just (m + n) ': sh) x) Source # txslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Maybe Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> AstNoSimplify s ('TKX2 ('Just ((i + n) + k) ': sh) x) -> AstNoSimplify s ('TKX2 ('Just n ': sh) x) Source # txreverse :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoSimplify s ('TKX2 (mn ': sh) x) -> AstNoSimplify s ('TKX2 (mn ': sh) x) Source # txtranspose :: forall (perm :: [Natural]) (sh :: [Maybe Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> AstNoSimplify s ('TKX2 sh x) -> AstNoSimplify s ('TKX2 (PermutePrefix perm sh) x) Source # txreshape :: forall (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh2 -> AstNoSimplify s ('TKX2 sh x) -> AstNoSimplify s ('TKX2 sh2 x) Source # trbuild1 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> (IntOf (AstNoSimplify s) -> AstNoSimplify s ('TKR2 n x)) -> AstNoSimplify s ('TKR2 (1 + n) x) Source # trmap0N :: forall (n :: Nat) (x :: TK) (x1 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1) => (AstNoSimplify s ('TKR2 0 x1) -> AstNoSimplify s ('TKR2 0 x)) -> AstNoSimplify s ('TKR2 n x1) -> AstNoSimplify s ('TKR2 n x) Source # trzipWith0N :: forall (n :: Nat) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1, KnownSTK x2) => (AstNoSimplify s ('TKR2 0 x1) -> AstNoSimplify s ('TKR2 0 x2) -> AstNoSimplify s ('TKR2 0 x)) -> AstNoSimplify s ('TKR2 n x1) -> AstNoSimplify s ('TKR2 n x2) -> AstNoSimplify s ('TKR2 n x) Source # tsbuild1 :: forall (k :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat k, KnownShS sh, KnownSTK x) => (IntOf (AstNoSimplify s) -> AstNoSimplify s ('TKS2 sh x)) -> AstNoSimplify s ('TKS2 (k ': sh) x) Source # tsmap0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1) => (AstNoSimplify s ('TKS2 ('[] :: [Nat]) x1) -> AstNoSimplify s ('TKS2 ('[] :: [Nat]) x)) -> AstNoSimplify s ('TKS2 sh x1) -> AstNoSimplify s ('TKS2 sh x) Source # tszipWith0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1, KnownSTK x2) => (AstNoSimplify s ('TKS2 ('[] :: [Nat]) x1) -> AstNoSimplify s ('TKS2 ('[] :: [Nat]) x2) -> AstNoSimplify s ('TKS2 ('[] :: [Nat]) x)) -> AstNoSimplify s ('TKS2 sh x1) -> AstNoSimplify s ('TKS2 sh x2) -> AstNoSimplify s ('TKS2 sh x) Source # txbuild1 :: forall (k :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat k, KnownShX sh, KnownSTK x) => (IntOf (AstNoSimplify s) -> AstNoSimplify s ('TKX2 sh x)) -> AstNoSimplify s ('TKX2 ('Just k ': sh) x) Source # tbuild1 :: forall (y :: TK) (k :: Nat). ConvertTensor (AstNoSimplify s) => SNat k -> SingletonTK y -> (IntOf (AstNoSimplify s) -> AstNoSimplify s y) -> AstNoSimplify s (BuildTensorKind k y) Source # tmapAccumRDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy (AstNoSimplify s) -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf (AstNoSimplify s) ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf (AstNoSimplify s) ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf (AstNoSimplify s) ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> AstNoSimplify s accy -> AstNoSimplify s (BuildTensorKind k ey) -> AstNoSimplify s ('TKProduct accy (BuildTensorKind k by)) Source # tmapAccumLDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy (AstNoSimplify s) -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf (AstNoSimplify s) ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf (AstNoSimplify s) ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf (AstNoSimplify s) ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> AstNoSimplify s accy -> AstNoSimplify s (BuildTensorKind k ey) -> AstNoSimplify s ('TKProduct accy (BuildTensorKind k by)) Source # tApply :: forall (x :: TK) (z :: TK). HFunOf (AstNoSimplify s) x z -> AstNoSimplify s x -> AstNoSimplify s z Source # tlambda :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstNoSimplify s) x z Source # tgrad :: forall (x :: TK) r. FullShapeTK x -> HFun x ('TKScalar r) -> HFunOf (AstNoSimplify s) x (ADTensorKind x) Source # tvjp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstNoSimplify s) ('TKProduct (ADTensorKind z) x) (ADTensorKind x) Source # tjvp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstNoSimplify s) ('TKProduct (ADTensorKind x) x) (ADTensorKind z) Source # tprimalPart :: forall (y :: TK). AstNoSimplify s y -> PrimalOf (AstNoSimplify s) y Source # tdualPart :: forall (y :: TK). SingletonTK y -> AstNoSimplify s y -> DualOf (AstNoSimplify s) y Source # tfromPrimal :: forall (y :: TK). SingletonTK y -> PrimalOf (AstNoSimplify s) y -> AstNoSimplify s y Source # tfromDual :: forall (y :: TK). DualOf (AstNoSimplify s) y -> AstNoSimplify s y Source # tScale :: forall (y :: TK). (Num (AstNoSimplify s y), Num (PrimalOf (AstNoSimplify s) y)) => SingletonTK y -> PrimalOf (AstNoSimplify s) y -> DualOf (AstNoSimplify s) y -> DualOf (AstNoSimplify s) y Source # tsum :: forall (z :: TK) (k :: Nat). ConvertTensor (AstNoSimplify s) => SNat k -> SingletonTK z -> AstNoSimplify s (BuildTensorKind k z) -> AstNoSimplify s z Source # treplicate :: forall (z :: TK) (k :: Nat). ConvertTensor (AstNoSimplify s) => SNat k -> SingletonTK z -> AstNoSimplify s z -> AstNoSimplify s (BuildTensorKind k z) Source # tindexBuild :: forall (z :: TK) (k :: Nat). ConvertTensor (AstNoSimplify s) => SNat k -> SingletonTK z -> AstNoSimplify s (BuildTensorKind k z) -> IntOf (AstNoSimplify s) -> AstNoSimplify s z Source # treplTarget :: forall (y :: TK). (forall r. GoodScalar r => r) -> FullShapeTK y -> AstNoSimplify s y Source # tdefTarget :: forall (y :: TK). FullShapeTK y -> AstNoSimplify s y Source # taddTarget :: forall (y :: TK). SingletonTK y -> AstNoSimplify s y -> AstNoSimplify s y -> AstNoSimplify s y Source # tmultTarget :: forall (y :: TK). SingletonTK y -> AstNoSimplify s y -> AstNoSimplify s y -> AstNoSimplify s y Source # tsum0Target :: forall (y :: TK). FullShapeTK y -> AstNoSimplify s y -> AstNoSimplify s ('TKScalar Double) Source # tdot0Target :: forall (y :: TK). FullShapeTK y -> AstNoSimplify s y -> AstNoSimplify s y -> AstNoSimplify s ('TKScalar Double) Source # xmcast :: forall (x :: TK) (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]). (KnownSTK x, KnownShX sh, Rank sh ~ Rank sh2, ConvertTensor (AstNoSimplify s)) => StaticShX sh2 -> AstNoSimplify s ('TKX2 sh x) -> AstNoSimplify s ('TKX2 sh2 x) Source # | |
AstSpan s => BaseTensor (AstNoVectorize s) Source # | |
Defined in HordeAd.Core.OpsAst Methods rshape :: forall (n :: Nat) (x :: TK). KnownSTK x => AstNoVectorize s ('TKR2 n x) -> IShR n Source # rlength :: forall (n :: Nat) (x :: TK). KnownSTK x => AstNoVectorize s ('TKR2 n x) -> Int Source # rsize :: forall (n :: Nat) (x :: TK). KnownSTK x => AstNoVectorize s ('TKR2 n x) -> Int Source # rwidth :: forall (n :: Natural) (x :: TK). KnownSTK x => AstNoVectorize s ('TKR2 (1 + n) x) -> Int Source # sshape :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKS2 sh x) -> ShS sh Source # slength :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKS2 sh x) -> Int Source # ssize :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKS2 sh x) -> Int Source # swidth :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKS2 (n ': sh) x) -> Int Source # xshape :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKX2 sh x) -> IShX sh Source # xlength :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKX2 sh x) -> Int Source # xsize :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKX2 sh x) -> Int Source # xwidth :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKX2 (mn ': sh) x) -> Int Source # tsize :: forall (y :: TK). SingletonTK y -> AstNoVectorize s y -> Int Source # tftk :: forall (y :: TK). SingletonTK y -> AstNoVectorize s y -> FullShapeTK y Source # tpair :: forall (x :: TK) (z :: TK). AstNoVectorize s x -> AstNoVectorize s z -> AstNoVectorize s ('TKProduct x z) Source # tproject1 :: forall (x :: TK) (z :: TK). AstNoVectorize s ('TKProduct x z) -> AstNoVectorize s x Source # tproject2 :: forall (x :: TK) (z :: TK). AstNoVectorize s ('TKProduct x z) -> AstNoVectorize s z Source # tcond :: forall (y :: TK). Boolean (BoolOf (AstNoVectorize s)) => SingletonTK y -> BoolOf (AstNoVectorize s) -> AstNoVectorize s y -> AstNoVectorize s y -> AstNoVectorize s y Source # trconcrete :: forall r (n :: Nat). GoodScalar r => Ranked n r -> AstNoVectorize s (TKR n r) Source # tsconcrete :: forall r (sh :: [Nat]). GoodScalar r => Shaped sh r -> AstNoVectorize s (TKS sh r) Source # txconcrete :: forall r (sh :: [Maybe Nat]). GoodScalar r => Mixed sh r -> AstNoVectorize s (TKX sh r) Source # tkconcrete :: GoodScalar r => r -> AstNoVectorize s ('TKScalar r) Source # tconcrete :: forall (y :: TK). FullShapeTK y -> Concrete y -> AstNoVectorize s y Source # trfromVector :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Vector (AstNoVectorize s ('TKR2 n x)) -> AstNoVectorize s ('TKR2 (1 + n) x) Source # trfromVector0N :: forall (n :: Nat) (x :: TK). KnownSTK x => IShR n -> Vector (AstNoVectorize s ('TKR2 0 x)) -> AstNoVectorize s ('TKR2 n x) Source # trunravelToList :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstNoVectorize s ('TKR2 (1 + n) x) -> [AstNoVectorize s ('TKR2 n x)] Source # tsfromVector :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => Vector (AstNoVectorize s ('TKS2 sh x)) -> AstNoVectorize s ('TKS2 (n ': sh) x) Source # tsfromVector0N :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => Vector (AstNoVectorize s ('TKS2 ('[] :: [Nat]) x)) -> AstNoVectorize s ('TKS2 sh x) Source # tsunravelToList :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => AstNoVectorize s ('TKS2 (n ': sh) x) -> [AstNoVectorize s ('TKS2 sh x)] Source # txfromVector :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => Vector (AstNoVectorize s ('TKX2 sh x)) -> AstNoVectorize s ('TKX2 ('Just n ': sh) x) Source # txfromVector0N :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh -> Vector (AstNoVectorize s ('TKX2 ('[] :: [Maybe Nat]) x)) -> AstNoVectorize s ('TKX2 sh x) Source # txunravelToList :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => AstNoVectorize s ('TKX2 ('Just n ': sh) x) -> [AstNoVectorize s ('TKX2 sh x)] Source # tfromVector :: forall (y :: TK) (k :: Nat). SNat k -> SingletonTK y -> Vector (AstNoVectorize s y) -> AstNoVectorize s (BuildTensorKind k y) Source # tfromListR :: forall (y :: TK) (k :: Nat). SingletonTK y -> ListR k (AstNoVectorize s y) -> AstNoVectorize s (BuildTensorKind k y) Source # trsum :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstNoVectorize s ('TKR2 (1 + n) x) -> AstNoVectorize s ('TKR2 n x) Source # trsum0 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstNoVectorize s ('TKR2 n x) -> AstNoVectorize s ('TKR2 0 x) Source # trdot0 :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstNoVectorize s (TKR n r) -> AstNoVectorize s (TKR n r) -> AstNoVectorize s (TKR 0 r) Source # trdot1In :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstNoVectorize s (TKR (1 + n) r) -> AstNoVectorize s (TKR (1 + n) r) -> AstNoVectorize s (TKR n r) Source # trmatvecmul :: GoodScalar r => AstNoVectorize s (TKR 2 r) -> AstNoVectorize s (TKR 1 r) -> AstNoVectorize s (TKR 1 r) Source # trmatmul2 :: GoodScalar r => AstNoVectorize s (TKR 2 r) -> AstNoVectorize s (TKR 2 r) -> AstNoVectorize s (TKR 2 r) Source # trreplicate :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> AstNoVectorize s ('TKR2 n x) -> AstNoVectorize s ('TKR2 (1 + n) x) Source # trreplicate0N :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => IShR n -> AstNoVectorize s ('TKR2 0 x) -> AstNoVectorize s ('TKR2 n x) Source # tssum :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => AstNoVectorize s ('TKS2 (n ': sh) x) -> AstNoVectorize s ('TKS2 sh x) Source # tssum0 :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => AstNoVectorize s ('TKS2 sh x) -> AstNoVectorize s ('TKS2 ('[] :: [Nat]) x) Source # tsdot0 :: forall (sh :: [Nat]) r. (KnownShS sh, GoodScalar r) => AstNoVectorize s (TKS sh r) -> AstNoVectorize s (TKS sh r) -> AstNoVectorize s (TKS ('[] :: [Nat]) r) Source # tsdot1In :: forall (sh :: [Nat]) r (n :: Nat). (KnownShS sh, GoodScalar r) => SNat n -> AstNoVectorize s (TKS (sh ++ '[n]) r) -> AstNoVectorize s (TKS (sh ++ '[n]) r) -> AstNoVectorize s (TKS sh r) Source # tsmatvecmul :: forall (m :: Nat) (n :: Nat) r. (KnownNat m, KnownNat n, GoodScalar r) => AstNoVectorize s (TKS '[m, n] r) -> AstNoVectorize s (TKS '[n] r) -> AstNoVectorize s (TKS '[m] r) Source # tsmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r) => AstNoVectorize s (TKS '[m, n] r) -> AstNoVectorize s (TKS '[n, p] r) -> AstNoVectorize s (TKS '[m, p] r) Source # tsreplicate :: forall (sh :: [Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> ShS sh -> AstNoVectorize s ('TKS2 sh x) -> AstNoVectorize s ('TKS2 (k ': sh) x) Source # tsreplicate0N :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => ShS sh -> AstNoVectorize s ('TKS2 ('[] :: [Nat]) x) -> AstNoVectorize s ('TKS2 sh x) Source # txsum :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => AstNoVectorize s ('TKX2 ('Just n ': sh) x) -> AstNoVectorize s ('TKX2 sh x) Source # txsum0 :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x, ConvertTensor (AstNoVectorize s)) => AstNoVectorize s ('TKX2 sh x) -> AstNoVectorize s ('TKX2 ('[] :: [Maybe Nat]) x) Source # txdot0 :: forall (sh :: [Maybe Nat]) r. (KnownShX sh, GoodScalar r, ConvertTensor (AstNoVectorize s)) => AstNoVectorize s (TKX sh r) -> AstNoVectorize s (TKX sh r) -> AstNoVectorize s (TKX ('[] :: [Maybe Nat]) r) Source # txdot1In :: forall (sh :: [Maybe Nat]) r (n :: Nat). (KnownShX sh, GoodScalar r) => SNat n -> AstNoVectorize s (TKX (sh ++ '['Just n]) r) -> AstNoVectorize s (TKX (sh ++ '['Just n]) r) -> AstNoVectorize s (TKX sh r) Source # txmatvecmul :: forall (mm :: Maybe Nat) (mn :: Maybe Nat) r. (GoodScalar r, ConvertTensor (AstNoVectorize s)) => SMayNat Int SNat mm -> SMayNat Int SNat mn -> AstNoVectorize s (TKX '[mm, mn] r) -> AstNoVectorize s (TKX '[mn] r) -> AstNoVectorize s (TKX '[mm] r) Source # txmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r, ConvertTensor (AstNoVectorize s)) => AstNoVectorize s (TKX '['Just m, 'Just n] r) -> AstNoVectorize s (TKX '['Just n, 'Just p] r) -> AstNoVectorize s (TKX '['Just m, 'Just p] r) Source # txreplicate :: forall (sh :: [Maybe Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> StaticShX sh -> AstNoVectorize s ('TKX2 sh x) -> AstNoVectorize s ('TKX2 ('Just k ': sh) x) Source # txreplicate0N :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x) => IShX sh -> AstNoVectorize s ('TKX2 ('[] :: [Maybe Nat]) x) -> AstNoVectorize s ('TKX2 sh x) Source # trindex :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x) => AstNoVectorize s ('TKR2 (m + n) x) -> IxROf (AstNoVectorize s) m -> AstNoVectorize s ('TKR2 n x) Source # trindex0 :: forall (m :: Nat) (x :: TK). (KnownNat m, KnownSTK x) => AstNoVectorize s ('TKR2 m x) -> IxROf (AstNoVectorize s) m -> AstNoVectorize s ('TKR2 0 x) Source # troneHot :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x, BoolOf (PrimalOf (AstNoVectorize s)) ~ BoolOf (AstNoVectorize s), EqH (PrimalOf (AstNoVectorize s)) ('TKScalar Int64)) => IShR m -> AstNoVectorize s ('TKR2 n x) -> IxROf (AstNoVectorize s) m -> AstNoVectorize s ('TKR2 (m + n) x) Source # trscatter :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> AstNoVectorize s ('TKR2 (m + n) x) -> (IxROf (AstNoVectorize s) m -> IxROf (AstNoVectorize s) p) -> AstNoVectorize s ('TKR2 (p + n) x) Source # trscatter1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> AstNoVectorize s ('TKR2 (1 + n) x) -> (IntOf (AstNoVectorize s) -> IxROf (AstNoVectorize s) p) -> AstNoVectorize s ('TKR2 (p + n) x) Source # trgather :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (m + n) -> AstNoVectorize s ('TKR2 (p + n) x) -> (IxROf (AstNoVectorize s) m -> IxROf (AstNoVectorize s) p) -> AstNoVectorize s ('TKR2 (m + n) x) Source # trgather1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => Int -> AstNoVectorize s ('TKR2 (p + n) x) -> (IntOf (AstNoVectorize s) -> IxROf (AstNoVectorize s) p) -> AstNoVectorize s ('TKR2 (1 + n) x) Source # tsindex :: forall (shm :: [Nat]) (shn :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownSTK x) => AstNoVectorize s ('TKS2 (shm ++ shn) x) -> IxSOf (AstNoVectorize s) shm -> AstNoVectorize s ('TKS2 shn x) Source # tsindex0 :: forall (sh1 :: [Nat]) (x :: TK). (KnownShS sh1, KnownSTK x) => AstNoVectorize s ('TKS2 sh1 x) -> IxSOf (AstNoVectorize s) sh1 -> AstNoVectorize s ('TKS2 ('[] :: [Nat]) x) Source # tsoneHot :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (x :: TK). (KnownShS sh1, KnownShS sh2, KnownSTK x, BoolOf (PrimalOf (AstNoVectorize s)) ~ BoolOf (AstNoVectorize s), EqH (PrimalOf (AstNoVectorize s)) ('TKScalar Int64)) => AstNoVectorize s ('TKS2 sh2 x) -> IxSOf (AstNoVectorize s) sh1 -> AstNoVectorize s ('TKS2 (sh1 ++ sh2) x) Source # tsscatter :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => AstNoVectorize s ('TKS2 (shm ++ shn) x) -> (IxSOf (AstNoVectorize s) shm -> IxSOf (AstNoVectorize s) shp) -> AstNoVectorize s ('TKS2 (shp ++ shn) x) Source # tsscatter1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => AstNoVectorize s ('TKS2 (n2 ': shn) x) -> (IntOf (AstNoVectorize s) -> IxSOf (AstNoVectorize s) shp) -> AstNoVectorize s ('TKS2 (shp ++ shn) x) Source # tsgather :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => AstNoVectorize s ('TKS2 (shp ++ shn) x) -> (IxSOf (AstNoVectorize s) shm -> IxSOf (AstNoVectorize s) shp) -> AstNoVectorize s ('TKS2 (shm ++ shn) x) Source # tsgather1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => AstNoVectorize s ('TKS2 (shp ++ shn) x) -> (IntOf (AstNoVectorize s) -> IxSOf (AstNoVectorize s) shp) -> AstNoVectorize s ('TKS2 (n2 ': shn) x) Source # txindex :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x) => AstNoVectorize s ('TKX2 (sh1 ++ sh2) x) -> IxXOf (AstNoVectorize s) sh1 -> AstNoVectorize s ('TKX2 sh2 x) Source # txindex0 :: forall (sh1 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownSTK x) => AstNoVectorize s ('TKX2 sh1 x) -> IxXOf (AstNoVectorize s) sh1 -> AstNoVectorize s ('TKX2 ('[] :: [Maybe Nat]) x) Source # txoneHot :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x, BoolOf (PrimalOf (AstNoVectorize s)) ~ BoolOf (AstNoVectorize s), EqH (PrimalOf (AstNoVectorize s)) ('TKScalar Int64), ConvertTensor (AstNoVectorize s)) => IShX sh1 -> AstNoVectorize s ('TKX2 sh2 x) -> IxXOf (AstNoVectorize s) sh1 -> AstNoVectorize s ('TKX2 (sh1 ++ sh2) x) Source # txscatter :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> AstNoVectorize s ('TKX2 (shm ++ shn) x) -> (IxXOf (AstNoVectorize s) shm -> IxXOf (AstNoVectorize s) shp) -> AstNoVectorize s ('TKX2 (shp ++ shn) x) Source # txscatter1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> AstNoVectorize s ('TKX2 ('Just n2 ': shn) x) -> (IntOf (AstNoVectorize s) -> IxXOf (AstNoVectorize s) shp) -> AstNoVectorize s ('TKX2 (shp ++ shn) x) Source # txgather :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shm ++ shn) -> AstNoVectorize s ('TKX2 (shp ++ shn) x) -> (IxXOf (AstNoVectorize s) shm -> IxXOf (AstNoVectorize s) shp) -> AstNoVectorize s ('TKX2 (shm ++ shn) x) Source # txgather1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => SNat n2 -> AstNoVectorize s ('TKX2 (shp ++ shn) x) -> (IntOf (AstNoVectorize s) -> IxXOf (AstNoVectorize s) shp) -> AstNoVectorize s ('TKX2 ('Just n2 ': shn) x) Source # trfloor :: forall r r2 (n :: Nat). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstNoVectorize s (TKR n r) -> AstNoVectorize s (TKR n r2) Source # trfromIntegral :: forall r1 r2 (n :: Nat). (GoodScalar r1, Integral r1, GoodScalar r2) => AstNoVectorize s (TKR n r1) -> AstNoVectorize s (TKR n r2) Source # trcast :: forall r1 r2 (n :: Nat). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstNoVectorize s (TKR n r1) -> AstNoVectorize s (TKR n r2) Source # trminIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => AstNoVectorize s (TKR (1 + n) r) -> AstNoVectorize s (TKR n r2) Source # trmaxIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => AstNoVectorize s (TKR (1 + n) r) -> AstNoVectorize s (TKR n r2) Source # triota :: GoodScalar r => Int -> AstNoVectorize s (TKR 1 r) Source # tsfloor :: forall r r2 (sh :: [Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstNoVectorize s (TKS sh r) -> AstNoVectorize s (TKS sh r2) Source # tsfromIntegral :: forall r1 r2 (sh :: [Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => AstNoVectorize s (TKS sh r1) -> AstNoVectorize s (TKS sh r2) Source # tscast :: forall r1 r2 (sh :: [Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstNoVectorize s (TKS sh r1) -> AstNoVectorize s (TKS sh r2) Source # tsminIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstNoVectorize s (TKS (n ': sh) r) -> AstNoVectorize s (TKS (Init (n ': sh)) r2) Source # tsmaxIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstNoVectorize s (TKS (n ': sh) r) -> AstNoVectorize s (TKS (Init (n ': sh)) r2) Source # tsiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstNoVectorize s (TKS '[n] r) Source # txfloor :: forall r r2 (sh :: [Maybe Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstNoVectorize s (TKX sh r) -> AstNoVectorize s (TKX sh r2) Source # txfromIntegral :: forall r1 r2 (sh :: [Maybe Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => AstNoVectorize s (TKX sh r1) -> AstNoVectorize s (TKX sh r2) Source # txcast :: forall r1 r2 (sh :: [Maybe Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstNoVectorize s (TKX sh r1) -> AstNoVectorize s (TKX sh r2) Source # txminIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstNoVectorize s (TKX (mn ': sh) r) -> AstNoVectorize s (TKX (Init (mn ': sh)) r2) Source # txmaxIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstNoVectorize s (TKX (mn ': sh) r) -> AstNoVectorize s (TKX (Init (mn ': sh)) r2) Source # txiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstNoVectorize s (TKX '['Just n] r) Source # tkfloor :: (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstNoVectorize s ('TKScalar r) -> AstNoVectorize s ('TKScalar r2) Source # tkfromIntegral :: (GoodScalar r1, Integral r1, GoodScalar r2) => AstNoVectorize s ('TKScalar r1) -> AstNoVectorize s ('TKScalar r2) Source # tkcast :: (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstNoVectorize s ('TKScalar r1) -> AstNoVectorize s ('TKScalar r2) Source # trappend :: forall (n :: Natural) (x :: TK). KnownSTK x => AstNoVectorize s ('TKR2 (1 + n) x) -> AstNoVectorize s ('TKR2 (1 + n) x) -> AstNoVectorize s ('TKR2 (1 + n) x) Source # trslice :: forall (n :: Natural) (x :: TK). KnownSTK x => Int -> Int -> AstNoVectorize s ('TKR2 (1 + n) x) -> AstNoVectorize s ('TKR2 (1 + n) x) Source # trreverse :: forall (n :: Natural) (x :: TK). KnownSTK x => AstNoVectorize s ('TKR2 (1 + n) x) -> AstNoVectorize s ('TKR2 (1 + n) x) Source # trtranspose :: forall (n :: Nat) (x :: TK). KnownSTK x => PermR -> AstNoVectorize s ('TKR2 n x) -> AstNoVectorize s ('TKR2 n x) Source # trreshape :: forall (n :: Nat) (m :: Nat) (x :: TK). KnownSTK x => IShR m -> AstNoVectorize s ('TKR2 n x) -> AstNoVectorize s ('TKR2 m x) Source # tsappend :: forall (m :: Nat) (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKS2 (m ': sh) x) -> AstNoVectorize s ('TKS2 (n ': sh) x) -> AstNoVectorize s ('TKS2 ((m + n) ': sh) x) Source # tsslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> AstNoVectorize s ('TKS2 (((i + n) + k) ': sh) x) -> AstNoVectorize s ('TKS2 (n ': sh) x) Source # tsreverse :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKS2 (n ': sh) x) -> AstNoVectorize s ('TKS2 (n ': sh) x) Source # tstranspose :: forall (perm :: [Natural]) (sh :: [Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> AstNoVectorize s ('TKS2 sh x) -> AstNoVectorize s ('TKS2 (PermutePrefix perm sh) x) Source # tsreshape :: forall (sh :: [Natural]) (sh2 :: [Natural]) (x :: TK). (Product sh ~ Product sh2, KnownSTK x) => ShS sh2 -> AstNoVectorize s ('TKS2 sh x) -> AstNoVectorize s ('TKS2 sh2 x) Source # txappend :: forall (m :: Nat) (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKX2 ('Just m ': sh) x) -> AstNoVectorize s ('TKX2 ('Just n ': sh) x) -> AstNoVectorize s ('TKX2 ('Just (m + n) ': sh) x) Source # txslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Maybe Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> AstNoVectorize s ('TKX2 ('Just ((i + n) + k) ': sh) x) -> AstNoVectorize s ('TKX2 ('Just n ': sh) x) Source # txreverse :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstNoVectorize s ('TKX2 (mn ': sh) x) -> AstNoVectorize s ('TKX2 (mn ': sh) x) Source # txtranspose :: forall (perm :: [Natural]) (sh :: [Maybe Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> AstNoVectorize s ('TKX2 sh x) -> AstNoVectorize s ('TKX2 (PermutePrefix perm sh) x) Source # txreshape :: forall (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh2 -> AstNoVectorize s ('TKX2 sh x) -> AstNoVectorize s ('TKX2 sh2 x) Source # trbuild1 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> (IntOf (AstNoVectorize s) -> AstNoVectorize s ('TKR2 n x)) -> AstNoVectorize s ('TKR2 (1 + n) x) Source # trmap0N :: forall (n :: Nat) (x :: TK) (x1 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1) => (AstNoVectorize s ('TKR2 0 x1) -> AstNoVectorize s ('TKR2 0 x)) -> AstNoVectorize s ('TKR2 n x1) -> AstNoVectorize s ('TKR2 n x) Source # trzipWith0N :: forall (n :: Nat) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1, KnownSTK x2) => (AstNoVectorize s ('TKR2 0 x1) -> AstNoVectorize s ('TKR2 0 x2) -> AstNoVectorize s ('TKR2 0 x)) -> AstNoVectorize s ('TKR2 n x1) -> AstNoVectorize s ('TKR2 n x2) -> AstNoVectorize s ('TKR2 n x) Source # tsbuild1 :: forall (k :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat k, KnownShS sh, KnownSTK x) => (IntOf (AstNoVectorize s) -> AstNoVectorize s ('TKS2 sh x)) -> AstNoVectorize s ('TKS2 (k ': sh) x) Source # tsmap0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1) => (AstNoVectorize s ('TKS2 ('[] :: [Nat]) x1) -> AstNoVectorize s ('TKS2 ('[] :: [Nat]) x)) -> AstNoVectorize s ('TKS2 sh x1) -> AstNoVectorize s ('TKS2 sh x) Source # tszipWith0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1, KnownSTK x2) => (AstNoVectorize s ('TKS2 ('[] :: [Nat]) x1) -> AstNoVectorize s ('TKS2 ('[] :: [Nat]) x2) -> AstNoVectorize s ('TKS2 ('[] :: [Nat]) x)) -> AstNoVectorize s ('TKS2 sh x1) -> AstNoVectorize s ('TKS2 sh x2) -> AstNoVectorize s ('TKS2 sh x) Source # txbuild1 :: forall (k :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat k, KnownShX sh, KnownSTK x) => (IntOf (AstNoVectorize s) -> AstNoVectorize s ('TKX2 sh x)) -> AstNoVectorize s ('TKX2 ('Just k ': sh) x) Source # tbuild1 :: forall (y :: TK) (k :: Nat). ConvertTensor (AstNoVectorize s) => SNat k -> SingletonTK y -> (IntOf (AstNoVectorize s) -> AstNoVectorize s y) -> AstNoVectorize s (BuildTensorKind k y) Source # tmapAccumRDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy (AstNoVectorize s) -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf (AstNoVectorize s) ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf (AstNoVectorize s) ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf (AstNoVectorize s) ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> AstNoVectorize s accy -> AstNoVectorize s (BuildTensorKind k ey) -> AstNoVectorize s ('TKProduct accy (BuildTensorKind k by)) Source # tmapAccumLDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy (AstNoVectorize s) -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf (AstNoVectorize s) ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf (AstNoVectorize s) ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf (AstNoVectorize s) ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> AstNoVectorize s accy -> AstNoVectorize s (BuildTensorKind k ey) -> AstNoVectorize s ('TKProduct accy (BuildTensorKind k by)) Source # tApply :: forall (x :: TK) (z :: TK). HFunOf (AstNoVectorize s) x z -> AstNoVectorize s x -> AstNoVectorize s z Source # tlambda :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstNoVectorize s) x z Source # tgrad :: forall (x :: TK) r. FullShapeTK x -> HFun x ('TKScalar r) -> HFunOf (AstNoVectorize s) x (ADTensorKind x) Source # tvjp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstNoVectorize s) ('TKProduct (ADTensorKind z) x) (ADTensorKind x) Source # tjvp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstNoVectorize s) ('TKProduct (ADTensorKind x) x) (ADTensorKind z) Source # tprimalPart :: forall (y :: TK). AstNoVectorize s y -> PrimalOf (AstNoVectorize s) y Source # tdualPart :: forall (y :: TK). SingletonTK y -> AstNoVectorize s y -> DualOf (AstNoVectorize s) y Source # tfromPrimal :: forall (y :: TK). SingletonTK y -> PrimalOf (AstNoVectorize s) y -> AstNoVectorize s y Source # tfromDual :: forall (y :: TK). DualOf (AstNoVectorize s) y -> AstNoVectorize s y Source # tScale :: forall (y :: TK). (Num (AstNoVectorize s y), Num (PrimalOf (AstNoVectorize s) y)) => SingletonTK y -> PrimalOf (AstNoVectorize s) y -> DualOf (AstNoVectorize s) y -> DualOf (AstNoVectorize s) y Source # tsum :: forall (z :: TK) (k :: Nat). ConvertTensor (AstNoVectorize s) => SNat k -> SingletonTK z -> AstNoVectorize s (BuildTensorKind k z) -> AstNoVectorize s z Source # treplicate :: forall (z :: TK) (k :: Nat). ConvertTensor (AstNoVectorize s) => SNat k -> SingletonTK z -> AstNoVectorize s z -> AstNoVectorize s (BuildTensorKind k z) Source # tindexBuild :: forall (z :: TK) (k :: Nat). ConvertTensor (AstNoVectorize s) => SNat k -> SingletonTK z -> AstNoVectorize s (BuildTensorKind k z) -> IntOf (AstNoVectorize s) -> AstNoVectorize s z Source # treplTarget :: forall (y :: TK). (forall r. GoodScalar r => r) -> FullShapeTK y -> AstNoVectorize s y Source # tdefTarget :: forall (y :: TK). FullShapeTK y -> AstNoVectorize s y Source # taddTarget :: forall (y :: TK). SingletonTK y -> AstNoVectorize s y -> AstNoVectorize s y -> AstNoVectorize s y Source # tmultTarget :: forall (y :: TK). SingletonTK y -> AstNoVectorize s y -> AstNoVectorize s y -> AstNoVectorize s y Source # tsum0Target :: forall (y :: TK). FullShapeTK y -> AstNoVectorize s y -> AstNoVectorize s ('TKScalar Double) Source # tdot0Target :: forall (y :: TK). FullShapeTK y -> AstNoVectorize s y -> AstNoVectorize s y -> AstNoVectorize s ('TKScalar Double) Source # xmcast :: forall (x :: TK) (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]). (KnownSTK x, KnownShX sh, Rank sh ~ Rank sh2, ConvertTensor (AstNoVectorize s)) => StaticShX sh2 -> AstNoVectorize s ('TKX2 sh x) -> AstNoVectorize s ('TKX2 sh2 x) Source # | |
AstSpan s => BaseTensor (AstRaw s) Source # | |
Defined in HordeAd.Core.OpsAst Methods rshape :: forall (n :: Nat) (x :: TK). KnownSTK x => AstRaw s ('TKR2 n x) -> IShR n Source # rlength :: forall (n :: Nat) (x :: TK). KnownSTK x => AstRaw s ('TKR2 n x) -> Int Source # rsize :: forall (n :: Nat) (x :: TK). KnownSTK x => AstRaw s ('TKR2 n x) -> Int Source # rwidth :: forall (n :: Natural) (x :: TK). KnownSTK x => AstRaw s ('TKR2 (1 + n) x) -> Int Source # sshape :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKS2 sh x) -> ShS sh Source # slength :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKS2 sh x) -> Int Source # ssize :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKS2 sh x) -> Int Source # swidth :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKS2 (n ': sh) x) -> Int Source # xshape :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKX2 sh x) -> IShX sh Source # xlength :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKX2 sh x) -> Int Source # xsize :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKX2 sh x) -> Int Source # xwidth :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKX2 (mn ': sh) x) -> Int Source # tsize :: forall (y :: TK). SingletonTK y -> AstRaw s y -> Int Source # tftk :: forall (y :: TK). SingletonTK y -> AstRaw s y -> FullShapeTK y Source # tpair :: forall (x :: TK) (z :: TK). AstRaw s x -> AstRaw s z -> AstRaw s ('TKProduct x z) Source # tproject1 :: forall (x :: TK) (z :: TK). AstRaw s ('TKProduct x z) -> AstRaw s x Source # tproject2 :: forall (x :: TK) (z :: TK). AstRaw s ('TKProduct x z) -> AstRaw s z Source # tcond :: forall (y :: TK). Boolean (BoolOf (AstRaw s)) => SingletonTK y -> BoolOf (AstRaw s) -> AstRaw s y -> AstRaw s y -> AstRaw s y Source # trconcrete :: forall r (n :: Nat). GoodScalar r => Ranked n r -> AstRaw s (TKR n r) Source # tsconcrete :: forall r (sh :: [Nat]). GoodScalar r => Shaped sh r -> AstRaw s (TKS sh r) Source # txconcrete :: forall r (sh :: [Maybe Nat]). GoodScalar r => Mixed sh r -> AstRaw s (TKX sh r) Source # tkconcrete :: GoodScalar r => r -> AstRaw s ('TKScalar r) Source # tconcrete :: forall (y :: TK). FullShapeTK y -> Concrete y -> AstRaw s y Source # trfromVector :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Vector (AstRaw s ('TKR2 n x)) -> AstRaw s ('TKR2 (1 + n) x) Source # trfromVector0N :: forall (n :: Nat) (x :: TK). KnownSTK x => IShR n -> Vector (AstRaw s ('TKR2 0 x)) -> AstRaw s ('TKR2 n x) Source # trunravelToList :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstRaw s ('TKR2 (1 + n) x) -> [AstRaw s ('TKR2 n x)] Source # tsfromVector :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => Vector (AstRaw s ('TKS2 sh x)) -> AstRaw s ('TKS2 (n ': sh) x) Source # tsfromVector0N :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => Vector (AstRaw s ('TKS2 ('[] :: [Nat]) x)) -> AstRaw s ('TKS2 sh x) Source # tsunravelToList :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => AstRaw s ('TKS2 (n ': sh) x) -> [AstRaw s ('TKS2 sh x)] Source # txfromVector :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => Vector (AstRaw s ('TKX2 sh x)) -> AstRaw s ('TKX2 ('Just n ': sh) x) Source # txfromVector0N :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh -> Vector (AstRaw s ('TKX2 ('[] :: [Maybe Nat]) x)) -> AstRaw s ('TKX2 sh x) Source # txunravelToList :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => AstRaw s ('TKX2 ('Just n ': sh) x) -> [AstRaw s ('TKX2 sh x)] Source # tfromVector :: forall (y :: TK) (k :: Nat). SNat k -> SingletonTK y -> Vector (AstRaw s y) -> AstRaw s (BuildTensorKind k y) Source # tfromListR :: forall (y :: TK) (k :: Nat). SingletonTK y -> ListR k (AstRaw s y) -> AstRaw s (BuildTensorKind k y) Source # trsum :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstRaw s ('TKR2 (1 + n) x) -> AstRaw s ('TKR2 n x) Source # trsum0 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstRaw s ('TKR2 n x) -> AstRaw s ('TKR2 0 x) Source # trdot0 :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstRaw s (TKR n r) -> AstRaw s (TKR n r) -> AstRaw s (TKR 0 r) Source # trdot1In :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstRaw s (TKR (1 + n) r) -> AstRaw s (TKR (1 + n) r) -> AstRaw s (TKR n r) Source # trmatvecmul :: GoodScalar r => AstRaw s (TKR 2 r) -> AstRaw s (TKR 1 r) -> AstRaw s (TKR 1 r) Source # trmatmul2 :: GoodScalar r => AstRaw s (TKR 2 r) -> AstRaw s (TKR 2 r) -> AstRaw s (TKR 2 r) Source # trreplicate :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> AstRaw s ('TKR2 n x) -> AstRaw s ('TKR2 (1 + n) x) Source # trreplicate0N :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => IShR n -> AstRaw s ('TKR2 0 x) -> AstRaw s ('TKR2 n x) Source # tssum :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => AstRaw s ('TKS2 (n ': sh) x) -> AstRaw s ('TKS2 sh x) Source # tssum0 :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => AstRaw s ('TKS2 sh x) -> AstRaw s ('TKS2 ('[] :: [Nat]) x) Source # tsdot0 :: forall (sh :: [Nat]) r. (KnownShS sh, GoodScalar r) => AstRaw s (TKS sh r) -> AstRaw s (TKS sh r) -> AstRaw s (TKS ('[] :: [Nat]) r) Source # tsdot1In :: forall (sh :: [Nat]) r (n :: Nat). (KnownShS sh, GoodScalar r) => SNat n -> AstRaw s (TKS (sh ++ '[n]) r) -> AstRaw s (TKS (sh ++ '[n]) r) -> AstRaw s (TKS sh r) Source # tsmatvecmul :: forall (m :: Nat) (n :: Nat) r. (KnownNat m, KnownNat n, GoodScalar r) => AstRaw s (TKS '[m, n] r) -> AstRaw s (TKS '[n] r) -> AstRaw s (TKS '[m] r) Source # tsmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r) => AstRaw s (TKS '[m, n] r) -> AstRaw s (TKS '[n, p] r) -> AstRaw s (TKS '[m, p] r) Source # tsreplicate :: forall (sh :: [Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> ShS sh -> AstRaw s ('TKS2 sh x) -> AstRaw s ('TKS2 (k ': sh) x) Source # tsreplicate0N :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => ShS sh -> AstRaw s ('TKS2 ('[] :: [Nat]) x) -> AstRaw s ('TKS2 sh x) Source # txsum :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => AstRaw s ('TKX2 ('Just n ': sh) x) -> AstRaw s ('TKX2 sh x) Source # txsum0 :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x, ConvertTensor (AstRaw s)) => AstRaw s ('TKX2 sh x) -> AstRaw s ('TKX2 ('[] :: [Maybe Nat]) x) Source # txdot0 :: forall (sh :: [Maybe Nat]) r. (KnownShX sh, GoodScalar r, ConvertTensor (AstRaw s)) => AstRaw s (TKX sh r) -> AstRaw s (TKX sh r) -> AstRaw s (TKX ('[] :: [Maybe Nat]) r) Source # txdot1In :: forall (sh :: [Maybe Nat]) r (n :: Nat). (KnownShX sh, GoodScalar r) => SNat n -> AstRaw s (TKX (sh ++ '['Just n]) r) -> AstRaw s (TKX (sh ++ '['Just n]) r) -> AstRaw s (TKX sh r) Source # txmatvecmul :: forall (mm :: Maybe Nat) (mn :: Maybe Nat) r. (GoodScalar r, ConvertTensor (AstRaw s)) => SMayNat Int SNat mm -> SMayNat Int SNat mn -> AstRaw s (TKX '[mm, mn] r) -> AstRaw s (TKX '[mn] r) -> AstRaw s (TKX '[mm] r) Source # txmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r, ConvertTensor (AstRaw s)) => AstRaw s (TKX '['Just m, 'Just n] r) -> AstRaw s (TKX '['Just n, 'Just p] r) -> AstRaw s (TKX '['Just m, 'Just p] r) Source # txreplicate :: forall (sh :: [Maybe Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> StaticShX sh -> AstRaw s ('TKX2 sh x) -> AstRaw s ('TKX2 ('Just k ': sh) x) Source # txreplicate0N :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x) => IShX sh -> AstRaw s ('TKX2 ('[] :: [Maybe Nat]) x) -> AstRaw s ('TKX2 sh x) Source # trindex :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x) => AstRaw s ('TKR2 (m + n) x) -> IxROf (AstRaw s) m -> AstRaw s ('TKR2 n x) Source # trindex0 :: forall (m :: Nat) (x :: TK). (KnownNat m, KnownSTK x) => AstRaw s ('TKR2 m x) -> IxROf (AstRaw s) m -> AstRaw s ('TKR2 0 x) Source # troneHot :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x, BoolOf (PrimalOf (AstRaw s)) ~ BoolOf (AstRaw s), EqH (PrimalOf (AstRaw s)) ('TKScalar Int64)) => IShR m -> AstRaw s ('TKR2 n x) -> IxROf (AstRaw s) m -> AstRaw s ('TKR2 (m + n) x) Source # trscatter :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> AstRaw s ('TKR2 (m + n) x) -> (IxROf (AstRaw s) m -> IxROf (AstRaw s) p) -> AstRaw s ('TKR2 (p + n) x) Source # trscatter1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> AstRaw s ('TKR2 (1 + n) x) -> (IntOf (AstRaw s) -> IxROf (AstRaw s) p) -> AstRaw s ('TKR2 (p + n) x) Source # trgather :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (m + n) -> AstRaw s ('TKR2 (p + n) x) -> (IxROf (AstRaw s) m -> IxROf (AstRaw s) p) -> AstRaw s ('TKR2 (m + n) x) Source # trgather1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => Int -> AstRaw s ('TKR2 (p + n) x) -> (IntOf (AstRaw s) -> IxROf (AstRaw s) p) -> AstRaw s ('TKR2 (1 + n) x) Source # tsindex :: forall (shm :: [Nat]) (shn :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownSTK x) => AstRaw s ('TKS2 (shm ++ shn) x) -> IxSOf (AstRaw s) shm -> AstRaw s ('TKS2 shn x) Source # tsindex0 :: forall (sh1 :: [Nat]) (x :: TK). (KnownShS sh1, KnownSTK x) => AstRaw s ('TKS2 sh1 x) -> IxSOf (AstRaw s) sh1 -> AstRaw s ('TKS2 ('[] :: [Nat]) x) Source # tsoneHot :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (x :: TK). (KnownShS sh1, KnownShS sh2, KnownSTK x, BoolOf (PrimalOf (AstRaw s)) ~ BoolOf (AstRaw s), EqH (PrimalOf (AstRaw s)) ('TKScalar Int64)) => AstRaw s ('TKS2 sh2 x) -> IxSOf (AstRaw s) sh1 -> AstRaw s ('TKS2 (sh1 ++ sh2) x) Source # tsscatter :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => AstRaw s ('TKS2 (shm ++ shn) x) -> (IxSOf (AstRaw s) shm -> IxSOf (AstRaw s) shp) -> AstRaw s ('TKS2 (shp ++ shn) x) Source # tsscatter1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => AstRaw s ('TKS2 (n2 ': shn) x) -> (IntOf (AstRaw s) -> IxSOf (AstRaw s) shp) -> AstRaw s ('TKS2 (shp ++ shn) x) Source # tsgather :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => AstRaw s ('TKS2 (shp ++ shn) x) -> (IxSOf (AstRaw s) shm -> IxSOf (AstRaw s) shp) -> AstRaw s ('TKS2 (shm ++ shn) x) Source # tsgather1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => AstRaw s ('TKS2 (shp ++ shn) x) -> (IntOf (AstRaw s) -> IxSOf (AstRaw s) shp) -> AstRaw s ('TKS2 (n2 ': shn) x) Source # txindex :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x) => AstRaw s ('TKX2 (sh1 ++ sh2) x) -> IxXOf (AstRaw s) sh1 -> AstRaw s ('TKX2 sh2 x) Source # txindex0 :: forall (sh1 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownSTK x) => AstRaw s ('TKX2 sh1 x) -> IxXOf (AstRaw s) sh1 -> AstRaw s ('TKX2 ('[] :: [Maybe Nat]) x) Source # txoneHot :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x, BoolOf (PrimalOf (AstRaw s)) ~ BoolOf (AstRaw s), EqH (PrimalOf (AstRaw s)) ('TKScalar Int64), ConvertTensor (AstRaw s)) => IShX sh1 -> AstRaw s ('TKX2 sh2 x) -> IxXOf (AstRaw s) sh1 -> AstRaw s ('TKX2 (sh1 ++ sh2) x) Source # txscatter :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> AstRaw s ('TKX2 (shm ++ shn) x) -> (IxXOf (AstRaw s) shm -> IxXOf (AstRaw s) shp) -> AstRaw s ('TKX2 (shp ++ shn) x) Source # txscatter1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> AstRaw s ('TKX2 ('Just n2 ': shn) x) -> (IntOf (AstRaw s) -> IxXOf (AstRaw s) shp) -> AstRaw s ('TKX2 (shp ++ shn) x) Source # txgather :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shm ++ shn) -> AstRaw s ('TKX2 (shp ++ shn) x) -> (IxXOf (AstRaw s) shm -> IxXOf (AstRaw s) shp) -> AstRaw s ('TKX2 (shm ++ shn) x) Source # txgather1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => SNat n2 -> AstRaw s ('TKX2 (shp ++ shn) x) -> (IntOf (AstRaw s) -> IxXOf (AstRaw s) shp) -> AstRaw s ('TKX2 ('Just n2 ': shn) x) Source # trfloor :: forall r r2 (n :: Nat). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstRaw s (TKR n r) -> AstRaw s (TKR n r2) Source # trfromIntegral :: forall r1 r2 (n :: Nat). (GoodScalar r1, Integral r1, GoodScalar r2) => AstRaw s (TKR n r1) -> AstRaw s (TKR n r2) Source # trcast :: forall r1 r2 (n :: Nat). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstRaw s (TKR n r1) -> AstRaw s (TKR n r2) Source # trminIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => AstRaw s (TKR (1 + n) r) -> AstRaw s (TKR n r2) Source # trmaxIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => AstRaw s (TKR (1 + n) r) -> AstRaw s (TKR n r2) Source # triota :: GoodScalar r => Int -> AstRaw s (TKR 1 r) Source # tsfloor :: forall r r2 (sh :: [Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstRaw s (TKS sh r) -> AstRaw s (TKS sh r2) Source # tsfromIntegral :: forall r1 r2 (sh :: [Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => AstRaw s (TKS sh r1) -> AstRaw s (TKS sh r2) Source # tscast :: forall r1 r2 (sh :: [Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstRaw s (TKS sh r1) -> AstRaw s (TKS sh r2) Source # tsminIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstRaw s (TKS (n ': sh) r) -> AstRaw s (TKS (Init (n ': sh)) r2) Source # tsmaxIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstRaw s (TKS (n ': sh) r) -> AstRaw s (TKS (Init (n ': sh)) r2) Source # tsiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstRaw s (TKS '[n] r) Source # txfloor :: forall r r2 (sh :: [Maybe Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstRaw s (TKX sh r) -> AstRaw s (TKX sh r2) Source # txfromIntegral :: forall r1 r2 (sh :: [Maybe Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => AstRaw s (TKX sh r1) -> AstRaw s (TKX sh r2) Source # txcast :: forall r1 r2 (sh :: [Maybe Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstRaw s (TKX sh r1) -> AstRaw s (TKX sh r2) Source # txminIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstRaw s (TKX (mn ': sh) r) -> AstRaw s (TKX (Init (mn ': sh)) r2) Source # txmaxIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstRaw s (TKX (mn ': sh) r) -> AstRaw s (TKX (Init (mn ': sh)) r2) Source # txiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstRaw s (TKX '['Just n] r) Source # tkfloor :: (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstRaw s ('TKScalar r) -> AstRaw s ('TKScalar r2) Source # tkfromIntegral :: (GoodScalar r1, Integral r1, GoodScalar r2) => AstRaw s ('TKScalar r1) -> AstRaw s ('TKScalar r2) Source # tkcast :: (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstRaw s ('TKScalar r1) -> AstRaw s ('TKScalar r2) Source # trappend :: forall (n :: Natural) (x :: TK). KnownSTK x => AstRaw s ('TKR2 (1 + n) x) -> AstRaw s ('TKR2 (1 + n) x) -> AstRaw s ('TKR2 (1 + n) x) Source # trslice :: forall (n :: Natural) (x :: TK). KnownSTK x => Int -> Int -> AstRaw s ('TKR2 (1 + n) x) -> AstRaw s ('TKR2 (1 + n) x) Source # trreverse :: forall (n :: Natural) (x :: TK). KnownSTK x => AstRaw s ('TKR2 (1 + n) x) -> AstRaw s ('TKR2 (1 + n) x) Source # trtranspose :: forall (n :: Nat) (x :: TK). KnownSTK x => PermR -> AstRaw s ('TKR2 n x) -> AstRaw s ('TKR2 n x) Source # trreshape :: forall (n :: Nat) (m :: Nat) (x :: TK). KnownSTK x => IShR m -> AstRaw s ('TKR2 n x) -> AstRaw s ('TKR2 m x) Source # tsappend :: forall (m :: Nat) (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKS2 (m ': sh) x) -> AstRaw s ('TKS2 (n ': sh) x) -> AstRaw s ('TKS2 ((m + n) ': sh) x) Source # tsslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> AstRaw s ('TKS2 (((i + n) + k) ': sh) x) -> AstRaw s ('TKS2 (n ': sh) x) Source # tsreverse :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKS2 (n ': sh) x) -> AstRaw s ('TKS2 (n ': sh) x) Source # tstranspose :: forall (perm :: [Natural]) (sh :: [Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> AstRaw s ('TKS2 sh x) -> AstRaw s ('TKS2 (PermutePrefix perm sh) x) Source # tsreshape :: forall (sh :: [Natural]) (sh2 :: [Natural]) (x :: TK). (Product sh ~ Product sh2, KnownSTK x) => ShS sh2 -> AstRaw s ('TKS2 sh x) -> AstRaw s ('TKS2 sh2 x) Source # txappend :: forall (m :: Nat) (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKX2 ('Just m ': sh) x) -> AstRaw s ('TKX2 ('Just n ': sh) x) -> AstRaw s ('TKX2 ('Just (m + n) ': sh) x) Source # txslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Maybe Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> AstRaw s ('TKX2 ('Just ((i + n) + k) ': sh) x) -> AstRaw s ('TKX2 ('Just n ': sh) x) Source # txreverse :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstRaw s ('TKX2 (mn ': sh) x) -> AstRaw s ('TKX2 (mn ': sh) x) Source # txtranspose :: forall (perm :: [Natural]) (sh :: [Maybe Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> AstRaw s ('TKX2 sh x) -> AstRaw s ('TKX2 (PermutePrefix perm sh) x) Source # txreshape :: forall (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh2 -> AstRaw s ('TKX2 sh x) -> AstRaw s ('TKX2 sh2 x) Source # trbuild1 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> (IntOf (AstRaw s) -> AstRaw s ('TKR2 n x)) -> AstRaw s ('TKR2 (1 + n) x) Source # trmap0N :: forall (n :: Nat) (x :: TK) (x1 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1) => (AstRaw s ('TKR2 0 x1) -> AstRaw s ('TKR2 0 x)) -> AstRaw s ('TKR2 n x1) -> AstRaw s ('TKR2 n x) Source # trzipWith0N :: forall (n :: Nat) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1, KnownSTK x2) => (AstRaw s ('TKR2 0 x1) -> AstRaw s ('TKR2 0 x2) -> AstRaw s ('TKR2 0 x)) -> AstRaw s ('TKR2 n x1) -> AstRaw s ('TKR2 n x2) -> AstRaw s ('TKR2 n x) Source # tsbuild1 :: forall (k :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat k, KnownShS sh, KnownSTK x) => (IntOf (AstRaw s) -> AstRaw s ('TKS2 sh x)) -> AstRaw s ('TKS2 (k ': sh) x) Source # tsmap0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1) => (AstRaw s ('TKS2 ('[] :: [Nat]) x1) -> AstRaw s ('TKS2 ('[] :: [Nat]) x)) -> AstRaw s ('TKS2 sh x1) -> AstRaw s ('TKS2 sh x) Source # tszipWith0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1, KnownSTK x2) => (AstRaw s ('TKS2 ('[] :: [Nat]) x1) -> AstRaw s ('TKS2 ('[] :: [Nat]) x2) -> AstRaw s ('TKS2 ('[] :: [Nat]) x)) -> AstRaw s ('TKS2 sh x1) -> AstRaw s ('TKS2 sh x2) -> AstRaw s ('TKS2 sh x) Source # txbuild1 :: forall (k :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat k, KnownShX sh, KnownSTK x) => (IntOf (AstRaw s) -> AstRaw s ('TKX2 sh x)) -> AstRaw s ('TKX2 ('Just k ': sh) x) Source # tbuild1 :: forall (y :: TK) (k :: Nat). ConvertTensor (AstRaw s) => SNat k -> SingletonTK y -> (IntOf (AstRaw s) -> AstRaw s y) -> AstRaw s (BuildTensorKind k y) Source # tmapAccumRDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy (AstRaw s) -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf (AstRaw s) ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf (AstRaw s) ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf (AstRaw s) ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> AstRaw s accy -> AstRaw s (BuildTensorKind k ey) -> AstRaw s ('TKProduct accy (BuildTensorKind k by)) Source # tmapAccumLDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy (AstRaw s) -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf (AstRaw s) ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf (AstRaw s) ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf (AstRaw s) ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> AstRaw s accy -> AstRaw s (BuildTensorKind k ey) -> AstRaw s ('TKProduct accy (BuildTensorKind k by)) Source # tApply :: forall (x :: TK) (z :: TK). HFunOf (AstRaw s) x z -> AstRaw s x -> AstRaw s z Source # tlambda :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstRaw s) x z Source # tgrad :: forall (x :: TK) r. FullShapeTK x -> HFun x ('TKScalar r) -> HFunOf (AstRaw s) x (ADTensorKind x) Source # tvjp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstRaw s) ('TKProduct (ADTensorKind z) x) (ADTensorKind x) Source # tjvp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstRaw s) ('TKProduct (ADTensorKind x) x) (ADTensorKind z) Source # tprimalPart :: forall (y :: TK). AstRaw s y -> PrimalOf (AstRaw s) y Source # tdualPart :: forall (y :: TK). SingletonTK y -> AstRaw s y -> DualOf (AstRaw s) y Source # tfromPrimal :: forall (y :: TK). SingletonTK y -> PrimalOf (AstRaw s) y -> AstRaw s y Source # tfromDual :: forall (y :: TK). DualOf (AstRaw s) y -> AstRaw s y Source # tScale :: forall (y :: TK). (Num (AstRaw s y), Num (PrimalOf (AstRaw s) y)) => SingletonTK y -> PrimalOf (AstRaw s) y -> DualOf (AstRaw s) y -> DualOf (AstRaw s) y Source # tsum :: forall (z :: TK) (k :: Nat). ConvertTensor (AstRaw s) => SNat k -> SingletonTK z -> AstRaw s (BuildTensorKind k z) -> AstRaw s z Source # treplicate :: forall (z :: TK) (k :: Nat). ConvertTensor (AstRaw s) => SNat k -> SingletonTK z -> AstRaw s z -> AstRaw s (BuildTensorKind k z) Source # tindexBuild :: forall (z :: TK) (k :: Nat). ConvertTensor (AstRaw s) => SNat k -> SingletonTK z -> AstRaw s (BuildTensorKind k z) -> IntOf (AstRaw s) -> AstRaw s z Source # treplTarget :: forall (y :: TK). (forall r. GoodScalar r => r) -> FullShapeTK y -> AstRaw s y Source # tdefTarget :: forall (y :: TK). FullShapeTK y -> AstRaw s y Source # taddTarget :: forall (y :: TK). SingletonTK y -> AstRaw s y -> AstRaw s y -> AstRaw s y Source # tmultTarget :: forall (y :: TK). SingletonTK y -> AstRaw s y -> AstRaw s y -> AstRaw s y Source # tsum0Target :: forall (y :: TK). FullShapeTK y -> AstRaw s y -> AstRaw s ('TKScalar Double) Source # tdot0Target :: forall (y :: TK). FullShapeTK y -> AstRaw s y -> AstRaw s y -> AstRaw s ('TKScalar Double) Source # xmcast :: forall (x :: TK) (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]). (KnownSTK x, KnownShX sh, Rank sh ~ Rank sh2, ConvertTensor (AstRaw s)) => StaticShX sh2 -> AstRaw s ('TKX2 sh x) -> AstRaw s ('TKX2 sh2 x) Source # | |
AstSpan s => BaseTensor (AstTensor 'AstMethodLet s) Source # | The checks and error messages in these functions result in complete shape-checking of the ranked and mixed user code (shaped is already fully checked by the Haskell type system). |
Defined in HordeAd.Core.OpsAst Methods rshape :: forall (n :: Nat) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKR2 n x) -> IShR n Source # rlength :: forall (n :: Nat) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKR2 n x) -> Int Source # rsize :: forall (n :: Nat) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKR2 n x) -> Int Source # rwidth :: forall (n :: Natural) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) -> Int Source # sshape :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKS2 sh x) -> ShS sh Source # slength :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKS2 sh x) -> Int Source # ssize :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKS2 sh x) -> Int Source # swidth :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKS2 (n ': sh) x) -> Int Source # xshape :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKX2 sh x) -> IShX sh Source # xlength :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKX2 sh x) -> Int Source # xsize :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKX2 sh x) -> Int Source # xwidth :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKX2 (mn ': sh) x) -> Int Source # tsize :: forall (y :: TK). SingletonTK y -> AstTensor 'AstMethodLet s y -> Int Source # tftk :: forall (y :: TK). SingletonTK y -> AstTensor 'AstMethodLet s y -> FullShapeTK y Source # tpair :: forall (x :: TK) (z :: TK). AstTensor 'AstMethodLet s x -> AstTensor 'AstMethodLet s z -> AstTensor 'AstMethodLet s ('TKProduct x z) Source # tproject1 :: forall (x :: TK) (z :: TK). AstTensor 'AstMethodLet s ('TKProduct x z) -> AstTensor 'AstMethodLet s x Source # tproject2 :: forall (x :: TK) (z :: TK). AstTensor 'AstMethodLet s ('TKProduct x z) -> AstTensor 'AstMethodLet s z Source # tcond :: forall (y :: TK). Boolean (BoolOf (AstTensor 'AstMethodLet s)) => SingletonTK y -> BoolOf (AstTensor 'AstMethodLet s) -> AstTensor 'AstMethodLet s y -> AstTensor 'AstMethodLet s y -> AstTensor 'AstMethodLet s y Source # trconcrete :: forall r (n :: Nat). GoodScalar r => Ranked n r -> AstTensor 'AstMethodLet s (TKR n r) Source # tsconcrete :: forall r (sh :: [Nat]). GoodScalar r => Shaped sh r -> AstTensor 'AstMethodLet s (TKS sh r) Source # txconcrete :: forall r (sh :: [Maybe Nat]). GoodScalar r => Mixed sh r -> AstTensor 'AstMethodLet s (TKX sh r) Source # tkconcrete :: GoodScalar r => r -> AstTensor 'AstMethodLet s ('TKScalar r) Source # tconcrete :: forall (y :: TK). FullShapeTK y -> Concrete y -> AstTensor 'AstMethodLet s y Source # trfromVector :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Vector (AstTensor 'AstMethodLet s ('TKR2 n x)) -> AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) Source # trfromVector0N :: forall (n :: Nat) (x :: TK). KnownSTK x => IShR n -> Vector (AstTensor 'AstMethodLet s ('TKR2 0 x)) -> AstTensor 'AstMethodLet s ('TKR2 n x) Source # trunravelToList :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) -> [AstTensor 'AstMethodLet s ('TKR2 n x)] Source # tsfromVector :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => Vector (AstTensor 'AstMethodLet s ('TKS2 sh x)) -> AstTensor 'AstMethodLet s ('TKS2 (n ': sh) x) Source # tsfromVector0N :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => Vector (AstTensor 'AstMethodLet s ('TKS2 ('[] :: [Nat]) x)) -> AstTensor 'AstMethodLet s ('TKS2 sh x) Source # tsunravelToList :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => AstTensor 'AstMethodLet s ('TKS2 (n ': sh) x) -> [AstTensor 'AstMethodLet s ('TKS2 sh x)] Source # txfromVector :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => Vector (AstTensor 'AstMethodLet s ('TKX2 sh x)) -> AstTensor 'AstMethodLet s ('TKX2 ('Just n ': sh) x) Source # txfromVector0N :: forall (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh -> Vector (AstTensor 'AstMethodLet s ('TKX2 ('[] :: [Maybe Nat]) x)) -> AstTensor 'AstMethodLet s ('TKX2 sh x) Source # txunravelToList :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => AstTensor 'AstMethodLet s ('TKX2 ('Just n ': sh) x) -> [AstTensor 'AstMethodLet s ('TKX2 sh x)] Source # tfromVector :: forall (y :: TK) (k :: Nat). SNat k -> SingletonTK y -> Vector (AstTensor 'AstMethodLet s y) -> AstTensor 'AstMethodLet s (BuildTensorKind k y) Source # tfromListR :: forall (y :: TK) (k :: Nat). SingletonTK y -> ListR k (AstTensor 'AstMethodLet s y) -> AstTensor 'AstMethodLet s (BuildTensorKind k y) Source # trsum :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) -> AstTensor 'AstMethodLet s ('TKR2 n x) Source # trsum0 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => AstTensor 'AstMethodLet s ('TKR2 n x) -> AstTensor 'AstMethodLet s ('TKR2 0 x) Source # trdot0 :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstTensor 'AstMethodLet s (TKR n r) -> AstTensor 'AstMethodLet s (TKR n r) -> AstTensor 'AstMethodLet s (TKR 0 r) Source # trdot1In :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstTensor 'AstMethodLet s (TKR (1 + n) r) -> AstTensor 'AstMethodLet s (TKR (1 + n) r) -> AstTensor 'AstMethodLet s (TKR n r) Source # trmatvecmul :: GoodScalar r => AstTensor 'AstMethodLet s (TKR 2 r) -> AstTensor 'AstMethodLet s (TKR 1 r) -> AstTensor 'AstMethodLet s (TKR 1 r) Source # trmatmul2 :: GoodScalar r => AstTensor 'AstMethodLet s (TKR 2 r) -> AstTensor 'AstMethodLet s (TKR 2 r) -> AstTensor 'AstMethodLet s (TKR 2 r) Source # trreplicate :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> AstTensor 'AstMethodLet s ('TKR2 n x) -> AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) Source # trreplicate0N :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => IShR n -> AstTensor 'AstMethodLet s ('TKR2 0 x) -> AstTensor 'AstMethodLet s ('TKR2 n x) Source # tssum :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat n, KnownShS sh, KnownSTK x) => AstTensor 'AstMethodLet s ('TKS2 (n ': sh) x) -> AstTensor 'AstMethodLet s ('TKS2 sh x) Source # tssum0 :: forall (sh :: [Nat]) (x :: TK). (KnownShS sh, KnownSTK x) => AstTensor 'AstMethodLet s ('TKS2 sh x) -> AstTensor 'AstMethodLet s ('TKS2 ('[] :: [Nat]) x) Source # tsdot0 :: forall (sh :: [Nat]) r. (KnownShS sh, GoodScalar r) => AstTensor 'AstMethodLet s (TKS sh r) -> AstTensor 'AstMethodLet s (TKS sh r) -> AstTensor 'AstMethodLet s (TKS ('[] :: [Nat]) r) Source # tsdot1In :: forall (sh :: [Nat]) r (n :: Nat). (KnownShS sh, GoodScalar r) => SNat n -> AstTensor 'AstMethodLet s (TKS (sh ++ '[n]) r) -> AstTensor 'AstMethodLet s (TKS (sh ++ '[n]) r) -> AstTensor 'AstMethodLet s (TKS sh r) Source # tsmatvecmul :: forall (m :: Nat) (n :: Nat) r. (KnownNat m, KnownNat n, GoodScalar r) => AstTensor 'AstMethodLet s (TKS '[m, n] r) -> AstTensor 'AstMethodLet s (TKS '[n] r) -> AstTensor 'AstMethodLet s (TKS '[m] r) Source # tsmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r) => AstTensor 'AstMethodLet s (TKS '[m, n] r) -> AstTensor 'AstMethodLet s (TKS '[n, p] r) -> AstTensor 'AstMethodLet s (TKS '[m, p] r) Source # tsreplicate :: forall (sh :: [Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> ShS sh -> AstTensor 'AstMethodLet s ('TKS2 sh x) -> AstTensor 'AstMethodLet s ('TKS2 (k ': sh) x) Source # tsreplicate0N :: forall (sh :: [Nat]) (x :: TK). KnownSTK x => ShS sh -> AstTensor 'AstMethodLet s ('TKS2 ('[] :: [Nat]) x) -> AstTensor 'AstMethodLet s ('TKS2 sh x) Source # txsum :: forall (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat n, KnownShX sh, KnownSTK x) => AstTensor 'AstMethodLet s ('TKX2 ('Just n ': sh) x) -> AstTensor 'AstMethodLet s ('TKX2 sh x) Source # txsum0 :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x, ConvertTensor (AstTensor 'AstMethodLet s)) => AstTensor 'AstMethodLet s ('TKX2 sh x) -> AstTensor 'AstMethodLet s ('TKX2 ('[] :: [Maybe Nat]) x) Source # txdot0 :: forall (sh :: [Maybe Nat]) r. (KnownShX sh, GoodScalar r, ConvertTensor (AstTensor 'AstMethodLet s)) => AstTensor 'AstMethodLet s (TKX sh r) -> AstTensor 'AstMethodLet s (TKX sh r) -> AstTensor 'AstMethodLet s (TKX ('[] :: [Maybe Nat]) r) Source # txdot1In :: forall (sh :: [Maybe Nat]) r (n :: Nat). (KnownShX sh, GoodScalar r) => SNat n -> AstTensor 'AstMethodLet s (TKX (sh ++ '['Just n]) r) -> AstTensor 'AstMethodLet s (TKX (sh ++ '['Just n]) r) -> AstTensor 'AstMethodLet s (TKX sh r) Source # txmatvecmul :: forall (mm :: Maybe Nat) (mn :: Maybe Nat) r. (GoodScalar r, ConvertTensor (AstTensor 'AstMethodLet s)) => SMayNat Int SNat mm -> SMayNat Int SNat mn -> AstTensor 'AstMethodLet s (TKX '[mm, mn] r) -> AstTensor 'AstMethodLet s (TKX '[mn] r) -> AstTensor 'AstMethodLet s (TKX '[mm] r) Source # txmatmul2 :: forall (m :: Nat) (n :: Nat) (p :: Nat) r. (KnownNat m, KnownNat n, KnownNat p, GoodScalar r, ConvertTensor (AstTensor 'AstMethodLet s)) => AstTensor 'AstMethodLet s (TKX '['Just m, 'Just n] r) -> AstTensor 'AstMethodLet s (TKX '['Just n, 'Just p] r) -> AstTensor 'AstMethodLet s (TKX '['Just m, 'Just p] r) Source # txreplicate :: forall (sh :: [Maybe Nat]) (k :: Nat) (x :: TK). KnownSTK x => SNat k -> StaticShX sh -> AstTensor 'AstMethodLet s ('TKX2 sh x) -> AstTensor 'AstMethodLet s ('TKX2 ('Just k ': sh) x) Source # txreplicate0N :: forall (sh :: [Maybe Nat]) (x :: TK). (KnownShX sh, KnownSTK x) => IShX sh -> AstTensor 'AstMethodLet s ('TKX2 ('[] :: [Maybe Nat]) x) -> AstTensor 'AstMethodLet s ('TKX2 sh x) Source # trindex :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x) => AstTensor 'AstMethodLet s ('TKR2 (m + n) x) -> IxROf (AstTensor 'AstMethodLet s) m -> AstTensor 'AstMethodLet s ('TKR2 n x) Source # trindex0 :: forall (m :: Nat) (x :: TK). (KnownNat m, KnownSTK x) => AstTensor 'AstMethodLet s ('TKR2 m x) -> IxROf (AstTensor 'AstMethodLet s) m -> AstTensor 'AstMethodLet s ('TKR2 0 x) Source # troneHot :: forall (m :: Nat) (n :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownSTK x, BoolOf (PrimalOf (AstTensor 'AstMethodLet s)) ~ BoolOf (AstTensor 'AstMethodLet s), EqH (PrimalOf (AstTensor 'AstMethodLet s)) ('TKScalar Int64)) => IShR m -> AstTensor 'AstMethodLet s ('TKR2 n x) -> IxROf (AstTensor 'AstMethodLet s) m -> AstTensor 'AstMethodLet s ('TKR2 (m + n) x) Source # trscatter :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> AstTensor 'AstMethodLet s ('TKR2 (m + n) x) -> (IxROf (AstTensor 'AstMethodLet s) m -> IxROf (AstTensor 'AstMethodLet s) p) -> AstTensor 'AstMethodLet s ('TKR2 (p + n) x) Source # trscatter1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => IShR (p + n) -> AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) -> (IntOf (AstTensor 'AstMethodLet s) -> IxROf (AstTensor 'AstMethodLet s) p) -> AstTensor 'AstMethodLet s ('TKR2 (p + n) x) Source # trgather :: forall (m :: Nat) (n :: Nat) (p :: Nat) (x :: TK). (KnownNat m, KnownNat n, KnownNat p, KnownSTK x) => IShR (m + n) -> AstTensor 'AstMethodLet s ('TKR2 (p + n) x) -> (IxROf (AstTensor 'AstMethodLet s) m -> IxROf (AstTensor 'AstMethodLet s) p) -> AstTensor 'AstMethodLet s ('TKR2 (m + n) x) Source # trgather1 :: forall (n :: Nat) (p :: Nat) (x :: TK). (KnownNat n, KnownNat p, KnownSTK x) => Int -> AstTensor 'AstMethodLet s ('TKR2 (p + n) x) -> (IntOf (AstTensor 'AstMethodLet s) -> IxROf (AstTensor 'AstMethodLet s) p) -> AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) Source # tsindex :: forall (shm :: [Nat]) (shn :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownSTK x) => AstTensor 'AstMethodLet s ('TKS2 (shm ++ shn) x) -> IxSOf (AstTensor 'AstMethodLet s) shm -> AstTensor 'AstMethodLet s ('TKS2 shn x) Source # tsindex0 :: forall (sh1 :: [Nat]) (x :: TK). (KnownShS sh1, KnownSTK x) => AstTensor 'AstMethodLet s ('TKS2 sh1 x) -> IxSOf (AstTensor 'AstMethodLet s) sh1 -> AstTensor 'AstMethodLet s ('TKS2 ('[] :: [Nat]) x) Source # tsoneHot :: forall (sh1 :: [Nat]) (sh2 :: [Nat]) (x :: TK). (KnownShS sh1, KnownShS sh2, KnownSTK x, BoolOf (PrimalOf (AstTensor 'AstMethodLet s)) ~ BoolOf (AstTensor 'AstMethodLet s), EqH (PrimalOf (AstTensor 'AstMethodLet s)) ('TKScalar Int64)) => AstTensor 'AstMethodLet s ('TKS2 sh2 x) -> IxSOf (AstTensor 'AstMethodLet s) sh1 -> AstTensor 'AstMethodLet s ('TKS2 (sh1 ++ sh2) x) Source # tsscatter :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => AstTensor 'AstMethodLet s ('TKS2 (shm ++ shn) x) -> (IxSOf (AstTensor 'AstMethodLet s) shm -> IxSOf (AstTensor 'AstMethodLet s) shp) -> AstTensor 'AstMethodLet s ('TKS2 (shp ++ shn) x) Source # tsscatter1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => AstTensor 'AstMethodLet s ('TKS2 (n2 ': shn) x) -> (IntOf (AstTensor 'AstMethodLet s) -> IxSOf (AstTensor 'AstMethodLet s) shp) -> AstTensor 'AstMethodLet s ('TKS2 (shp ++ shn) x) Source # tsgather :: forall (shm :: [Nat]) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownShS shm, KnownShS shn, KnownShS shp, KnownSTK x) => AstTensor 'AstMethodLet s ('TKS2 (shp ++ shn) x) -> (IxSOf (AstTensor 'AstMethodLet s) shm -> IxSOf (AstTensor 'AstMethodLet s) shp) -> AstTensor 'AstMethodLet s ('TKS2 (shm ++ shn) x) Source # tsgather1 :: forall (n2 :: Nat) (shn :: [Nat]) (shp :: [Nat]) (x :: TK). (KnownNat n2, KnownShS shn, KnownShS shp, KnownSTK x) => AstTensor 'AstMethodLet s ('TKS2 (shp ++ shn) x) -> (IntOf (AstTensor 'AstMethodLet s) -> IxSOf (AstTensor 'AstMethodLet s) shp) -> AstTensor 'AstMethodLet s ('TKS2 (n2 ': shn) x) Source # txindex :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x) => AstTensor 'AstMethodLet s ('TKX2 (sh1 ++ sh2) x) -> IxXOf (AstTensor 'AstMethodLet s) sh1 -> AstTensor 'AstMethodLet s ('TKX2 sh2 x) Source # txindex0 :: forall (sh1 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownSTK x) => AstTensor 'AstMethodLet s ('TKX2 sh1 x) -> IxXOf (AstTensor 'AstMethodLet s) sh1 -> AstTensor 'AstMethodLet s ('TKX2 ('[] :: [Maybe Nat]) x) Source # txoneHot :: forall (sh1 :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). (KnownShX sh1, KnownShX sh2, KnownSTK x, BoolOf (PrimalOf (AstTensor 'AstMethodLet s)) ~ BoolOf (AstTensor 'AstMethodLet s), EqH (PrimalOf (AstTensor 'AstMethodLet s)) ('TKScalar Int64), ConvertTensor (AstTensor 'AstMethodLet s)) => IShX sh1 -> AstTensor 'AstMethodLet s ('TKX2 sh2 x) -> IxXOf (AstTensor 'AstMethodLet s) sh1 -> AstTensor 'AstMethodLet s ('TKX2 (sh1 ++ sh2) x) Source # txscatter :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> AstTensor 'AstMethodLet s ('TKX2 (shm ++ shn) x) -> (IxXOf (AstTensor 'AstMethodLet s) shm -> IxXOf (AstTensor 'AstMethodLet s) shp) -> AstTensor 'AstMethodLet s ('TKX2 (shp ++ shn) x) Source # txscatter1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shp ++ shn) -> AstTensor 'AstMethodLet s ('TKX2 ('Just n2 ': shn) x) -> (IntOf (AstTensor 'AstMethodLet s) -> IxXOf (AstTensor 'AstMethodLet s) shp) -> AstTensor 'AstMethodLet s ('TKX2 (shp ++ shn) x) Source # txgather :: forall (shm :: [Maybe Nat]) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownShX shm, KnownShX shn, KnownShX shp, KnownSTK x) => IShX (shm ++ shn) -> AstTensor 'AstMethodLet s ('TKX2 (shp ++ shn) x) -> (IxXOf (AstTensor 'AstMethodLet s) shm -> IxXOf (AstTensor 'AstMethodLet s) shp) -> AstTensor 'AstMethodLet s ('TKX2 (shm ++ shn) x) Source # txgather1 :: forall (n2 :: Nat) (shn :: [Maybe Nat]) (shp :: [Maybe Nat]) (x :: TK). (KnownNat n2, KnownShX shn, KnownShX shp, KnownSTK x) => SNat n2 -> AstTensor 'AstMethodLet s ('TKX2 (shp ++ shn) x) -> (IntOf (AstTensor 'AstMethodLet s) -> IxXOf (AstTensor 'AstMethodLet s) shp) -> AstTensor 'AstMethodLet s ('TKX2 ('Just n2 ': shn) x) Source # trfloor :: forall r r2 (n :: Nat). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstTensor 'AstMethodLet s (TKR n r) -> AstTensor 'AstMethodLet s (TKR n r2) Source # trfromIntegral :: forall r1 r2 (n :: Nat). (GoodScalar r1, Integral r1, GoodScalar r2) => AstTensor 'AstMethodLet s (TKR n r1) -> AstTensor 'AstMethodLet s (TKR n r2) Source # trcast :: forall r1 r2 (n :: Nat). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstTensor 'AstMethodLet s (TKR n r1) -> AstTensor 'AstMethodLet s (TKR n r2) Source # trminIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => AstTensor 'AstMethodLet s (TKR (1 + n) r) -> AstTensor 'AstMethodLet s (TKR n r2) Source # trmaxIndex :: forall (n :: Natural) r r2. (GoodScalar r, GoodScalar r2) => AstTensor 'AstMethodLet s (TKR (1 + n) r) -> AstTensor 'AstMethodLet s (TKR n r2) Source # triota :: GoodScalar r => Int -> AstTensor 'AstMethodLet s (TKR 1 r) Source # tsfloor :: forall r r2 (sh :: [Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstTensor 'AstMethodLet s (TKS sh r) -> AstTensor 'AstMethodLet s (TKS sh r2) Source # tsfromIntegral :: forall r1 r2 (sh :: [Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => AstTensor 'AstMethodLet s (TKS sh r1) -> AstTensor 'AstMethodLet s (TKS sh r2) Source # tscast :: forall r1 r2 (sh :: [Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstTensor 'AstMethodLet s (TKS sh r1) -> AstTensor 'AstMethodLet s (TKS sh r2) Source # tsminIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstTensor 'AstMethodLet s (TKS (n ': sh) r) -> AstTensor 'AstMethodLet s (TKS (Init (n ': sh)) r2) Source # tsmaxIndex :: forall (n :: Nat) (sh :: [Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstTensor 'AstMethodLet s (TKS (n ': sh) r) -> AstTensor 'AstMethodLet s (TKS (Init (n ': sh)) r2) Source # tsiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstTensor 'AstMethodLet s (TKS '[n] r) Source # txfloor :: forall r r2 (sh :: [Maybe Nat]). (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstTensor 'AstMethodLet s (TKX sh r) -> AstTensor 'AstMethodLet s (TKX sh r2) Source # txfromIntegral :: forall r1 r2 (sh :: [Maybe Nat]). (GoodScalar r1, Integral r1, GoodScalar r2) => AstTensor 'AstMethodLet s (TKX sh r1) -> AstTensor 'AstMethodLet s (TKX sh r2) Source # txcast :: forall r1 r2 (sh :: [Maybe Nat]). (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstTensor 'AstMethodLet s (TKX sh r1) -> AstTensor 'AstMethodLet s (TKX sh r2) Source # txminIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstTensor 'AstMethodLet s (TKX (mn ': sh) r) -> AstTensor 'AstMethodLet s (TKX (Init (mn ': sh)) r2) Source # txmaxIndex :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) r r2. (GoodScalar r, GoodScalar r2) => AstTensor 'AstMethodLet s (TKX (mn ': sh) r) -> AstTensor 'AstMethodLet s (TKX (Init (mn ': sh)) r2) Source # txiota :: forall (n :: Nat) r. (KnownNat n, GoodScalar r) => AstTensor 'AstMethodLet s (TKX '['Just n] r) Source # tkfloor :: (GoodScalar r, RealFrac r, GoodScalar r2, Integral r2) => AstTensor 'AstMethodLet s ('TKScalar r) -> AstTensor 'AstMethodLet s ('TKScalar r2) Source # tkfromIntegral :: (GoodScalar r1, Integral r1, GoodScalar r2) => AstTensor 'AstMethodLet s ('TKScalar r1) -> AstTensor 'AstMethodLet s ('TKScalar r2) Source # tkcast :: (RealFrac r1, GoodScalar r1, RealFrac r2, GoodScalar r2) => AstTensor 'AstMethodLet s ('TKScalar r1) -> AstTensor 'AstMethodLet s ('TKScalar r2) Source # trappend :: forall (n :: Natural) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) -> AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) -> AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) Source # trslice :: forall (n :: Natural) (x :: TK). KnownSTK x => Int -> Int -> AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) -> AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) Source # trreverse :: forall (n :: Natural) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) -> AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) Source # trtranspose :: forall (n :: Nat) (x :: TK). KnownSTK x => PermR -> AstTensor 'AstMethodLet s ('TKR2 n x) -> AstTensor 'AstMethodLet s ('TKR2 n x) Source # trreshape :: forall (n :: Nat) (m :: Nat) (x :: TK). KnownSTK x => IShR m -> AstTensor 'AstMethodLet s ('TKR2 n x) -> AstTensor 'AstMethodLet s ('TKR2 m x) Source # tsappend :: forall (m :: Nat) (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKS2 (m ': sh) x) -> AstTensor 'AstMethodLet s ('TKS2 (n ': sh) x) -> AstTensor 'AstMethodLet s ('TKS2 ((m + n) ': sh) x) Source # tsslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> AstTensor 'AstMethodLet s ('TKS2 (((i + n) + k) ': sh) x) -> AstTensor 'AstMethodLet s ('TKS2 (n ': sh) x) Source # tsreverse :: forall (n :: Nat) (sh :: [Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKS2 (n ': sh) x) -> AstTensor 'AstMethodLet s ('TKS2 (n ': sh) x) Source # tstranspose :: forall (perm :: [Natural]) (sh :: [Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> AstTensor 'AstMethodLet s ('TKS2 sh x) -> AstTensor 'AstMethodLet s ('TKS2 (PermutePrefix perm sh) x) Source # tsreshape :: forall (sh :: [Natural]) (sh2 :: [Natural]) (x :: TK). (Product sh ~ Product sh2, KnownSTK x) => ShS sh2 -> AstTensor 'AstMethodLet s ('TKS2 sh x) -> AstTensor 'AstMethodLet s ('TKS2 sh2 x) Source # txappend :: forall (m :: Nat) (n :: Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKX2 ('Just m ': sh) x) -> AstTensor 'AstMethodLet s ('TKX2 ('Just n ': sh) x) -> AstTensor 'AstMethodLet s ('TKX2 ('Just (m + n) ': sh) x) Source # txslice :: forall (i :: Nat) (n :: Nat) (k :: Nat) (sh :: [Maybe Natural]) (x :: TK). KnownSTK x => SNat i -> SNat n -> SNat k -> AstTensor 'AstMethodLet s ('TKX2 ('Just ((i + n) + k) ': sh) x) -> AstTensor 'AstMethodLet s ('TKX2 ('Just n ': sh) x) Source # txreverse :: forall (mn :: Maybe Nat) (sh :: [Maybe Nat]) (x :: TK). KnownSTK x => AstTensor 'AstMethodLet s ('TKX2 (mn ': sh) x) -> AstTensor 'AstMethodLet s ('TKX2 (mn ': sh) x) Source # txtranspose :: forall (perm :: [Natural]) (sh :: [Maybe Nat]) (x :: TK). (IsPermutation perm, Rank perm <= Rank sh, KnownSTK x) => Perm perm -> AstTensor 'AstMethodLet s ('TKX2 sh x) -> AstTensor 'AstMethodLet s ('TKX2 (PermutePrefix perm sh) x) Source # txreshape :: forall (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]) (x :: TK). KnownSTK x => IShX sh2 -> AstTensor 'AstMethodLet s ('TKX2 sh x) -> AstTensor 'AstMethodLet s ('TKX2 sh2 x) Source # trbuild1 :: forall (n :: Nat) (x :: TK). (KnownNat n, KnownSTK x) => Int -> (IntOf (AstTensor 'AstMethodLet s) -> AstTensor 'AstMethodLet s ('TKR2 n x)) -> AstTensor 'AstMethodLet s ('TKR2 (1 + n) x) Source # trmap0N :: forall (n :: Nat) (x :: TK) (x1 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1) => (AstTensor 'AstMethodLet s ('TKR2 0 x1) -> AstTensor 'AstMethodLet s ('TKR2 0 x)) -> AstTensor 'AstMethodLet s ('TKR2 n x1) -> AstTensor 'AstMethodLet s ('TKR2 n x) Source # trzipWith0N :: forall (n :: Nat) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownNat n, KnownSTK x, KnownSTK x1, KnownSTK x2) => (AstTensor 'AstMethodLet s ('TKR2 0 x1) -> AstTensor 'AstMethodLet s ('TKR2 0 x2) -> AstTensor 'AstMethodLet s ('TKR2 0 x)) -> AstTensor 'AstMethodLet s ('TKR2 n x1) -> AstTensor 'AstMethodLet s ('TKR2 n x2) -> AstTensor 'AstMethodLet s ('TKR2 n x) Source # tsbuild1 :: forall (k :: Nat) (sh :: [Nat]) (x :: TK). (KnownNat k, KnownShS sh, KnownSTK x) => (IntOf (AstTensor 'AstMethodLet s) -> AstTensor 'AstMethodLet s ('TKS2 sh x)) -> AstTensor 'AstMethodLet s ('TKS2 (k ': sh) x) Source # tsmap0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1) => (AstTensor 'AstMethodLet s ('TKS2 ('[] :: [Nat]) x1) -> AstTensor 'AstMethodLet s ('TKS2 ('[] :: [Nat]) x)) -> AstTensor 'AstMethodLet s ('TKS2 sh x1) -> AstTensor 'AstMethodLet s ('TKS2 sh x) Source # tszipWith0N :: forall (sh :: [Nat]) (x :: TK) (x1 :: TK) (x2 :: TK). (KnownShS sh, KnownSTK x, KnownSTK x1, KnownSTK x2) => (AstTensor 'AstMethodLet s ('TKS2 ('[] :: [Nat]) x1) -> AstTensor 'AstMethodLet s ('TKS2 ('[] :: [Nat]) x2) -> AstTensor 'AstMethodLet s ('TKS2 ('[] :: [Nat]) x)) -> AstTensor 'AstMethodLet s ('TKS2 sh x1) -> AstTensor 'AstMethodLet s ('TKS2 sh x2) -> AstTensor 'AstMethodLet s ('TKS2 sh x) Source # txbuild1 :: forall (k :: Nat) (sh :: [Maybe Nat]) (x :: TK). (KnownNat k, KnownShX sh, KnownSTK x) => (IntOf (AstTensor 'AstMethodLet s) -> AstTensor 'AstMethodLet s ('TKX2 sh x)) -> AstTensor 'AstMethodLet s ('TKX2 ('Just k ': sh) x) Source # tbuild1 :: forall (y :: TK) (k :: Nat). ConvertTensor (AstTensor 'AstMethodLet s) => SNat k -> SingletonTK y -> (IntOf (AstTensor 'AstMethodLet s) -> AstTensor 'AstMethodLet s y) -> AstTensor 'AstMethodLet s (BuildTensorKind k y) Source # tmapAccumRDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy (AstTensor 'AstMethodLet s) -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf (AstTensor 'AstMethodLet s) ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf (AstTensor 'AstMethodLet s) ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf (AstTensor 'AstMethodLet s) ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> AstTensor 'AstMethodLet s accy -> AstTensor 'AstMethodLet s (BuildTensorKind k ey) -> AstTensor 'AstMethodLet s ('TKProduct accy (BuildTensorKind k by)) Source # tmapAccumLDer :: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat). Proxy (AstTensor 'AstMethodLet s) -> SNat k -> FullShapeTK accy -> FullShapeTK by -> FullShapeTK ey -> HFunOf (AstTensor 'AstMethodLet s) ('TKProduct accy ey) ('TKProduct accy by) -> HFunOf (AstTensor 'AstMethodLet s) ('TKProduct (ADTensorKind ('TKProduct accy ey)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy by)) -> HFunOf (AstTensor 'AstMethodLet s) ('TKProduct (ADTensorKind ('TKProduct accy by)) ('TKProduct accy ey)) (ADTensorKind ('TKProduct accy ey)) -> AstTensor 'AstMethodLet s accy -> AstTensor 'AstMethodLet s (BuildTensorKind k ey) -> AstTensor 'AstMethodLet s ('TKProduct accy (BuildTensorKind k by)) Source # tApply :: forall (x :: TK) (z :: TK). HFunOf (AstTensor 'AstMethodLet s) x z -> AstTensor 'AstMethodLet s x -> AstTensor 'AstMethodLet s z Source # tlambda :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstTensor 'AstMethodLet s) x z Source # tgrad :: forall (x :: TK) r. FullShapeTK x -> HFun x ('TKScalar r) -> HFunOf (AstTensor 'AstMethodLet s) x (ADTensorKind x) Source # tvjp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstTensor 'AstMethodLet s) ('TKProduct (ADTensorKind z) x) (ADTensorKind x) Source # tjvp :: forall (x :: TK) (z :: TK). FullShapeTK x -> HFun x z -> HFunOf (AstTensor 'AstMethodLet s) ('TKProduct (ADTensorKind x) x) (ADTensorKind z) Source # tprimalPart :: forall (y :: TK). AstTensor 'AstMethodLet s y -> PrimalOf (AstTensor 'AstMethodLet s) y Source # tdualPart :: forall (y :: TK). SingletonTK y -> AstTensor 'AstMethodLet s y -> DualOf (AstTensor 'AstMethodLet s) y Source # tfromPrimal :: forall (y :: TK). SingletonTK y -> PrimalOf (AstTensor 'AstMethodLet s) y -> AstTensor 'AstMethodLet s y Source # tfromDual :: forall (y :: TK). DualOf (AstTensor 'AstMethodLet s) y -> AstTensor 'AstMethodLet s y Source # tScale :: forall (y :: TK). (Num (AstTensor 'AstMethodLet s y), Num (PrimalOf (AstTensor 'AstMethodLet s) y)) => SingletonTK y -> PrimalOf (AstTensor 'AstMethodLet s) y -> DualOf (AstTensor 'AstMethodLet s) y -> DualOf (AstTensor 'AstMethodLet s) y Source # tsum :: forall (z :: TK) (k :: Nat). ConvertTensor (AstTensor 'AstMethodLet s) => SNat k -> SingletonTK z -> AstTensor 'AstMethodLet s (BuildTensorKind k z) -> AstTensor 'AstMethodLet s z Source # treplicate :: forall (z :: TK) (k :: Nat). ConvertTensor (AstTensor 'AstMethodLet s) => SNat k -> SingletonTK z -> AstTensor 'AstMethodLet s z -> AstTensor 'AstMethodLet s (BuildTensorKind k z) Source # tindexBuild :: forall (z :: TK) (k :: Nat). ConvertTensor (AstTensor 'AstMethodLet s) => SNat k -> SingletonTK z -> AstTensor 'AstMethodLet s (BuildTensorKind k z) -> IntOf (AstTensor 'AstMethodLet s) -> AstTensor 'AstMethodLet s z Source # treplTarget :: forall (y :: TK). (forall r. GoodScalar r => r) -> FullShapeTK y -> AstTensor 'AstMethodLet s y Source # tdefTarget :: forall (y :: TK). FullShapeTK y -> AstTensor 'AstMethodLet s y Source # taddTarget :: forall (y :: TK). SingletonTK y -> AstTensor 'AstMethodLet s y -> AstTensor 'AstMethodLet s y -> AstTensor 'AstMethodLet s y Source # tmultTarget :: forall (y :: TK). SingletonTK y -> AstTensor 'AstMethodLet s y -> AstTensor 'AstMethodLet s y -> AstTensor 'AstMethodLet s y Source # tsum0Target :: forall (y :: TK). FullShapeTK y -> AstTensor 'AstMethodLet s y -> AstTensor 'AstMethodLet s ('TKScalar Double) Source # tdot0Target :: forall (y :: TK). FullShapeTK y -> AstTensor 'AstMethodLet s y -> AstTensor 'AstMethodLet s y -> AstTensor 'AstMethodLet s ('TKScalar Double) Source # xmcast :: forall (x :: TK) (sh :: [Maybe Nat]) (sh2 :: [Maybe Nat]). (KnownSTK x, KnownShX sh, Rank sh ~ Rank sh2, ConvertTensor (AstTensor 'AstMethodLet s)) => StaticShX sh2 -> AstTensor 'AstMethodLet s ('TKX2 sh x) -> AstTensor 'AstMethodLet s ('TKX2 sh2 x) Source # |
The giga-constraint
type ADReadyNoLet (target :: Target) = (ADReadyEqsClasses target, ADReadyEqsClasses (ShareOf target), ShareTensor (ShareOf target), ShareTensor (PrimalOf (ShareOf target)), ShareOf (ShareOf target) ~ ShareOf target) Source #
type ADReadyClasses (target :: Target) = (BaseTensor target, ConvertTensor target, Boolean (BoolOf target), AllTargetShow target, CommonTargetEqOrd target) Source #
type ADReadyEqsClasses (target :: Target) = (ADReadyEqs target, ADReadyClasses target, ADReadyClasses (PrimalOf target)) Source #
class (forall (y :: TK). KnownSTK y => Show (target y)) => AllTargetShow (target :: Target) Source #
Instances
(forall (y :: TK). KnownSTK y => Show (target y)) => AllTargetShow target Source # | |
Defined in HordeAd.Core.Ops |
class (forall r. GoodScalar r => EqH target ('TKScalar r), forall r. GoodScalar r => OrdH target ('TKScalar r), forall r (n :: Nat). GoodScalar r => EqH target (TKR n r), forall r (n :: Nat). GoodScalar r => OrdH target (TKR n r), forall r (sh :: [Nat]). GoodScalar r => EqH target (TKS sh r), forall r (sh :: [Nat]). GoodScalar r => OrdH target (TKS sh r), forall r (sh :: [Maybe Nat]). GoodScalar r => EqH target (TKX sh r), forall r (sh :: [Maybe Nat]). GoodScalar r => OrdH target (TKX sh r)) => CommonTargetEqOrd (target :: Target) Source #
Instances
(forall r. GoodScalar r => EqH target ('TKScalar r), forall r. GoodScalar r => OrdH target ('TKScalar r), forall r (n :: Nat). GoodScalar r => EqH target (TKR n r), forall r (n :: Nat). GoodScalar r => OrdH target (TKR n r), forall r (sh :: [Nat]). GoodScalar r => EqH target (TKS sh r), forall r (sh :: [Nat]). GoodScalar r => OrdH target (TKS sh r), forall r (sh :: [Maybe Nat]). GoodScalar r => EqH target (TKX sh r), forall r (sh :: [Maybe Nat]). GoodScalar r => OrdH target (TKX sh r)) => CommonTargetEqOrd target Source # | |
Defined in HordeAd.Core.Ops |
Helper functions
rtr :: forall (n :: Natural) (x :: TK) target. (KnownSTK x, BaseTensor target) => target ('TKR2 (2 + n) x) -> target ('TKR2 (2 + n) x) Source #
rflatten :: forall (n :: Nat) (x :: TK) target. (KnownSTK x, BaseTensor target) => target ('TKR2 n x) -> target ('TKR2 1 x) Source #
str :: forall (n :: Nat) (m :: Nat) (sh :: [Nat]) (x :: TK) target. (KnownSTK x, BaseTensor target) => target ('TKS2 (n ': (m ': sh)) x) -> target ('TKS2 (m ': (n ': sh)) x) Source #
sflatten :: forall (sh :: [Nat]) (x :: TK) target. (KnownShS sh, KnownSTK x, BaseTensor target) => target ('TKS2 sh x) -> target ('TKS2 '[Product sh] x) Source #
xtr :: forall (n :: Nat) (m :: Nat) (sh :: [Maybe Nat]) (x :: TK) target. (KnownSTK x, BaseTensor target) => target ('TKX2 ('Just n ': ('Just m ': sh)) x) -> target ('TKX2 ('Just m ': ('Just n ': sh)) x) Source #
xflatten :: forall (sh :: [Maybe Nat]) (x :: TK) target. (KnownSTK x, BaseTensor target) => target ('TKX2 sh x) -> target ('TKX2 '['Nothing :: Maybe Nat] x) Source #
Arguments
:: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat) target. BaseTensor target | |
=> Proxy target | |
-> SNat k | length of the input |
-> FullShapeTK accy | shape of the accumulator |
-> FullShapeTK by | shape of the output |
-> FullShapeTK ey | shape of an individual input |
-> (forall (f :: Target). ADReady f => f accy -> f ey -> f ('TKProduct accy by)) | the function to mapAccum with |
-> target accy | the initial accumulator |
-> target (BuildTensorKind k ey) | the inputs |
-> target ('TKProduct accy (BuildTensorKind k by)) |
A strict right mapAccum.
Arguments
:: forall (accy :: TK) (by :: TK) (ey :: TK) (k :: Nat) target. BaseTensor target | |
=> Proxy target | |
-> SNat k | length of the input |
-> FullShapeTK accy | shape of the accumulator |
-> FullShapeTK by | shape of the output |
-> FullShapeTK ey | shape of an individual input |
-> (forall (f :: Target). ADReady f => f accy -> f ey -> f ('TKProduct accy by)) | the function to mapAccum with |
-> target accy | the initial accumulator |
-> target (BuildTensorKind k ey) | the inputs |
-> target ('TKProduct accy (BuildTensorKind k by)) |
A strict left mapAccum.
Helper classes and types
class (IntegralH r, IntElt r) => IntegralHAndIntElt r Source #
Instances
(IntegralH r, IntElt r) => IntegralHAndIntElt r Source # | |
Defined in HordeAd.Core.Ops |
class (RealFloatH r, FloatElt r) => RealFloatAndFloatElt r Source #
Instances
(RealFloatH r, FloatElt r) => RealFloatAndFloatElt r Source # | |
Defined in HordeAd.Core.Ops |
type TensorSupportsX (c1 :: Type -> Constraint) (c2 :: Type -> Constraint) (f :: Target) = forall r (sh :: [Maybe Nat]). (GoodScalar r, c1 r) => c2 (f (TKX sh r)) Source #
type TensorSupportsS (c1 :: Type -> Constraint) (c2 :: Type -> Constraint) (f :: Target) = forall r (sh :: [Nat]). (GoodScalar r, c1 r) => c2 (f (TKS sh r)) Source #
type TensorSupportsR (c1 :: Type -> Constraint) (c2 :: Type -> Constraint) (f :: Target) = forall r (n :: Nat). (GoodScalar r, c1 r) => c2 (f (TKR n r)) Source #
type TensorSupports (c1 :: Type -> Constraint) (c2 :: Type -> Constraint) (f :: Target) = forall r. (GoodScalar r, c1 r) => c2 (f ('TKScalar r)) Source #