hakaru-0.6.0: A probabilistic programming language

CopyrightCopyright (c) 2016 the Hakaru team
LicenseBSD3
Stabilityexperimental
PortabilityGHC-only
Safe HaskellNone
LanguageHaskell2010

Language.Hakaru.Syntax.Transform

Contents

Description

The internal syntax of Hakaru transformations, which are functions on Hakaru terms which are neither primitive, nor expressible in terms of Hakaru primitives.

Synopsis

Transformation internal syntax

data TransformImpl Source #

Some transformations have the same type and same semantics, but are implemented in multiple different ways. Such transformations are distinguished in concrete syntax by differing keywords.

Constructors

InMaple 
InHaskell 
Instances
Eq TransformImpl Source # 
Instance details
Data TransformImpl Source # 
Instance details

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TransformImpl -> c TransformImpl #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TransformImpl #

toConstr :: TransformImpl -> Constr #

dataTypeOf :: TransformImpl -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c TransformImpl) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TransformImpl) #

gmapT :: (forall b. Data b => b -> b) -> TransformImpl -> TransformImpl #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TransformImpl -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TransformImpl -> r #

gmapQ :: (forall d. Data d => d -> u) -> TransformImpl -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TransformImpl -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TransformImpl -> m TransformImpl #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TransformImpl -> m TransformImpl #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TransformImpl -> m TransformImpl #

Ord TransformImpl Source # 
Instance details
Read TransformImpl Source # 
Instance details
Show TransformImpl Source # 
Instance details

data Transform :: [([Hakaru], Hakaru)] -> Hakaru -> * where Source #

Transformations and their types. Like SCon.

Constructors

Expect :: Transform '[LC (HMeasure a), '('[a], HProb)] HProb 
Observe :: Transform '[LC (HMeasure a), LC a] (HMeasure a) 
MH :: Transform '[LC (a :-> HMeasure a), LC (HMeasure a)] (a :-> HMeasure (HPair a HProb)) 
MCMC :: Transform '[LC (a :-> HMeasure a), LC (HMeasure a)] (a :-> HMeasure a) 
Disint :: TransformImpl -> Transform '[LC (HMeasure (HPair a b))] (a :-> HMeasure b) 
Summarize :: Transform '[LC a] a 
Simplify :: Transform '[LC a] a 
Reparam :: Transform '[LC a] a 
Instances
Eq (Transform args a) Source # 
Instance details

Methods

(==) :: Transform args a -> Transform args a -> Bool #

(/=) :: Transform args a -> Transform args a -> Bool #

Show (Transform args a) Source # 
Instance details

Methods

showsPrec :: Int -> Transform args a -> ShowS #

show :: Transform args a -> String #

showList :: [Transform args a] -> ShowS #

Eq (Some2 Transform) Source # 
Instance details
Read (Some2 Transform) Source # 
Instance details

Some utilities

transformName :: Transform args a -> String Source #

The concrete syntax names of transformations.

allTransforms :: [Some2 Transform] Source #

All transformations.

Mapping of input type to output type for transforms

Transformation contexts

newtype TransformCtx Source #

The context in which a transformation is called. Currently this is simply the next free variable in the enclosing program, but it could one day be expanded to include more information, e.g., an association of variables to terms in the enclosing program.

Constructors

TransformCtx 

Fields

class HasTransformCtx x where Source #

The class of types which have an associated context

Minimal complete definition

ctxOf

Methods

ctxOf :: x -> TransformCtx Source #

Instances
ABT syn abt => HasTransformCtx (abt xs a) Source # 
Instance details

Methods

ctxOf :: abt xs a -> TransformCtx Source #

HasTransformCtx (Variable a) Source # 
Instance details

unionCtx :: TransformCtx -> TransformCtx -> TransformCtx Source #

The union of two contexts

minimalCtx :: TransformCtx Source #

The smallest possible context, i.e. a default context suitable for use when performing induction on terms which may contain transformations as subterms.

Transformation tables

newtype TransformTable abt m Source #

A functional lookup table which indicates how to expand transformations. The function returns Nothing when the transformation shouldn't be expanded. When it returns Just k, k is passed an SArgs and a TransformCtx.

Constructors

TransformTable 

Fields

lookupTransform' :: Applicative m => TransformTable abt m -> Transform as b -> TransformCtx -> SArgs abt as -> m (Maybe (abt '[] b)) Source #

A variant of lookupTransform which joins the two layers of Maybe.

simpleTable :: Applicative m => (forall as b. Transform as b -> Maybe (TransformCtx -> SArgs abt as -> Maybe (abt '[] b))) -> TransformTable abt m Source #

Builds a simple transformation table, i.e. one which doesn't make use of the monadic context. Such a table is valid in every Applicative context.

unionTable :: TransformTable abt m -> TransformTable abt m -> TransformTable abt m Source #

Take the left-biased union of two transformation tables

someTransformations :: [Some2 Transform] -> TransformTable abt m -> TransformTable abt m Source #

Intersect a transformation table with a list of transformations