Nomyx-Rules-0.1.0: Language to express rules for Nomic

Safe HaskellNone

Language.Nomyx.Rule

Contents

Description

All the building blocks to build rules and basic rules examples.

Synopsis

Variables

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

variable creation

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

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

variable reading

readVar_ :: forall a. (Typeable a, Show a, Eq a) => V a -> Exp aSource

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

variable writing

writeVar_ :: (Typeable a, Show a, Eq a) => V a -> a -> Exp ()Source

modifyVar :: (Typeable a, Show a, Eq a) => V a -> (a -> a) -> Exp ()Source

modify a variable using the provided function

delVar :: V a -> Exp BoolSource

delete variable

delVar_ :: V a -> Exp ()Source

Variable arrays

data ArrayVar i a Source

ArrayVar is an indexed array with a signal attached to warn when the array is filled. each indexed elements starts empty (value=Nothing), and when the array is full, the signal is triggered. This is useful to wait for a serie of events to happen, and trigger a computation on the collected results.

Constructors

ArrayVar (Event (Message [(i, a)])) (V (Map i (Maybe a))) 

newArrayVar :: (Ord i, Typeable a, Show a, Eq a, Typeable i, Show i) => VarName -> [i] -> Exp (ArrayVar i a)Source

initialize an empty ArrayVar

newArrayVar' :: (Ord i, Typeable a, Show a, Eq a, Typeable i, Show i) => VarName -> [i] -> ([(i, a)] -> Exp ()) -> Exp (ArrayVar i a)Source

initialize an empty ArrayVar, registering a callback that will be triggered when the array is filled

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

initialize an empty ArrayVar, registering a callback. the callback will be triggered when the array is filled, and then the ArrayVar will be deleted

putArrayVar :: (Ord i, Typeable a, Show a, Eq a, Typeable i, Show i) => ArrayVar i a -> i -> a -> Exp ()Source

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

getArrayVarMessage :: (Ord i, Typeable a, Show a, Eq a, Typeable i, Show i) => ArrayVar i a -> Exp (Event (Message [(i, a)]))Source

get the messsage triggered when the array is filled

getArrayVarData :: (Ord i, Typeable a, Show a, Eq a, Typeable i, Show i) => ArrayVar i a -> Exp [(i, Maybe a)]Source

get the association array

getArrayVarData' :: (Ord i, Typeable a, Show a, Eq a, Typeable i, Show i) => ArrayVar i a -> Exp [(i, a)]Source

get the association array with only the filled values

delArrayVar :: (Ord i, Typeable a, Show a, Eq a, Typeable i, Show i) => ArrayVar i a -> Exp ()Source

Events

onEvent :: (Typeable e, Show e, Eq e) => Event e -> ((EventNumber, EventData e) -> Exp ()) -> Exp EventNumberSource

register a callback on an event

onEvent_ :: forall e. (Typeable e, Show e, Eq e) => Event e -> (EventData e -> Exp ()) -> Exp ()Source

register a callback on an event, disregard the event number

onEventOnce :: (Typeable e, Show e, Eq e) => Event e -> (EventData e -> Exp ()) -> Exp EventNumberSource

set an handler for an event that will be triggered only once

onEventOnce_ :: (Typeable e, Show e, Eq e) => Event e -> (EventData e -> Exp ()) -> Exp ()Source

set an handler for an event that will be triggered only once

delAllEvents :: (Typeable e, Show e, Eq e) => Event e -> Exp ()Source

sendMessage :: (Typeable a, Show a, Eq a) => Event (Message a) -> a -> Exp ()Source

broadcast a message that can be catched by another rule

onMessage :: (Typeable m, Show m) => Event (Message m) -> (EventData (Message m) -> Exp ()) -> Exp ()Source

subscribe on a message

onMessageOnce :: (Typeable m, Show m) => Event (Message m) -> (EventData (Message m) -> Exp ()) -> Exp ()Source

schedule :: Schedule Freq -> (UTCTime -> Exp ()) -> Exp ()Source

on the provided schedule, the supplied function will be called

schedule' :: [UTCTime] -> (UTCTime -> Exp ()) -> Exp ()Source

schedule'_ :: [UTCTime] -> Exp () -> Exp ()Source

Rule management

activateRule :: RuleNumber -> Exp BoolSource

activate a rule: change its state to Active and execute it

rejectRule :: RuleNumber -> Exp BoolSource

reject a rule: change its state to Suppressed and suppresses all its environment (events, variables, inputs) the rule can be activated again later

addRule :: Rule -> Exp BoolSource

add a rule to the game, it will have to be activated

Inputs

inputChoice :: (Eq c, Show c) => PlayerNumber -> String -> [c] -> c -> Event (InputChoice c)Source

inputChoiceEnum :: forall c. (Enum c, Bounded c, Typeable c, Eq c, Show c) => PlayerNumber -> String -> c -> Event (InputChoice c)Source

onInputChoice :: (Typeable a, Eq a, Show a) => String -> [a] -> (EventNumber -> a -> Exp ()) -> PlayerNumber -> Exp EventNumberSource

triggers a choice input to the user. The result will be sent to the callback

