Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- data ADM a
- data RState = RState {}
- runADM :: MonadFreshNames m => ADM a -> m a
- data Adj
- data InBounds
- data Sparse = Sparse {
- sparseShape :: Shape
- sparseType :: PrimType
- sparseIdxVals :: [(InBounds, SubExp, SubExp)]
- adjFromParam :: Param t -> Adj
- adjFromVar :: VName -> Adj
- lookupAdj :: VName -> ADM Adj
- lookupAdjVal :: VName -> ADM VName
- adjVal :: Adj -> ADM VName
- updateAdj :: VName -> VName -> ADM ()
- updateSubExpAdj :: SubExp -> VName -> ADM ()
- updateAdjSlice :: Slice SubExp -> VName -> VName -> ADM ()
- updateAdjIndex :: VName -> (InBounds, SubExp) -> SubExp -> ADM ()
- setAdj :: VName -> Adj -> ADM ()
- insAdj :: VName -> VName -> ADM ()
- adjsReps :: [Adj] -> ([SubExp], [SubExp] -> [Adj])
- copyConsumedArrsInStm :: Stm SOACS -> ADM (Substitutions, Stms SOACS)
- copyConsumedArrsInBody :: [VName] -> Body SOACS -> ADM Substitutions
- addSubstitution :: VName -> VName -> ADM ()
- returnSweepCode :: ADM a -> ADM a
- adjVName :: VName -> ADM VName
- subAD :: ADM a -> ADM a
- noAdjsFor :: Names -> ADM a -> ADM a
- subSubsts :: ADM a -> ADM a
- isActive :: VName -> ADM Bool
- tabNest :: Int -> [VName] -> ([VName] -> [VName] -> ADM [VName]) -> ADM [VName]
- oneExp :: Type -> Exp rep
- zeroExp :: Type -> Exp rep
- unitAdjOfType :: Type -> ADM Adj
- addLambda :: Type -> ADM (Lambda SOACS)
- data VjpOps = VjpOps {}
- setLoopTape :: VName -> VName -> ADM ()
- lookupLoopTape :: VName -> ADM (Maybe VName)
- substLoopTape :: VName -> VName -> ADM ()
- renameLoopTape :: Substitutions -> ADM ()
Documentation
Instances
Applicative ADM Source # | |
Functor ADM Source # | |
Monad ADM Source # | |
MonadBuilder ADM Source # | |
Defined in Futhark.AD.Rev.Monad mkExpDecM :: Pat (LetDec (Rep ADM)) -> Exp (Rep ADM) -> ADM (ExpDec (Rep ADM)) Source # mkBodyM :: Stms (Rep ADM) -> Result -> ADM (Body (Rep ADM)) Source # mkLetNamesM :: [VName] -> Exp (Rep ADM) -> ADM (Stm (Rep ADM)) Source # addStm :: Stm (Rep ADM) -> ADM () Source # addStms :: Stms (Rep ADM) -> ADM () Source # | |
MonadFreshNames ADM Source # | |
Defined in Futhark.AD.Rev.Monad getNameSource :: ADM VNameSource Source # putNameSource :: VNameSource -> ADM () Source # | |
HasScope SOACS ADM Source # | |
LocalScope SOACS ADM Source # | |
Defined in Futhark.AD.Rev.Monad | |
MonadState RState ADM Source # | |
type Rep ADM Source # | |
Defined in Futhark.AD.Rev.Monad |
Instances
MonadState RState ADM Source # | |
MonadFreshNames (State RState) Source # | |
Defined in Futhark.AD.Rev.Monad getNameSource :: State RState VNameSource Source # putNameSource :: VNameSource -> State RState () Source # |
runADM :: MonadFreshNames m => ADM a -> m a Source #
The adjoint of a variable.
Whether Sparse
should check bounds or assume they are correct.
The latter results in simpler code.
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. |
A symbolic representation of an array that is all zeroes, except at certain indexes.
Sparse | |
|
adjFromParam :: Param t -> Adj Source #
adjFromVar :: VName -> Adj 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].
copyConsumedArrsInBody :: [VName] -> Body SOACS -> ADM Substitutions Source #
returnSweepCode :: 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.
addLambda :: Type -> ADM (Lambda SOACS) Source #
Construct a lambda for adding two values of the given type.
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.