horde-ad-0.2.0.0: Higher Order Reverse Derivatives Efficiently - Automatic Differentiation
Safe HaskellNone
LanguageGHC2024

HordeAd.Core.Adaptor

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

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.

Associated Types

type X vals :: TK Source #

Methods

toTarget Source #

Arguments

:: vals 
-> target (X vals)

represent a collection of tensors

fromTarget Source #

Arguments

:: target (X vals) 
-> vals

recovers a collection of tensors from its canonical representation; requires a duplicable argument

Instances

Instances details
(BaseTensor target, ConvertTensor target, GoodScalar r) => AdaptableTarget target (Vector (target ('TKScalar r))) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type X (Vector (target ('TKScalar r))) 
Instance details

Defined in HordeAd.Core.Adaptor

type X (Vector (target ('TKScalar r))) = TKR 1 r

Methods

toTarget :: Vector (target ('TKScalar r)) -> target (X (Vector (target ('TKScalar r)))) Source #

fromTarget :: target (X (Vector (target ('TKScalar r)))) -> Vector (target ('TKScalar r)) Source #

(BaseTensor target, ConvertTensor target, GoodScalar r) => AdaptableTarget target [target ('TKScalar r)] Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type X [target ('TKScalar r)] 
Instance details

Defined in HordeAd.Core.Adaptor

type X [target ('TKScalar r)] = TKR 1 r

Methods

toTarget :: [target ('TKScalar r)] -> target (X [target ('TKScalar r)]) Source #

fromTarget :: target (X [target ('TKScalar r)]) -> [target ('TKScalar r)] Source #

AdaptableTarget target (target y) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type X (target y) 
Instance details

Defined in HordeAd.Core.Adaptor

type X (target y) = y

Methods

toTarget :: target y -> target (X (target y)) Source #

fromTarget :: target (X (target y)) -> target y Source #

(BaseTensor target, KnownNat n, AdaptableTarget target a) => AdaptableTarget target (ListR n a) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type X (ListR n a) 
Instance details

Defined in HordeAd.Core.Adaptor

type X (ListR n a) = Tups n (X a)

Methods

toTarget :: ListR n a -> target (X (ListR n a)) Source #

fromTarget :: target (X (ListR n a)) -> ListR n a Source #

(BaseTensor target, AdaptableTarget target a, AdaptableTarget target b) => AdaptableTarget target (a, b) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type X (a, b) 
Instance details

Defined in HordeAd.Core.Adaptor

type X (a, b) = 'TKProduct (X a) (X b)

Methods

toTarget :: (a, b) -> target (X (a, b)) Source #

fromTarget :: target (X (a, b)) -> (a, b) Source #

(BaseTensor target, AdaptableTarget target a, AdaptableTarget target b, AdaptableTarget target c) => AdaptableTarget target (a, b, c) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type X (a, b, c) 
Instance details

Defined in HordeAd.Core.Adaptor

type X (a, b, c) = 'TKProduct ('TKProduct (X a) (X b)) (X c)

Methods

toTarget :: (a, b, c) -> target (X (a, b, c)) Source #

fromTarget :: target (X (a, b, c)) -> (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 # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type X (a, b, c, d) 
Instance details

Defined in HordeAd.Core.Adaptor

type X (a, b, c, d) = 'TKProduct ('TKProduct (X a) (X b)) ('TKProduct (X c) (X d))

Methods

toTarget :: (a, b, c, d) -> target (X (a, b, c, d)) Source #

fromTarget :: target (X (a, b, c, d)) -> (a, b, c, d) Source #

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

Defined in HordeAd.Core.Adaptor

Associated Types

type X (a, b, c, d, e) 
Instance details

Defined in HordeAd.Core.Adaptor

type X (a, b, c, d, e) = 'TKProduct ('TKProduct ('TKProduct (X a) (X b)) (X c)) ('TKProduct (X d) (X e))

Methods

toTarget :: (a, b, c, d, e) -> target (X (a, b, c, d, e)) Source #

fromTarget :: target (X (a, b, c, d, e)) -> (a, b, c, d, e) Source #

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.

Associated Types

type Value vals = (result :: Type) | result -> vals Source #

Methods

fromValue Source #

Arguments

:: Value vals 
-> vals

an embedding

Instances

Instances details
TermValue (Concrete ('TKScalar Double)) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type Value (Concrete ('TKScalar Double)) 
Instance details

Defined in HordeAd.Core.Adaptor

TermValue (Concrete ('TKScalar Float)) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type Value (Concrete ('TKScalar Float)) 
Instance details

Defined in HordeAd.Core.Adaptor

TermValue a => TermValue (Vector a) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type Value (Vector a) 
Instance details

Defined in HordeAd.Core.Adaptor

type Value (Vector a) = Vector (Value a)

Methods

fromValue :: Value (Vector a) -> Vector a Source #

TermValue a => TermValue [a] Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type Value [a] 
Instance details

Defined in HordeAd.Core.Adaptor

type Value [a] = [Value a]

Methods

fromValue :: Value [a] -> [a] Source #

TermValue a => TermValue (ListR n a) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type Value (ListR n a) 
Instance details

Defined in HordeAd.Core.Adaptor

type Value (ListR n a) = ListR n (Value a)

Methods

fromValue :: Value (ListR n a) -> ListR n a Source #

(TermValue a, TermValue b) => TermValue (a, b) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type Value (a, b) 
Instance details

Defined in HordeAd.Core.Adaptor

type Value (a, b) = (Value a, Value b)

Methods

fromValue :: Value (a, b) -> (a, b) Source #

KnownSTK y => TermValue (AstTensor 'AstMethodLet 'FullSpan y) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type Value (AstTensor 'AstMethodLet 'FullSpan y) 
Instance details

Defined in HordeAd.Core.Adaptor

(TermValue a, TermValue b, TermValue c) => TermValue (a, b, c) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type Value (a, b, c) 
Instance details

Defined in HordeAd.Core.Adaptor

type Value (a, b, c) = (Value a, Value b, Value c)

Methods

fromValue :: Value (a, b, c) -> (a, b, c) Source #

(TermValue a, TermValue b, TermValue c, TermValue d) => TermValue (a, b, c, d) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type Value (a, b, c, d) 
Instance details

Defined in HordeAd.Core.Adaptor

type Value (a, b, c, d) = (Value a, Value b, Value c, Value d)

Methods

fromValue :: Value (a, b, c, d) -> (a, b, c, d) Source #

(TermValue a, TermValue b, TermValue c, TermValue d, TermValue e) => TermValue (a, b, c, d, e) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type Value (a, b, c, d, e) 
Instance details

Defined in HordeAd.Core.Adaptor

type Value (a, b, c, d, e) = (Value a, Value b, Value c, Value d, Value e)

Methods

fromValue :: Value (a, b, c, d, e) -> (a, b, c, d, e) Source #

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.

Associated Types

type DValue vals Source #

Methods

fromDValue Source #

Arguments

:: DValue vals 
-> vals

an embedding

Instances

Instances details
DualNumberValue Double Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type DValue Double 
Instance details

Defined in HordeAd.Core.Adaptor

DualNumberValue Float Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type DValue Float 
Instance details

Defined in HordeAd.Core.Adaptor

DualNumberValue a => DualNumberValue (Vector a) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type DValue (Vector a) 
Instance details

Defined in HordeAd.Core.Adaptor

type DValue (Vector a) = Vector (DValue a)

Methods

fromDValue :: DValue (Vector a) -> Vector a Source #

DualNumberValue a => DualNumberValue [a] Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type DValue [a] 
Instance details

Defined in HordeAd.Core.Adaptor

type DValue [a] = [DValue a]

Methods

fromDValue :: DValue [a] -> [a] Source #

(BaseTensor target, BaseTensor (PrimalOf target), KnownSTK y) => DualNumberValue (target y) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type DValue (target y) 
Instance details

Defined in HordeAd.Core.Adaptor

type DValue (target y) = Concrete y

Methods

fromDValue :: DValue (target y) -> target y Source #

DualNumberValue a => DualNumberValue (ListR n a) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type DValue (ListR n a) 
Instance details

Defined in HordeAd.Core.Adaptor

type DValue (ListR n a) = ListR n (DValue a)

Methods

fromDValue :: DValue (ListR n a) -> ListR n a Source #

(DualNumberValue a, DualNumberValue b) => DualNumberValue (a, b) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type DValue (a, b) 
Instance details

Defined in HordeAd.Core.Adaptor

type DValue (a, b) = (DValue a, DValue b)

Methods

fromDValue :: DValue (a, b) -> (a, b) Source #

(DualNumberValue a, DualNumberValue b, DualNumberValue c) => DualNumberValue (a, b, c) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type DValue (a, b, c) 
Instance details

Defined in HordeAd.Core.Adaptor

type DValue (a, b, c) = (DValue a, DValue b, DValue c)

Methods

fromDValue :: DValue (a, b, c) -> (a, b, c) Source #

(DualNumberValue a, DualNumberValue b, DualNumberValue c, DualNumberValue d) => DualNumberValue (a, b, c, d) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type DValue (a, b, c, d) 
Instance details

Defined in HordeAd.Core.Adaptor

type DValue (a, b, c, d) = (DValue a, DValue b, DValue c, DValue d)

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 # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type DValue (a, b, c, d, e) 
Instance details

Defined in HordeAd.Core.Adaptor

type DValue (a, b, c, d, e) = (DValue a, DValue b, DValue c, DValue d, DValue e)

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.

Associated Types

type NoShape vals Source #

Methods

forgetShape :: vals -> NoShape vals Source #

Instances

Instances details
ForgetShape (Vector a) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape (Vector a) 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape (Vector a) = Vector a

Methods

forgetShape :: Vector a -> NoShape (Vector a) Source #

ForgetShape [a] Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape [a] 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape [a] = [a]

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 # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape (target ('TKProduct a b)) 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape (target ('TKProduct a b)) = target (NoShapeTensorKind ('TKProduct a b))

Methods

forgetShape :: target ('TKProduct a b) -> NoShape (target ('TKProduct a b)) Source #

ForgetShape (target (TKR n r)) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape (target (TKR n r)) 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape (target (TKR n r)) = target (TKR n r)

Methods

forgetShape :: target (TKR n r) -> NoShape (target (TKR n r)) Source #

(KnownShS sh, GoodScalar r, ConvertTensor target) => ForgetShape (target (TKS sh r)) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape (target (TKS sh r)) 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape (target (TKS sh r)) = target (TKR (Rank sh) r)

Methods

forgetShape :: target (TKS sh r) -> NoShape (target (TKS sh r)) Source #

ForgetShape (target ('TKScalar r)) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape (target ('TKScalar r)) 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape (target ('TKScalar r)) = target ('TKScalar r)

Methods

forgetShape :: target ('TKScalar r) -> NoShape (target ('TKScalar r)) Source #

ForgetShape (target (TKX sh r)) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape (target (TKX sh r)) 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape (target (TKX sh r)) = target (TKX sh r)

Methods

forgetShape :: target (TKX sh r) -> NoShape (target (TKX sh r)) Source #

ForgetShape a => ForgetShape (ListR n a) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape (ListR n a) 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape (ListR n a) = ListR n (NoShape a)

Methods

forgetShape :: ListR n a -> NoShape (ListR n a) Source #

(ForgetShape a, ForgetShape b) => ForgetShape (a, b) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape (a, b) 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape (a, b) = (NoShape a, NoShape b)

Methods

forgetShape :: (a, b) -> NoShape (a, b) Source #

(ForgetShape a, ForgetShape b, ForgetShape c) => ForgetShape (a, b, c) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape (a, b, c) 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape (a, b, c) = (NoShape a, NoShape b, NoShape c)

Methods

forgetShape :: (a, b, c) -> NoShape (a, b, c) Source #

(ForgetShape a, ForgetShape b, ForgetShape c, ForgetShape d) => ForgetShape (a, b, c, d) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape (a, b, c, d) 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape (a, b, c, d) = (NoShape a, NoShape b, NoShape c, NoShape d)

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 # 
Instance details

Defined in HordeAd.Core.Adaptor

Associated Types

type NoShape (a, b, c, d, e) 
Instance details

Defined in HordeAd.Core.Adaptor

type NoShape (a, b, c, d, e) = (NoShape a, NoShape b, NoShape c, NoShape d, NoShape e)

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.

Methods

randomValue :: Double -> StdGen -> (vals, StdGen) Source #

Instances

Instances details
(RandomValue (target a), RandomValue (target b), BaseTensor target) => RandomValue (target ('TKProduct a b)) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Methods

randomValue :: Double -> StdGen -> (target ('TKProduct a b), StdGen) Source #

(KnownShS sh, GoodScalar r, BaseTensor target) => RandomValue (target (TKS sh r)) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Methods

randomValue :: Double -> StdGen -> (target (TKS sh r), StdGen) Source #

(GoodScalar r, BaseTensor target) => RandomValue (target ('TKScalar r)) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Methods

randomValue :: Double -> StdGen -> (target ('TKScalar r), StdGen) Source #

(RandomValue a, KnownNat n) => RandomValue (ListR n a) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Methods

randomValue :: Double -> StdGen -> (ListR n a, StdGen) Source #

(RandomValue a, RandomValue b) => RandomValue (a, b) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Methods

randomValue :: Double -> StdGen -> ((a, b), StdGen) Source #

(RandomValue a, RandomValue b, RandomValue c) => RandomValue (a, b, c) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Methods

randomValue :: Double -> StdGen -> ((a, b, c), StdGen) Source #

(RandomValue a, RandomValue b, RandomValue c, RandomValue d) => RandomValue (a, b, c, d) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Methods

randomValue :: Double -> StdGen -> ((a, b, c, d), StdGen) Source #

(RandomValue a, RandomValue b, RandomValue c, RandomValue d, RandomValue e) => RandomValue (a, b, c, d, e) Source # 
Instance details

Defined in HordeAd.Core.Adaptor

Methods

randomValue :: Double -> StdGen -> ((a, b, c, d, e), StdGen) Source #

stkOfListR :: forall (t :: TK) (n :: Nat). SingletonTK t -> SNat n -> SingletonTK (Tups n t) Source #

Helper classes and types

type family Tups (n :: Natural) (t :: TK) :: TK where ... Source #

Equations

Tups 0 t = TKUnit 
Tups n t = 'TKProduct t (Tups (n - 1) t) 

type family NoShapeTensorKind (tk :: TK) :: TK where ... Source #