onInputChoice_ :: (Typeable a, Eq a, Show a) => String -> [a] -> (a -> Exp ()) -> PlayerNumber -> Exp ()Source

the same, disregard the event number

onInputChoiceOnce :: (Typeable a, Eq a, Show a) => String -> [a] -> (a -> Exp ()) -> PlayerNumber -> Exp EventNumberSource

the same, suppress the event after first trigger

onInputChoiceOnce_ :: (Typeable a, Eq a, Show a) => String -> [a] -> (a -> Exp ()) -> PlayerNumber -> Exp ()Source

the same, disregard the event number

onInputChoiceEnum :: forall a. (Enum a, Bounded a, Typeable a, Eq a, Show a) => String -> a -> (EventNumber -> a -> Exp ()) -> PlayerNumber -> Exp EventNumberSource

triggers a choice input to the user, using an enumerate as input

onInputChoiceEnum_ :: forall a. (Enum a, Bounded a, Typeable a, Eq a, Show a) => String -> a -> (a -> Exp ()) -> PlayerNumber -> Exp ()Source

the same, disregard the event number

onInputChoiceEnumOnce_ :: forall a. (Enum a, Bounded a, Typeable a, Eq a, Show a) => String -> a -> (a -> Exp ()) -> PlayerNumber -> Exp ()Source

the same, suppress the event after first trigger

onInputString :: String -> (EventNumber -> String -> Exp ()) -> PlayerNumber -> Exp EventNumberSource

triggers a string input to the user. The result will be sent to the callback

onInputString_ :: String -> (String -> Exp ()) -> PlayerNumber -> Exp ()Source

asks the player pn to answer a question, and feed the callback with this data.

onInputStringOnce_ :: String -> (String -> Exp ()) -> PlayerNumber -> Exp ()Source

asks the player pn to answer a question, and feed the callback with this data.

Victory, players, output, time and self-number

setVictory :: [PlayerNumber] -> Exp ()Source

set victory to a list of players

giveVictory :: PlayerNumber -> Exp ()Source

give victory to one player

getPlayersNumber :: Exp IntSource

Get the total number of players

output :: String -> PlayerNumber -> Exp ()Source

outputs a message to one player

getSelfRuleNumber :: Exp RuleNumberSource

allows a rule to retrieve its self number (for auto-deleting for example)

Rule samples

autoActivate :: RuleFuncSource

This rule will activate automatically any new rule.

immutableRule :: RuleNumber -> RuleFuncSource

This rule will forbid any new rule to delete the rule in parameter

legal :: RuleFuncSource

A rule will be always legal

illegal :: RuleFuncSource

A rule will be always illegal

simpleApplicationRule :: RuleFuncSource

This rule establishes a list of criteria rules that will be used to test any incoming rule the rules applyed shall give the answer immediatly

checkWithMetarules :: Rule -> Exp RuleResponseSource

active metarules are automatically used to evaluate a given rule

onRuleProposed :: (Rule -> Exp RuleResponse) -> RuleFuncSource

any new rule will be activate if all active meta rules returns True

voteWith :: ([(PlayerNumber, ForAgainst)] -> Bool) -> Rule -> Exp RuleResponseSource

rule that performs a vote for a rule on all players. The provided function is used to count the votes.

unanimity :: [(PlayerNumber, ForAgainst)] -> BoolSource

assess the vote results according to a unanimity

majority :: [(PlayerNumber, ForAgainst)] -> BoolSource

assess the vote results according to an absolute majority (half participants plus one)

voteWithTimeLimit :: ([(PlayerNumber, ForAgainst)] -> Bool) -> UTCTime -> RuleFuncSource

rule that performs a vote for a rule on all players. The provided function is used to count the votes, it will be called when every players has voted or when the time limit is reached

forEachPlayer :: (PlayerNumber -> Exp ()) -> (PlayerNumber -> Exp ()) -> (PlayerNumber -> Exp ()) -> Exp ()Source

perform an action for each current players, new players and leaving players

forEachPlayer_ :: (PlayerNumber -> Exp ()) -> Exp ()Source

perform the same action for each players, including new players

forEachPlayer' :: (PlayerNumber -> Exp a) -> ((PlayerNumber, a) -> Exp ()) -> Exp ()Source

createValueForEachPlayer :: Int -> V [(Int, Int)] -> Exp ()Source

create a value initialized for each players manages players joining and leaving

createValueForEachPlayer_ :: V [(Int, Int)] -> Exp ()Source

create a value initialized for each players initialized to zero manages players joining and leaving

modifyAllValues :: V [(Int, Int)] -> (Int -> Int) -> Exp ()Source

noPlayPlayer :: PlayerNumber -> RuleFuncSource

Player p cannot propose anymore rules

autoDelete :: Exp ()Source

a rule can autodelete itself (generaly after having performed some actions)

eraseAllRules :: PlayerNumber -> Exp BoolSource

All rules from player p are erased:

Miscellaneous

mapMaybeM :: Monad m => (a -> m (Maybe b)) -> [a] -> m [b]Source

sndMaybe :: (a, Maybe b) -> Maybe (a, b)Source

defaultRule :: RuleSource

a default rule