Copyright | (c) Edward Kmett 2010-2021 |
---|---|
License | BSD3 |
Maintainer | ekmett@gmail.com |
Stability | experimental |
Portability | GHC only |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
This module provides reverse-mode Automatic Differentiation implementation using linear time topological sorting after the fact.
For this form of reverse-mode AD we use StableName
to recover
sharing information from the tape to avoid combinatorial explosion, and thus
run asymptotically faster than it could without such sharing information, but the use
of side-effects contained herein is benign.
Synopsis
- newtype KahnFloat = Kahn (Tape KahnFloat)
- data Tape t
- partials :: KahnFloat -> [(Int, Float)]
- partialArray :: (Int, Int) -> KahnFloat -> UArray Int Float
- partialMap :: KahnFloat -> IntMap Float
- derivative :: KahnFloat -> Float
- derivative' :: KahnFloat -> (Float, Float)
- vgrad :: Grad i o o' => i -> o
- vgrad' :: Grad i o o' => i -> o'
- class Grad i o o' | i -> o o', o -> i o', o' -> i o where
- bind :: Traversable f => f Float -> (f KahnFloat, (Int, Int))
- unbind :: Functor f => f KahnFloat -> UArray Int Float -> f Float
- unbindMap :: Functor f => f KahnFloat -> IntMap Float -> f Float
- unbindWithUArray :: (Functor f, IArray UArray b) => (Float -> b -> c) -> f KahnFloat -> UArray Int b -> f c
- unbindWithArray :: Functor f => (Float -> b -> c) -> f KahnFloat -> Array Int b -> f c
- unbindMapWithDefault :: Functor f => b -> (Float -> b -> c) -> f KahnFloat -> IntMap b -> f c
- primal :: KahnFloat -> Float
- var :: Float -> Int -> KahnFloat
- varId :: KahnFloat -> Int
Documentation
Kahn
is a Mode
using reverse-mode automatic differentiation that provides fast diffFU
, diff2FU
, grad
, grad2
and a fast jacobian
when you have a significantly smaller number of outputs than inputs.
Instances
A Tape
records the information needed back propagate from the output to each input during reverse Mode
AD.
Instances
Data t => Data (Tape t) Source # | |
Defined in Numeric.AD.Internal.Kahn.Float gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Tape t -> c (Tape t) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Tape t) # toConstr :: Tape t -> Constr # dataTypeOf :: Tape t -> DataType # dataCast1 :: Typeable t0 => (forall d. Data d => c (t0 d)) -> Maybe (c (Tape t)) # dataCast2 :: Typeable t0 => (forall d e. (Data d, Data e) => c (t0 d e)) -> Maybe (c (Tape t)) # gmapT :: (forall b. Data b => b -> b) -> Tape t -> Tape t # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Tape t -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Tape t -> r # gmapQ :: (forall d. Data d => d -> u) -> Tape t -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Tape t -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Tape t -> m (Tape t) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Tape t -> m (Tape t) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Tape t -> m (Tape t) # | |
Show t => Show (Tape t) Source # | |
partials :: KahnFloat -> [(Int, Float)] Source #
This returns a list of contributions to the partials. The variable ids returned in the list are likely not unique!
derivative :: KahnFloat -> Float Source #
class Grad i o o' | i -> o o', o -> i o', o' -> i o where Source #
unbindWithUArray :: (Functor f, IArray UArray b) => (Float -> b -> c) -> f KahnFloat -> UArray Int b -> f c Source #