futhark-0.23.1: An optimising compiler for a functional, array-oriented language.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Futhark.AD.Rev.Monad

Synopsis

Documentation

data ADM a Source #

Instances

Instances details
Applicative ADM Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Methods

pure :: a -> ADM a #

(<*>) :: ADM (a -> b) -> ADM a -> ADM b #

liftA2 :: (a -> b -> c) -> ADM a -> ADM b -> ADM c #

(*>) :: ADM a -> ADM b -> ADM b #

(<*) :: ADM a -> ADM b -> ADM a #

Functor ADM Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Methods

fmap :: (a -> b) -> ADM a -> ADM b #

(<$) :: a -> ADM b -> ADM a #

Monad ADM Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Methods

(>>=) :: ADM a -> (a -> ADM b) -> ADM b #

(>>) :: ADM a -> ADM b -> ADM b #

return :: a -> ADM a #

MonadBuilder ADM Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Associated Types

type Rep ADM Source #

MonadFreshNames ADM Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

HasScope SOACS ADM Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

LocalScope SOACS ADM Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Methods

localScope :: Scope SOACS -> ADM a -> ADM a Source #

MonadState RState ADM Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Methods

get :: ADM RState #

put :: RState -> ADM () #

state :: (RState -> (a, RState)) -> ADM a #

type Rep ADM Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

type Rep ADM = SOACS

runADM :: MonadFreshNames m => ADM a -> m a Source #

data Adj Source #

The adjoint of a variable.

Instances

Instances details
Show Adj Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Methods

showsPrec :: Int -> Adj -> ShowS #

show :: Adj -> String #

showList :: [Adj] -> ShowS #

Substitute Adj Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Eq Adj Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Methods

(==) :: Adj -> Adj -> Bool #

(/=) :: Adj -> Adj -> Bool #

Ord Adj Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Methods

compare :: Adj -> Adj -> Ordering #

(<) :: Adj -> Adj -> Bool #

(<=) :: Adj -> Adj -> Bool #

(>) :: Adj -> Adj -> Bool #

(>=) :: Adj -> Adj -> Bool #

max :: Adj -> Adj -> Adj #

min :: Adj -> Adj -> Adj #

data InBounds Source #

Whether Sparse should check bounds or assume they are correct. The latter results in simpler code.

Constructors

CheckBounds (Maybe SubExp)

If a SubExp is provided, it references a boolean that is true when in-bounds.

AssumeBounds 
OutOfBounds

Dynamically these will always fail, so don't bother generating code for the update. This is only needed to ensure a consistent representation of sparse Jacobians.

Instances

Instances details
Show InBounds Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Eq InBounds Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Ord InBounds Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

data Sparse Source #

A symbolic representation of an array that is all zeroes, except at certain indexes.

Constructors

Sparse 

Fields

Instances

Instances details
Show Sparse Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Eq Sparse Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

Methods

(==) :: Sparse -> Sparse -> Bool #

(/=) :: Sparse -> Sparse -> Bool #

Ord Sparse Source # 
Instance details

Defined in Futhark.AD.Rev.Monad

setAdj :: VName -> Adj -> ADM () Source #

adjsReps :: [Adj] -> ([SubExp], [SubExp] -> [Adj]) Source #

Conveniently convert a list of Adjs to their representation, as well as produce a function for converting back.

copyConsumedArrsInStm :: Stm SOACS -> ADM (Substitutions, Stms SOACS) Source #

Create copies of all arrays consumed in the given statement, and return statements which include copies of the consumed arrays.

See Note [Consumption].

subAD :: ADM a -> ADM a Source #

noAdjsFor :: Names -> ADM a -> ADM a Source #

isActive :: VName -> ADM Bool Source #

Is this primal variable active in the AD sense? FIXME: this is (obviously) much too conservative.

tabNest :: Int -> [VName] -> ([VName] -> [VName] -> ADM [VName]) -> ADM [VName] Source #

oneExp :: Type -> Exp rep Source #

zeroExp :: Type -> Exp rep Source #

addLambda :: Type -> ADM (Lambda SOACS) Source #

Construct a lambda for adding two values of the given type.

data VjpOps Source #

Constructors

VjpOps 

Fields

setLoopTape :: VName -> VName -> ADM () Source #

setLoopTape v vs establishes vs as the name of the array where values of loop parameter v from the forward pass are stored.

lookupLoopTape :: VName -> ADM (Maybe VName) Source #

Look-up the name of the array where v is stored.

substLoopTape :: VName -> VName -> ADM () Source #

substLoopTape v v' substitutes the key v for v'. That is, if v |-> vs then after the substitution v' |-> vs (and v points to nothing).

renameLoopTape :: Substitutions -> ADM () Source #

Renames the keys of the loop tape. Useful for fixing the the names in the loop tape after a loop rename.