prob-fx-0.1.0.2: A library for modular probabilistic modelling
Safe HaskellNone
LanguageHaskell2010

Env

Description

This implements the model environments that users must provide upon running a model; such environments assign traces of values to the "observable variables" (random variables which can be conditioned against) of a model.

Synopsis

Observable variable

data ObsVar (x :: Symbol) where Source #

Containers for observable variables

Constructors

ObsVar :: KnownSymbol x => ObsVar x 

Instances

Instances details
(KnownSymbol x, x ~ x') => IsLabel x (ObsVar x') Source #

Allows the syntax #x to be automatically lifted to the type ObsVar "x".

Instance details

Defined in Env

Methods

fromLabel :: ObsVar x' #

varToStr :: forall x. ObsVar x -> String Source #

Convert an observable variable from a type-level string to a value-level string

Model environment

data Assign x a Source #

Assign or associate a variable x with a value of type a

Constructors

x := a 

Instances

Instances details
FindElem x2 env => FindElem (x2 :: k) ((x' := a2) ': env :: [Assign x1 a1]) Source # 
Instance details

Defined in Env

Methods

findElem :: Idx x2 ((x' := a2) ': env) Source #

FindElem (x2 :: x1) ((x2 := a2) ': env :: [Assign x1 a1]) Source # 
Instance details

Defined in Env

Methods

findElem :: Idx x2 ((x2 := a2) ': env) Source #

(KnownSymbol x, Show a, Show (Env env)) => Show (Env ((x := a) ': env)) Source # 
Instance details

Defined in Env

Methods

showsPrec :: Int -> Env ((x := a) ': env) -> ShowS #

show :: Env ((x := a) ': env) -> String #

showList :: [Env ((x := a) ': env)] -> ShowS #

Show (Env ('[] :: [Assign Symbol Type])) Source # 
Instance details

Defined in Env

Methods

showsPrec :: Int -> Env '[] -> ShowS #

show :: Env '[] -> String #

showList :: [Env '[]] -> ShowS #

FromSTrace ('[] :: [Assign Symbol Type]) Source # 
Instance details

Defined in Trace

Methods

fromSTrace :: STrace -> Env '[] Source #

(UniqueKey x env ~ 'True, KnownSymbol x, Eq a, Member a PrimVal, FromSTrace env) => FromSTrace ((x := a) ': env) Source # 
Instance details

Defined in Trace

Methods

fromSTrace :: STrace -> Env ((x := a) ': env) Source #

data Env (env :: [Assign Symbol *]) where Source #

A model environment assigning traces (lists) of observed values to observable variables i.e. the type Env ((x := a) : env) indicates x is assigned a value of type [a].

Constructors

ENil :: Env '[] 
ECons :: [a] -> Env env -> Env ((x := a) ': env) 

Instances

Instances details
(KnownSymbol x, Show a, Show (Env env)) => Show (Env ((x := a) ': env)) Source # 
Instance details

Defined in Env

Methods

showsPrec :: Int -> Env ((x := a) ': env) -> ShowS #

show :: Env ((x := a) ': env) -> String #

showList :: [Env ((x := a) ': env)] -> ShowS #

Show (Env ('[] :: [Assign Symbol Type])) Source # 
Instance details

Defined in Env

Methods

showsPrec :: Int -> Env '[] -> ShowS #

show :: Env '[] -> String #

showList :: [Env '[]] -> ShowS #

(<:>) :: UniqueKey x env ~ True => Assign (ObsVar x) [a] -> Env env -> Env ((x := a) ': env) infixr 5 Source #

Prepend a variable assignment to a model environment

nil :: Env '[] Source #

Empty model environment

class (FindElem x env, LookupType x env ~ a) => Observable env x a where Source #

Specifies that an environment Env env has an observable variable x whose observed values are of type a

Methods

get :: ObsVar x -> Env env -> [a] Source #

set :: ObsVar x -> [a] -> Env env -> Env env Source #

Instances

Instances details
(FindElem x env, LookupType x env ~ a) => Observable env x a Source # 
Instance details

Defined in Env

Methods

get :: ObsVar x -> Env env -> [a] Source #

set :: ObsVar x -> [a] -> Env env -> Env env Source #

type family Observables env (ks :: [Symbol]) a :: Constraint where ... Source #

For each observable variable x in xs, construct the constraint Observable env x a

Equations

Observables env (x ': xs) a = (Observable env x a, Observables env xs a) 
Observables env '[] a = () 

type family UniqueKey x env where ... Source #

Check whether an observable variable x is unique in model environment env

Equations

UniqueKey x ((x := a) ': env) = False 
UniqueKey x ((x' := a) ': env) = UniqueKey x env 
UniqueKey x '[] = True 

type family LookupType x env where ... Source #

Retrieve the type of an observable variable x from an environment env

Equations

LookupType x ((x := a) ': env) = a 
LookupType x ((x' := a) ': env) = LookupType x env