-- Hoogle documentation, generated by Haddock -- See Hoogle, http://www.haskell.org/hoogle/ -- | Reverse mode automatic differentiation -- -- Simple and well typed implementation of reverse mode automatic -- differentiation. See home page -- https://andriusstank.github.io/downhill/ for more detailed -- description. @package downhill @version 0.4.0.0 module Downhill.Internal.Graph.OpenMap -- | Heterogeneous map with StableName as a key. data OpenMap (f :: Type -> Type) -- | A key of OpenMap. data OpenKey x -- | Key and value. data SomeOpenItem f SomeOpenItem :: OpenKey x -> f x -> SomeOpenItem f makeOpenKey :: f v -> IO (OpenKey v) empty :: OpenMap f insert :: forall f dx. OpenKey dx -> f dx -> OpenMap f -> OpenMap f lookup :: OpenMap f -> OpenKey x -> Maybe (f x) toList :: OpenMap f -> [SomeOpenItem f] elems :: OpenMap (Const b) -> [b] map :: forall f g. (forall x. f x -> g x) -> OpenMap f -> OpenMap g mapWithKey :: forall f g. (forall d. OpenKey d -> f d -> g d) -> OpenMap f -> OpenMap g mapMaybe :: forall f g. (forall x. f x -> Maybe (g x)) -> OpenMap f -> OpenMap g adjust :: forall f x. (f x -> f x) -> OpenKey x -> OpenMap f -> OpenMap f intersectionWith :: forall f g h. (forall x. f x -> g x -> h x) -> OpenMap f -> OpenMap g -> OpenMap h module Downhill.Internal.Graph.NodeMap -- | NodeMap s f is a map where value of type f x is -- associated with key NodeKey s x. Type variable s -- tracks the set of nodes. Lookups never fail. Maps can be zipped -- without losing any nodes. data NodeMap s f -- | Valid key, guaranteed to be a member of s data NodeKey s x fromOpenMap :: forall f. OpenMap f -> SomeNodeMap f generate :: forall s f. IsNodeSet s => (forall x. NodeKey s x -> f x) -> NodeMap s f lookup :: NodeMap s f -> NodeKey s v -> f v -- | If key belongs to s, tryLookup will return a proof -- of this fact and a corresponding value from the map. Otherwise returns -- Nothing. tryLookup :: NodeMap s f -> OpenKey x -> Maybe (NodeKey s x, f x) toList :: NodeMap s f -> [KeyAndValue s f] toListWith :: forall s f r. (forall x. NodeKey s x -> f x -> r) -> NodeMap s f -> [r] elems :: NodeMap s (Const b) -> [b] map :: forall s f g. (forall v. f v -> g v) -> NodeMap s f -> NodeMap s g mapWithKey :: forall s f g. (forall x. NodeKey s x -> f x -> g x) -> NodeMap s f -> NodeMap s g adjust :: forall s f x. (f x -> f x) -> NodeKey s x -> NodeMap s f -> NodeMap s f zipWith :: forall s f g h. (forall x. f x -> g x -> h x) -> NodeMap s f -> NodeMap s g -> NodeMap s h class IsNodeSet s -- | NodeMap with existential set of nodes. data SomeNodeMap f [SomeNodeMap] :: IsNodeSet s => NodeMap s f -> SomeNodeMap f data KeyAndValue s f KeyAndValue :: NodeKey s x -> f x -> KeyAndValue s f instance Data.Reflection.Reifies s (Downhill.Internal.Graph.OpenMap.OpenMap Data.Proxy.Proxy) => Downhill.Internal.Graph.NodeMap.IsNodeSet (Downhill.Internal.Graph.NodeMap.NodeSetWrapper s) module Downhill.Linear.Expr -- | Expr a v represents a linear expression of type v, -- containing some free variables of type a. data Expr a v [ExprVar] :: Expr a a [ExprSum] :: BasicVector v => [Term a v] -> Expr a v -- | Argument f in Term f x must be linear -- function. That's a law. data Term a v [Term] :: (v -> VecBuilder u) -> Expr a u -> Term a v class Monoid (VecBuilder v) => BasicVector v where { -- | VecBuilder v is a sparse representation of vector v. -- Edges of a computational graph produce builders, which are then summed -- into vectors in nodes. Monoid operation <> means addition -- of vectors, but it doesn't need to compute the sum immediately - it -- might defer computation until sumBuilder is evaluated. -- --
    --   sumBuilder mempty = zeroV
    --   sumBuilder (x <> y) = sumBuilder x ^+^ sumBuilder y
    --   
