Safe Haskell | None |
---|---|
Language | GHC2024 |
HordeAd.Core.Adaptor
Contents
Description
Adaptors for working with types of collections of tensors, e.g., tuples, sized lists and user types of statically known size, as long as they have the proper instances defined. The collections are used as representations of the domains of objective functions that become the codomains of the reverse derivative functions and also to handle multiple arguments and results of fold-like operations.
Synopsis
- class AdaptableTarget (target :: Target) vals where
- class TermValue vals where
- class DualNumberValue vals where
- type DValue vals
- fromDValue :: DValue vals -> vals
- class ForgetShape vals where
- type NoShape vals
- forgetShape :: vals -> NoShape vals
- class RandomValue vals where
- randomValue :: Double -> StdGen -> (vals, StdGen)
- stkOfListR :: forall (t :: TK) (n :: Nat). SingletonTK t -> SNat n -> SingletonTK (Tups n t)
- type family Tups (n :: Natural) (t :: TK) :: TK where ...
- type family NoShapeTensorKind (tk :: TK) :: TK where ...
Documentation
class AdaptableTarget (target :: Target) vals where Source #
The class that makes it possible to treat vals
(e.g., a tuple of tensors)
as a target
-based (e.g., concrete or symbolic) value
of tensor kind X vals
.
Methods
Arguments
:: vals | |
-> target (X vals) | represent a collection of tensors |
Arguments
:: target (X vals) | |
-> vals | recovers a collection of tensors from its canonical representation; requires a duplicable argument |
Instances
(BaseTensor target, ConvertTensor target, GoodScalar r) => AdaptableTarget target (Vector (target ('TKScalar r))) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
(BaseTensor target, ConvertTensor target, GoodScalar r) => AdaptableTarget target [target ('TKScalar r)] Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
AdaptableTarget target (target y) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
(BaseTensor target, KnownNat n, AdaptableTarget target a) => AdaptableTarget target (ListR n a) Source # | |||||
(BaseTensor target, AdaptableTarget target a, AdaptableTarget target b) => AdaptableTarget target (a, b) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
(BaseTensor target, AdaptableTarget target a, AdaptableTarget target b, AdaptableTarget target c) => AdaptableTarget target (a, b, c) Source # | |||||
(BaseTensor target, AdaptableTarget target a, AdaptableTarget target b, AdaptableTarget target c, AdaptableTarget target d) => AdaptableTarget target (a, b, c, d) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
(BaseTensor target, AdaptableTarget target a, AdaptableTarget target b, AdaptableTarget target c, AdaptableTarget target d, AdaptableTarget target e) => AdaptableTarget target (a, b, c, d, e) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
|
class TermValue vals where Source #
An embedding of a concrete collection of tensors to a non-concrete counterpart of the same shape and containing the same data.
Instances
class DualNumberValue vals where Source #
An embedding of a concrete collection of tensors to a non-concrete counterpart of the same shape and containing the same data. This variant is possible to define more often, but the associated type family is not injective.
Instances
DualNumberValue Double Source # | |||||
Defined in HordeAd.Core.Adaptor | |||||
DualNumberValue Float Source # | |||||
Defined in HordeAd.Core.Adaptor | |||||
DualNumberValue a => DualNumberValue (Vector a) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods fromDValue :: DValue (Vector a) -> Vector a Source # | |||||
DualNumberValue a => DualNumberValue [a] Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods fromDValue :: DValue [a] -> [a] Source # | |||||
(BaseTensor target, BaseTensor (PrimalOf target), KnownSTK y) => DualNumberValue (target y) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods fromDValue :: DValue (target y) -> target y Source # | |||||
DualNumberValue a => DualNumberValue (ListR n a) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
(DualNumberValue a, DualNumberValue b) => DualNumberValue (a, b) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods fromDValue :: DValue (a, b) -> (a, b) Source # | |||||
(DualNumberValue a, DualNumberValue b, DualNumberValue c) => DualNumberValue (a, b, c) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods fromDValue :: DValue (a, b, c) -> (a, b, c) Source # | |||||
(DualNumberValue a, DualNumberValue b, DualNumberValue c, DualNumberValue d) => DualNumberValue (a, b, c, d) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods fromDValue :: DValue (a, b, c, d) -> (a, b, c, d) Source # | |||||
(DualNumberValue a, DualNumberValue b, DualNumberValue c, DualNumberValue d, DualNumberValue e) => DualNumberValue (a, b, c, d, e) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods fromDValue :: DValue (a, b, c, d, e) -> (a, b, c, d, e) Source # |
class ForgetShape vals where Source #
A helper class for for converting all tensors inside a type
from shaped to ranked. It's useful when a collection of parameters
is defined as shaped tensor for RandomValue
but then is going
to be used as ranked tensor to make type reconstruction easier.
Methods
forgetShape :: vals -> NoShape vals Source #
Instances
ForgetShape (Vector a) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods forgetShape :: Vector a -> NoShape (Vector a) Source # | |||||
ForgetShape [a] Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods forgetShape :: [a] -> NoShape [a] Source # | |||||
(ForgetShape (target a), ForgetShape (target b), target (NoShapeTensorKind a) ~ NoShape (target a), target (NoShapeTensorKind b) ~ NoShape (target b), BaseTensor target, LetTensor target) => ForgetShape (target ('TKProduct a b)) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
ForgetShape (target (TKR n r)) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
(KnownShS sh, GoodScalar r, ConvertTensor target) => ForgetShape (target (TKS sh r)) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
ForgetShape (target ('TKScalar r)) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
ForgetShape (target (TKX sh r)) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
ForgetShape a => ForgetShape (ListR n a) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
| |||||
(ForgetShape a, ForgetShape b) => ForgetShape (a, b) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods forgetShape :: (a, b) -> NoShape (a, b) Source # | |||||
(ForgetShape a, ForgetShape b, ForgetShape c) => ForgetShape (a, b, c) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods forgetShape :: (a, b, c) -> NoShape (a, b, c) Source # | |||||
(ForgetShape a, ForgetShape b, ForgetShape c, ForgetShape d) => ForgetShape (a, b, c, d) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods forgetShape :: (a, b, c, d) -> NoShape (a, b, c, d) Source # | |||||
(ForgetShape a, ForgetShape b, ForgetShape c, ForgetShape d, ForgetShape e) => ForgetShape (a, b, c, d, e) Source # | |||||
Defined in HordeAd.Core.Adaptor Associated Types
Methods forgetShape :: (a, b, c, d, e) -> NoShape (a, b, c, d, e) Source # |
class RandomValue vals where Source #
A helper class for randomly generating initial parameters. Only instance for collections of shaped tensors and scalars are possible, because only then the shapes of the tensors to generate are known from their types.
Instances
(RandomValue (target a), RandomValue (target b), BaseTensor target) => RandomValue (target ('TKProduct a b)) Source # | |
Defined in HordeAd.Core.Adaptor | |
(KnownShS sh, GoodScalar r, BaseTensor target) => RandomValue (target (TKS sh r)) Source # | |
Defined in HordeAd.Core.Adaptor | |
(GoodScalar r, BaseTensor target) => RandomValue (target ('TKScalar r)) Source # | |
Defined in HordeAd.Core.Adaptor | |
(RandomValue a, KnownNat n) => RandomValue (ListR n a) Source # | |
Defined in HordeAd.Core.Adaptor | |
(RandomValue a, RandomValue b) => RandomValue (a, b) Source # | |
Defined in HordeAd.Core.Adaptor | |
(RandomValue a, RandomValue b, RandomValue c) => RandomValue (a, b, c) Source # | |
Defined in HordeAd.Core.Adaptor | |
(RandomValue a, RandomValue b, RandomValue c, RandomValue d) => RandomValue (a, b, c, d) Source # | |
Defined in HordeAd.Core.Adaptor | |
(RandomValue a, RandomValue b, RandomValue c, RandomValue d, RandomValue e) => RandomValue (a, b, c, d, e) Source # | |
Defined in HordeAd.Core.Adaptor |
stkOfListR :: forall (t :: TK) (n :: Nat). SingletonTK t -> SNat n -> SingletonTK (Tups n t) Source #
Helper classes and types
type family NoShapeTensorKind (tk :: TK) :: TK where ... Source #
Equations
NoShapeTensorKind ('TKScalar r) = 'TKScalar r | |
NoShapeTensorKind ('TKR2 n r) = 'TKR2 n r | |
NoShapeTensorKind ('TKS2 sh r) = 'TKR2 (Rank sh) r | |
NoShapeTensorKind ('TKX2 sh r) = 'TKX2 sh r | |
NoShapeTensorKind ('TKProduct y z) = 'TKProduct (NoShapeTensorKind y) (NoShapeTensorKind z) |