Nomyx-Language-0.6.1: Language to express rules for Nomic

Safe HaskellNone

Language.Nomyx.Variables

Description

All the building blocks to allow rules to build variables. for example, you can create a variable with: do newMsgVar_ MyMoney (0::Int)

Synopsis

Documentation

data V a Source

a container for a variable name and type

Constructors

V 

Fields

varName :: String
 

Instances

data VEvent a Source

a MsgVar is a variable with a message attached, allowing to trigger registered functions anytime the var if modified

Constructors

VUpdated a 
VDeleted 

Instances

Typeable1 VEvent 
Eq a => Eq (VEvent a) 
Show a => Show (VEvent a) 

data MsgVar a Source

Constructors

MsgVar 

Fields

message :: Msg (VEvent a)
 
variable :: V a
 

newVar :: (Typeable a, Show a) => VarName -> a -> Nomex (Maybe (V a))Source

variable creation

newVar_ :: (Typeable a, Show a) => VarName -> a -> Nomex (V a)Source

newVar' :: (Typeable a, Show a) => V a -> a -> Nomex BoolSource

readVar :: (Typeable a, Show a) => V a -> NomexNE (Maybe a)Source

variable reading

readVar_ :: (Typeable a, Show a) => V a -> Nomex aSource

writeVar :: (Typeable a, Show a) => V a -> a -> Nomex BoolSource

variable writing

modifyVar :: (Typeable a, Show a) => V a -> (a -> a) -> Nomex BoolSource

modify a variable using the provided function

delVar :: V a -> Nomex BoolSource

delete variable

modifyMsgVar :: (Typeable a, Show a) => MsgVar a -> (a -> a) -> Nomex BoolSource

newMsgVarOnEvent :: (Typeable a, Show a, Eq a) => VarName -> a -> (VEvent a -> Nomex ()) -> Nomex (Maybe (MsgVar a))Source

create a new MsgVar and register callback in case of change (update, delete)

onMsgVarChangeSource

Arguments

:: (Typeable a, Show a, Eq a) 
=> MsgVar a

the MsgVar

-> (a -> Nomex b)

callback on creation (called immediatly)

-> (a -> b -> Nomex ())

callback on update

-> (b -> Nomex ())

callback on delete

-> Nomex EventNumber

event number generated for update and delete

adds a callback for each of the MsgVar events: Create, Update, Delete

getMsgVarMessage :: (Typeable a, Show a) => MsgVar a -> NomexNE (Msg (VEvent a))Source

get the messsage triggered when the array is filled

getMsgVarData :: (Typeable a, Show a) => MsgVar a -> NomexNE (Maybe a)Source

get the association array

type ArrayVar i a = MsgVar [(i, Maybe a)]Source

ArrayVar is an indexed array with a signal attached triggered at every change. | each indexed elements starts empty (value=Nothing).

newArrayVar :: (Typeable a, Show a, Typeable i, Show i) => VarName -> [i] -> Nomex (Maybe (ArrayVar i a))Source

initialize an empty ArrayVar

newArrayVar_ :: (Typeable a, Show a, Typeable i, Show i) => VarName -> [i] -> Nomex (ArrayVar i a)Source

newArrayVar' :: (Typeable a, Show a, Eq a, Typeable i, Show i, Eq i) => VarName -> [i] -> (VEvent [(i, Maybe a)] -> Nomex ()) -> Nomex (Maybe (ArrayVar i a))Source

initialize an empty ArrayVar, registering a callback that will be triggered at every change

newArrayVarOnce :: (Typeable a, Show a, Eq a, Typeable i, Show i, Ord i) => VarName -> [i] -> (VEvent [(i, Maybe a)] -> Nomex ()) -> Nomex (Maybe (ArrayVar i a))Source

initialize an empty ArrayVar, registering a callback. the ArrayVar will be deleted when full

cleanOnFull :: (Typeable a, Show a, Eq a, Typeable i, Show i, Ord i) => ArrayVar i a -> Nomex ()Source

putArrayVar :: (Typeable a, Show a, Eq a, Typeable i, Show i, Eq i, Ord i) => ArrayVar i a -> i -> a -> Nomex BoolSource

store one value and the given index. If this is the last filled element, the registered callbacks are triggered.

putArrayVar_ :: (Typeable a, Show a, Eq a, Typeable i, Show i, Ord i) => ArrayVar i a -> i -> a -> Nomex ()Source