-- -- mempty must be cheap. <> must be O(1). type VecBuilder v :: Type; } sumBuilder :: BasicVector v => VecBuilder v -> v identityBuilder :: BasicVector v => v -> VecBuilder v sumBuilder :: forall b. (BasicVector v, VecBuilder v ~ Maybe b, Generic b, Generic v, GBasicVector (Rep b) (Rep v), AdditiveGroup v) => VecBuilder v -> v identityBuilder :: forall b. (BasicVector v, VecBuilder v ~ Maybe b, Generic b, Generic v, GBasicVector (Rep b) (Rep v), AdditiveGroup v) => v -> VecBuilder v -- | Normally graph node would compute the sum of gradients and then -- propagate it to ancestor nodes. That's the best strategy when some -- computation needs to be performed for backpropagation. Some -- operations, like constructing/deconstructing tuples or -- wrapping/unwrapping, don't need to compute the sum. Doing so only -- destroys sparsity. A node of type SparseVector v won't sum -- the gradients, it will simply forward builders to its parents. newtype SparseVector v SparseVector :: VecBuilder v -> SparseVector v [unSparseVector] :: SparseVector v -> VecBuilder v -- | When sparsity is not needed, we can use vector v as a builder -- of itself. DenseVector takes care of that. newtype DenseVector v DenseVector :: v -> DenseVector v newtype DenseBuilder v DenseBuilder :: Maybe v -> DenseBuilder v toDenseBuilder :: v -> DenseBuilder v genericSumBuilder :: forall b v. (Generic b, Generic v, GBasicVector (Rep b) (Rep v)) => b -> v genericIdentityBuilder :: forall b v. (Generic b, Generic v, GBasicVector (Rep b) (Rep v)) => v -> b genericSumMaybeBuilder :: forall b v. (Generic b, Generic v, AdditiveGroup v, GBasicVector (Rep b) (Rep v)) => Maybe b -> v genericIdentityMaybeBuilder :: forall b v. (Generic b, Generic v, GBasicVector (Rep b) (Rep v)) => v -> Maybe b maybeToMonoid :: Monoid m => Maybe m -> m instance Data.AdditiveGroup.AdditiveGroup v => GHC.Base.Monoid (Downhill.Linear.Expr.DenseBuilder v) instance Data.AdditiveGroup.AdditiveGroup v => GHC.Base.Semigroup (Downhill.Linear.Expr.DenseBuilder v) instance Data.VectorSpace.VectorSpace v => Data.VectorSpace.VectorSpace (Downhill.Linear.Expr.DenseVector v) instance Data.AdditiveGroup.AdditiveGroup v => Data.AdditiveGroup.AdditiveGroup (Downhill.Linear.Expr.DenseVector v) instance GHC.Base.Semigroup (Downhill.Linear.Expr.VecBuilder v) => GHC.Base.Semigroup (Downhill.Linear.Expr.SparseVector v) instance GHC.Base.Monoid (Downhill.Linear.Expr.VecBuilder v) => Downhill.Linear.Expr.BasicVector (Downhill.Linear.Expr.SparseVector v) instance Downhill.Linear.Expr.BasicVector GHC.Num.Integer.Integer instance (Downhill.Linear.Expr.BasicVector a, Downhill.Linear.Expr.BasicVector b) => Downhill.Linear.Expr.BasicVector (a, b) instance (Downhill.Linear.Expr.BasicVector a, Downhill.Linear.Expr.BasicVector b, Downhill.Linear.Expr.BasicVector c) => Downhill.Linear.Expr.BasicVector (a, b, c) instance Downhill.Linear.Expr.BasicVector GHC.Types.Float instance Downhill.Linear.Expr.BasicVector GHC.Types.Double instance Data.AdditiveGroup.AdditiveGroup v => Downhill.Linear.Expr.BasicVector (Downhill.Linear.Expr.DenseVector v) instance (Downhill.Linear.Expr.BasicVector v, b GHC.Types.~ Downhill.Linear.Expr.VecBuilder v) => Downhill.Linear.Expr.GBasicVector (GHC.Generics.K1 x b) (GHC.Generics.K1 x v) instance Downhill.Linear.Expr.GBasicVector b v => Downhill.Linear.Expr.GBasicVector (GHC.Generics.M1 x y b) (GHC.Generics.M1 x y' v) instance (Downhill.Linear.Expr.GBasicVector bu u, Downhill.Linear.Expr.GBasicVector bv v) => Downhill.Linear.Expr.GBasicVector (bu GHC.Generics.:*: bv) (u GHC.Generics.:*: v) instance Downhill.Linear.Expr.GBasicVector GHC.Generics.V1 GHC.Generics.V1 instance Downhill.Linear.Expr.GBasicVector GHC.Generics.U1 GHC.Generics.U1 instance Data.AdditiveGroup.AdditiveGroup v => GHC.Base.Semigroup (Downhill.Linear.Expr.DenseSemibuilder v) module Downhill.Linear.BackGrad -- | Linear expression, made for backpropagation. It is similar to -- Expr BackFun, but has a more flexible form. newtype BackGrad a v BackGrad :: (forall x. (x -> VecBuilder v) -> Term a x) -> BackGrad a v -- | Creates a BackGrad that is backed by a real node. Gradient of -- type v will be computed and stored in a graph for this node. realNode :: Expr a v -> BackGrad a v -- | inlineNode f x will apply function f to variable -- x without creating a node. All of the gradients coming to -- this expression will be forwarded to the parents of x. -- However, if this expression is used more than once, f will be -- evaluated multiple times, too. It is intended to be used for -- newtype wrappers. inlineNode f x also doesn't -- prevent compiler to inline and optimize x inlineNode :: forall r u v. (VecBuilder v -> VecBuilder u) -> BackGrad r u -> BackGrad r v sparseNode :: forall r a z. BasicVector z => (VecBuilder z -> VecBuilder a) -> BackGrad r a -> BackGrad r z -- | BackGrad doesn't track the type of the node. Type of -- BackGrad can be changed freely as long as VecBuilder -- stays the same. castBackGrad :: forall r v z. VecBuilder z ~ VecBuilder v => BackGrad r v -> BackGrad r z instance (Downhill.Linear.Expr.BasicVector v, Data.AdditiveGroup.AdditiveGroup v) => Data.AdditiveGroup.AdditiveGroup (Downhill.Linear.BackGrad.BackGrad r v) instance (Downhill.Linear.Expr.BasicVector v, Data.VectorSpace.VectorSpace v) => Data.VectorSpace.VectorSpace (Downhill.Linear.BackGrad.BackGrad r v) -- | Types of nodes and edges of the computational graph. -- -- Parameters: -- -- module Downhill.Internal.Graph.Types -- | Edge type for backward mode evaluation newtype BackFun u v BackFun :: (v -> VecBuilder u) -> BackFun u v [unBackFun] :: BackFun u v -> v -> VecBuilder u -- | Edge type for forward mode evaluation newtype FwdFun u v FwdFun :: (u -> VecBuilder v) -> FwdFun u v [unFwdFun] :: FwdFun u v -> u -> VecBuilder v flipBackFun :: BackFun u v -> FwdFun v u flipFwdFun :: FwdFun u v -> BackFun v u module Downhill.Internal.Graph.OpenGraph data OpenEdge a v [OpenEdge] :: BackFun u v -> OpenEndpoint a u -> OpenEdge a v data OpenEndpoint a v [OpenSourceNode] :: OpenEndpoint a a [OpenInnerNode] :: OpenKey v -> OpenEndpoint a v data OpenNode a v OpenNode :: [OpenEdge a v] -> OpenNode a v -- | Computational graph under construction. Open refers to the set -- of the nodes – new nodes can be added to this graph. Once the graph is -- complete the set of nodes will be frozen and the type of the graph -- will become Graph (Downhill.Internal.Graph module). data OpenGraph a z OpenGraph :: OpenNode a z -> OpenMap (OpenNode a) -> OpenGraph a z -- | Collects duplicate nodes in Expr tree and converts it to a -- graph. recoverSharing :: forall a z. BasicVector z => [Term a z] -> IO (OpenGraph a z) instance GHC.Base.Monad (Downhill.Internal.Graph.OpenGraph.TreeBuilder a) instance GHC.Base.Applicative (Downhill.Internal.Graph.OpenGraph.TreeBuilder a) instance GHC.Base.Functor (Downhill.Internal.Graph.OpenGraph.TreeBuilder a) module Downhill.Internal.Graph.Graph data Graph s e a z Graph :: NodeMap s (Node s e a) -> Node s e a z -> Graph s e a z [graphInnerNodes] :: Graph s e a z -> NodeMap s (Node s e a) [graphFinalNode] :: Graph s e a z -> Node s e a z -- | Inner node. This does not include initial node. Contains a list of -- ingoing edges. data Node s e a v Node :: [Edge s e a v] -> Node s e a v data SomeGraph e a z [SomeGraph] :: IsNodeSet s => Graph s e a z -> SomeGraph e a z -- | Forward mode evaluation evalGraph :: forall s x z. Graph s FwdFun z x -> z -> x -- | Reverse edges. Turns reverse mode evaluation into forward mode. transposeGraph :: forall s f g a z. IsNodeSet s => (forall u v. f u v -> g v u) -> Graph s f a z -> Graph s g z a -- | Will crash if graph has invalid keys unsafeFromOpenGraph :: (BasicVector a, HasCallStack) => OpenGraph a v -> SomeGraph BackFun a v module Downhill.Linear.Backprop -- | Purity of this function depends on laws of arithmetic and linearity -- law of Term. If your addition is approximately associative, -- then this function is approximately pure. Fair? backprop :: forall a v. (BasicVector a, BasicVector v) => BackGrad a v -> v -> a buildGraph :: forall a v. (BasicVector a, BasicVector v) => [Term a v] -> IO (SomeGraph BackFun a v) module Downhill.Grad -- | Dual of a vector v is a linear map v -> Scalar v. class (Scalar v ~ Scalar dv, AdditiveGroup (Scalar v), VectorSpace v, VectorSpace dv) => Dual v dv evalGrad :: Dual v dv => dv -> v -> Scalar v evalGrad :: (Dual v dv, GDual (Scalar v) (Rep v) (Rep dv), Generic dv, Generic v) => dv -> v -> Scalar v -- | u . v = evalDual (riesz u) v | du . dv = evalDual du -- (coriesz dv) class Dual v dv => HilbertSpace v dv riesz :: HilbertSpace v dv => v -> dv coriesz :: HilbertSpace v dv => dv -> v class (Dual (Tang p) (Grad p), Scalar (Tang p) ~ Scalar (Grad p)) => Manifold p where { -- | Tangent space. type Tang p :: Type; -- | Cotangent space. type Grad p :: Type; } -- | Differentiable functions don't need to be constrained to vector -- spaces, they can be defined on other smooth manifolds, too. type HasGrad p = (Manifold p, BasicVector (Grad p)) type MScalar p = Scalar (Tang p) type GradBuilder v = VecBuilder (Grad v) type HasGradAffine p = (AffineSpace p, HasGrad p, HasGrad (Tang p), Tang p ~ Diff p, Tang (Tang p) ~ Tang p, Grad (Tang p) ~ Grad p) instance (Downhill.Grad.HasGrad a, Downhill.Grad.HasGrad b, Downhill.Grad.MScalar b GHC.Types.~ Downhill.Grad.MScalar a) => Downhill.Grad.Manifold (a, b) instance (Downhill.Grad.HasGrad a, Downhill.Grad.HasGrad b, Downhill.Grad.HasGrad c, Downhill.Grad.MScalar b GHC.Types.~ Downhill.Grad.MScalar a, Downhill.Grad.MScalar c GHC.Types.~ Downhill.Grad.MScalar a) => Downhill.Grad.Manifold (a, b, c) instance Downhill.Grad.Manifold GHC.Num.Integer.Integer instance Downhill.Grad.Manifold GHC.Types.Float instance Downhill.Grad.Manifold GHC.Types.Double instance Downhill.Grad.Dual GHC.Num.Integer.Integer GHC.Num.Integer.Integer instance (Data.VectorSpace.Scalar a GHC.Types.~ Data.VectorSpace.Scalar b, Downhill.Grad.Dual a da, Downhill.Grad.Dual b db) => Downhill.Grad.Dual (a, b) (da, db) instance (Data.VectorSpace.Scalar a GHC.Types.~ Data.VectorSpace.Scalar b, Data.VectorSpace.Scalar a GHC.Types.~ Data.VectorSpace.Scalar c, Downhill.Grad.Dual a da, Downhill.Grad.Dual b db, Downhill.Grad.Dual c dc) => Downhill.Grad.Dual (a, b, c) (da, db, dc) instance Downhill.Grad.Dual GHC.Types.Float GHC.Types.Float instance Downhill.Grad.Dual GHC.Types.Double GHC.Types.Double instance (s GHC.Types.~ Data.VectorSpace.Scalar v, Downhill.Grad.Dual v dv) => Downhill.Grad.GDual s (GHC.Generics.K1 x v) (GHC.Generics.K1 x dv) instance Downhill.Grad.GDual s v dv => Downhill.Grad.GDual s (GHC.Generics.M1 x y v) (GHC.Generics.M1 x y' dv) instance (Data.AdditiveGroup.AdditiveGroup s, Downhill.Grad.GDual s u du, Downhill.Grad.GDual s v dv) => Downhill.Grad.GDual s (u GHC.Generics.:*: v) (du GHC.Generics.:*: dv) instance Downhill.Grad.GDual s GHC.Generics.V1 GHC.Generics.V1 instance Data.AdditiveGroup.AdditiveGroup s => Downhill.Grad.GDual s GHC.Generics.U1 GHC.Generics.U1 -- | While BackGrad is intended to be simple to construct manually, -- this module provides a way to do that with a bit less of boilerplate. module Downhill.Linear.Lift lift1 :: forall z r a. BasicVector z => (z -> VecBuilder a) -> BackGrad r a -> BackGrad r z lift2 :: forall z r a b. BasicVector z => (z -> VecBuilder a) -> (z -> VecBuilder b) -> BackGrad r a -> BackGrad r b -> BackGrad r z lift3 :: forall z r a b c. BasicVector z => (z -> VecBuilder a) -> (z -> VecBuilder b) -> (z -> VecBuilder c) -> BackGrad r a -> BackGrad r b -> BackGrad r c -> BackGrad r z lift1_dense :: (BasicVector v, BasicVector a) => (v -> a) -> BackGrad r a -> BackGrad r v lift2_dense :: (BasicVector v, BasicVector a, BasicVector b) => (v -> a) -> (v -> b) -> BackGrad r a -> BackGrad r b -> BackGrad r v lift3_dense :: (BasicVector v, BasicVector a, BasicVector b, BasicVector c) => (v -> a) -> (v -> b) -> (v -> c) -> BackGrad r a -> BackGrad r b -> BackGrad r c -> BackGrad r v -- | Same as sparseNode, included here for completeness. lift1_sparse :: forall r a z. BasicVector z => (VecBuilder z -> VecBuilder a) -> BackGrad r a -> BackGrad r z lift2_sparse :: forall r a b z. BasicVector z => (VecBuilder z -> VecBuilder a) -> (VecBuilder z -> VecBuilder b) -> BackGrad r a -> BackGrad r b -> BackGrad r z lift3_sparse :: forall r a b c z. BasicVector z => (VecBuilder z -> VecBuilder a) -> (VecBuilder z -> VecBuilder b) -> (VecBuilder z -> VecBuilder c) -> BackGrad r a -> BackGrad r b -> BackGrad r c -> BackGrad r z module Downhill.Linear.Prelude -- |
--   getFst :: (BasicVector (DualOf a), BasicVector (DualOf b)) => BackGrad r (a, b) -> BackGrad r a
--   getFst (T2 x _) = x
--   
-- --
--   mkPair :: (BasicVector (DualOf a), BasicVector (DualOf b)) => BackGrad r a -> BackGrad r b -> BackGrad r (a, b)
--   mkPair x y = (T2 x y)
--   
pattern T2 :: forall r a b. (BasicVector a, BasicVector b) => BackGrad r a -> BackGrad r b -> BackGrad r (a, b) pattern T3 :: forall r a b c. (BasicVector a, BasicVector b, BasicVector c) => BackGrad r a -> BackGrad r b -> BackGrad r c -> BackGrad r (a, b, c) module Downhill.BVar -- | Variable is a value paired with derivative. data BVar r a BVar :: a -> BackGrad r (Grad a) -> BVar r a [bvarValue] :: BVar r a -> a [bvarGrad] :: BVar r a -> BackGrad r (Grad a) -- | A variable with identity derivative. var :: a -> BVar (Grad a) a -- | A variable with derivative of zero. constant :: forall r a. (BasicVector (Grad a), AdditiveGroup (Grad a)) => a -> BVar r a -- | Reverse mode differentiation. backprop :: forall r a. (HasGrad a, BasicVector r) => BVar r a -> Grad a -> r pattern T2 :: forall r a b. (BasicVector (Grad a), BasicVector (Grad b)) => BVar r a -> BVar r b -> BVar r (a, b) pattern T3 :: forall r a b c. (BasicVector (Grad a), BasicVector (Grad b), BasicVector (Grad c)) => BVar r a -> BVar r b -> BVar r c -> BVar r (a, b, c) instance (Data.AdditiveGroup.AdditiveGroup b, Downhill.Grad.HasGrad b) => Data.AdditiveGroup.AdditiveGroup (Downhill.BVar.BVar r b) instance (GHC.Num.Num b, Downhill.Grad.HasGrad b, Downhill.Grad.MScalar b GHC.Types.~ b) => GHC.Num.Num (Downhill.BVar.BVar r b) instance (GHC.Real.Fractional b, Downhill.Grad.HasGrad b, Downhill.Grad.MScalar b GHC.Types.~ b) => GHC.Real.Fractional (Downhill.BVar.BVar r b) instance (GHC.Float.Floating b, Downhill.Grad.HasGrad b, Downhill.Grad.MScalar b GHC.Types.~ b) => GHC.Float.Floating (Downhill.BVar.BVar r b) instance (Data.VectorSpace.VectorSpace v, Downhill.Grad.HasGrad v, Downhill.Grad.Tang v GHC.Types.~ v, Downhill.Grad.HasGrad (Downhill.Grad.MScalar v), Downhill.Grad.Grad (Data.VectorSpace.Scalar v) GHC.Types.~ Data.VectorSpace.Scalar v) => Data.VectorSpace.VectorSpace (Downhill.BVar.BVar r v) instance (Downhill.Grad.HasGrad p, Downhill.Grad.HasGradAffine p) => Data.AffineSpace.AffineSpace (Downhill.BVar.BVar r p) instance (Downhill.Grad.HasGrad (Data.VectorSpace.Scalar v), Downhill.Grad.HasGrad v, Downhill.Grad.HasGrad dv, Downhill.Grad.Dual v dv, Downhill.Grad.Grad dv GHC.Types.~ v, Downhill.Grad.Grad v GHC.Types.~ dv, Downhill.Grad.Tang v GHC.Types.~ v, Downhill.Grad.Tang dv GHC.Types.~ dv, Downhill.Grad.Grad (Data.VectorSpace.Scalar dv) GHC.Types.~ Data.VectorSpace.Scalar dv) => Downhill.Grad.Dual (Downhill.BVar.BVar r v) (Downhill.BVar.BVar r dv) instance (Downhill.Grad.HasGrad (Downhill.Grad.MScalar p), Downhill.Grad.HasGrad (Downhill.Grad.Tang p), Downhill.Grad.HasGrad (Downhill.Grad.Grad p), Downhill.Grad.Grad (Downhill.Grad.Grad p) GHC.Types.~ Downhill.Grad.Tang p, Downhill.Grad.Tang (Downhill.Grad.Grad p) GHC.Types.~ Downhill.Grad.Grad p, Downhill.Grad.Tang (Downhill.Grad.Tang p) GHC.Types.~ Downhill.Grad.Tang p, Downhill.Grad.Grad (Downhill.Grad.Tang p) GHC.Types.~ Downhill.Grad.Grad p, Downhill.Grad.Grad (Downhill.Grad.MScalar p) GHC.Types.~ Downhill.Grad.MScalar p, Data.VectorSpace.Scalar (Downhill.Grad.Grad p) GHC.Types.~ Data.VectorSpace.Scalar (Downhill.Grad.Tang p), Downhill.Grad.Manifold p) => Downhill.Grad.Manifold (Downhill.BVar.BVar r p) instance (Downhill.Grad.HilbertSpace v dv, Downhill.Grad.HasGrad (Data.VectorSpace.Scalar v), Downhill.Grad.HasGrad v, Downhill.Grad.HasGrad dv, Downhill.Grad.Grad dv GHC.Types.~ v, Downhill.Grad.Grad v GHC.Types.~ dv, Downhill.Grad.Tang v GHC.Types.~ v, Downhill.Grad.Tang dv GHC.Types.~ dv, Downhill.Grad.Grad (Data.VectorSpace.Scalar dv) GHC.Types.~ Data.VectorSpace.Scalar dv) => Downhill.Grad.HilbertSpace (Downhill.BVar.BVar r v) (Downhill.BVar.BVar r dv) instance (Data.VectorSpace.VectorSpace v, Downhill.Grad.HasGrad v, Downhill.Grad.Tang v GHC.Types.~ v, Downhill.Grad.HilbertSpace (Downhill.Grad.Tang v) (Downhill.Grad.Grad v), Downhill.Linear.Expr.BasicVector (Downhill.Grad.MScalar v), Downhill.Grad.Grad (Downhill.Grad.MScalar v) GHC.Types.~ Downhill.Grad.MScalar v, Data.VectorSpace.InnerSpace v, Downhill.Grad.HasGrad (Downhill.Grad.MScalar v)) => Data.VectorSpace.InnerSpace (Downhill.BVar.BVar r v) module Downhill.BVar.Prelude pattern T2 :: (HasGrad a, HasGrad b) => BVar r a -> BVar r b -> BVar r (a, b) pattern T3 :: (HasGrad a, HasGrad b, HasGrad c) => BVar r a -> BVar r b -> BVar r c -> BVar r (a, b, c) module Downhill.Metric -- | MetricTensor converts gradients to vectors. -- -- It is really inverse of a metric tensor, because it maps cotangent -- space into tangent space. Gradient descent doesn't need metric tensor, -- it needs inverse. class Dual (Tang p) (Grad p) => MetricTensor p g -- | m must be symmetric: -- --
--   evalGrad x (evalMetric m y) = evalGrad y (evalMetric m x)
--   
evalMetric :: MetricTensor p g => g -> Grad p -> Tang p -- |
--   innerProduct m x y = evalGrad x (evalMetric m y)
--   
innerProduct :: MetricTensor p g => g -> Grad p -> Grad p -> MScalar p -- |
--   sqrNorm m x = innerProduct m x x
--   
sqrNorm :: MetricTensor p g => g -> Grad p -> MScalar p instance (Downhill.Grad.Dual (Downhill.Grad.Tang p) (Downhill.Grad.Grad p), Downhill.Grad.Grad p GHC.Types.~ Downhill.Grad.Tang p) => Downhill.Metric.MetricTensor p Downhill.Metric.L2 instance Downhill.Metric.MetricTensor GHC.Num.Integer.Integer GHC.Num.Integer.Integer instance (Downhill.Grad.MScalar a GHC.Types.~ Downhill.Grad.MScalar b, Downhill.Metric.MetricTensor a ma, Downhill.Metric.MetricTensor b mb) => Downhill.Metric.MetricTensor (a, b) (ma, mb) instance (Downhill.Grad.MScalar a GHC.Types.~ Downhill.Grad.MScalar b, Downhill.Grad.MScalar a GHC.Types.~ Downhill.Grad.MScalar c, Downhill.Metric.MetricTensor a ma, Downhill.Metric.MetricTensor b mb, Downhill.Metric.MetricTensor c mc) => Downhill.Metric.MetricTensor (a, b, c) (ma, mb, mc) instance Downhill.Metric.MetricTensor GHC.Types.Float GHC.Types.Float instance Downhill.Metric.MetricTensor GHC.Types.Double GHC.Types.Double -- | Easy backpropagation when all variables have the same type. -- --
--   data MyRecord a = ...
--     deriving (Functor, Foldable, Traversable)
--   
--   deriving via (TraversableVar MyRecord a) instance HasGrad a => HasGrad (MyRecord a)
--   
-- --

Gradient type

-- -- One might excect gradient type to be type Grad (MyRecord a) = -- MyRecord (Grad a), but it's not the case, because record could -- contain additional members apart from as, for example: -- --
--   data MyPoint a = MyPoint
--   {
--   ,  pointLabel :: String
--   ,  pointX :: a
--   ,  pointY :: a
--   }
--   
-- -- and MyPoint (Grad a) can't be made VectorSpace. -- Gradient type Grad (MyRecord a) is a newtype wrapper over -- IntMap that is not exported. module Downhill.BVar.Traversable -- |
--   backpropTraversable one combine fun
--   
-- -- one is a value to be backpropagated. In case of p -- being scalar, set one to 1 to compute unscaled gradient. -- -- combine is given value of a parameter and its gradient to -- construct result, just like zipWith. -- -- fun is the function to be differentiated. backpropTraversable :: forall f a b p. (Traversable f, Grad (f a) ~ Grad (TraversableVar f a), HasGrad a, HasGrad p) => Grad p -> (a -> Grad a -> b) -> (forall r. f (BVar r a) -> BVar r p) -> f a -> f b -- | Like backpropTraversable, but returns gradient only. backpropTraversable_GradOnly :: forall f a p. (Traversable f, Grad (f a) ~ Grad (TraversableVar f a), HasGrad a, HasGrad p) => Grad p -> (forall r. f (BVar r a) -> BVar r p) -> f a -> f (Grad a) -- | backpropTraversable specialized to return a pair of value and -- gradient. backpropTraversable_ValueAndGrad :: forall f a p. (Traversable f, Grad (f a) ~ Grad (TraversableVar f a), HasGrad a, HasGrad p) => Grad p -> (forall r. f (BVar r a) -> BVar r p) -> f a -> f (a, Grad a) -- | Note that splitTraversable won't be useful for top level -- BVar, because the type Grad (f a) is not exposed. splitTraversable :: forall f r a. (Traversable f, Grad (f a) ~ Grad (TraversableVar f a), HasGrad a) => BVar r (f a) -> f (BVar r a) -- | Provides HasGrad instance for use in deriving via newtype TraversableVar f a TraversableVar :: f a -> TraversableVar f a [unTraversableVar] :: TraversableVar f a -> f a instance Data.Traversable.Traversable f => Data.Traversable.Traversable (Downhill.BVar.Traversable.TraversableVar f) instance Data.Foldable.Foldable f => Data.Foldable.Foldable (Downhill.BVar.Traversable.TraversableVar f) instance GHC.Base.Functor f => GHC.Base.Functor (Downhill.BVar.Traversable.TraversableVar f) instance GHC.Generics.Generic (Downhill.BVar.Traversable.TraversableMetric f g) instance GHC.Show.Show v => GHC.Show.Show (Downhill.BVar.Traversable.IntmapVector f v) instance GHC.Base.Semigroup v => GHC.Base.Semigroup (Downhill.BVar.Traversable.IntmapVector f v) instance GHC.Base.Monoid v => GHC.Base.Monoid (Downhill.BVar.Traversable.IntmapVector f v) instance Downhill.Metric.MetricTensor p g => Downhill.Metric.MetricTensor (Downhill.BVar.Traversable.TraversableVar f p) (Downhill.BVar.Traversable.TraversableMetric f g) instance Downhill.Grad.Manifold a => Downhill.Grad.Manifold (Downhill.BVar.Traversable.TraversableVar f a) instance Downhill.Grad.Manifold v => Downhill.Grad.Manifold (Downhill.BVar.Traversable.IntmapVector f v) instance Data.AdditiveGroup.AdditiveGroup a => Data.AdditiveGroup.AdditiveGroup (Downhill.BVar.Traversable.IntmapVector f a) instance Data.VectorSpace.VectorSpace v => Data.VectorSpace.VectorSpace (Downhill.BVar.Traversable.IntmapVector f v) instance Downhill.Grad.Dual dv v => Downhill.Grad.Dual (Downhill.BVar.Traversable.IntmapVector f dv) (Downhill.BVar.Traversable.IntmapVector f v) instance Downhill.Linear.Expr.BasicVector v => Downhill.Linear.Expr.BasicVector (Downhill.BVar.Traversable.IntmapVector f v) instance Data.AdditiveGroup.AdditiveGroup g => Data.AdditiveGroup.AdditiveGroup (Downhill.BVar.Traversable.TraversableMetric f g) instance Data.VectorSpace.VectorSpace g => Data.VectorSpace.VectorSpace (Downhill.BVar.Traversable.TraversableMetric f g) module Downhill.BVar.Num -- | AsNum a implements many instances in terms of Num a -- instance. newtype AsNum a AsNum :: a -> AsNum a [unAsNum] :: AsNum a -> a type NumBVar a = BVar (AsNum a) (AsNum a) numbvarValue :: NumBVar a -> a var :: Num a => a -> NumBVar a constant :: forall a. Num a => a -> NumBVar a backpropNum :: forall a. Num a => NumBVar a -> a instance GHC.Float.Floating a => GHC.Float.Floating (Downhill.BVar.Num.AsNum a) instance GHC.Real.Fractional a => GHC.Real.Fractional (Downhill.BVar.Num.AsNum a) instance GHC.Num.Num a => GHC.Num.Num (Downhill.BVar.Num.AsNum a) instance GHC.Show.Show a => GHC.Show.Show (Downhill.BVar.Num.AsNum a) instance GHC.Num.Num a => Downhill.Grad.Dual (Downhill.BVar.Num.AsNum a) (Downhill.BVar.Num.AsNum a) instance GHC.Num.Num a => Downhill.Grad.Manifold (Downhill.BVar.Num.AsNum a) instance GHC.Num.Num a => Downhill.Metric.MetricTensor (Downhill.BVar.Num.AsNum a) (Downhill.BVar.Num.AsNum a) instance GHC.Num.Num a => Data.AdditiveGroup.AdditiveGroup (Downhill.BVar.Num.AsNum a) instance GHC.Num.Num a => Data.VectorSpace.VectorSpace (Downhill.BVar.Num.AsNum a) instance GHC.Num.Num a => Downhill.Linear.Expr.BasicVector (Downhill.BVar.Num.AsNum a) instance GHC.Num.Num a => Data.AffineSpace.AffineSpace (Downhill.BVar.Num.AsNum a)