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

Safe HaskellNone

Language.Nomyx.Expression

Contents

Description

This module containt the type definitions necessary to build a Nomic rule.

Synopsis

Documentation

Expression

data Exp a whereSource

an Exp allows the player's rule to have access to the state of the game. | it is a compositional algebra defined with a GADT.

Constructors

NewVar :: (Typeable a, Show a, Eq a) => VarName -> a -> Exp (Maybe (V a)) 
DelVar :: V a -> Exp Bool 
ReadVar :: (Typeable a, Show a, Eq a) => V a -> Exp (Maybe a) 
WriteVar :: (Typeable a, Show a, Eq a) => V a -> a -> Exp Bool 
OnEvent :: (Typeable e, Show e, Eq e) => Event e -> ((EventNumber, EventData e) -> Exp ()) -> Exp EventNumber 
DelEvent :: EventNumber -> Exp Bool 
DelAllEvents :: (Typeable e, Show e, Eq e) => Event e -> Exp () 
SendMessage :: (Typeable a, Show a, Eq a) => Event (Message a) -> a -> Exp () 
Output :: PlayerNumber -> String -> Exp () 
ProposeRule :: Rule -> Exp Bool 
ActivateRule :: RuleNumber -> Exp Bool 
RejectRule :: RuleNumber -> Exp Bool 
AddRule :: Rule -> Exp Bool 
DelRule :: RuleNumber -> Exp Bool 
ModifyRule :: RuleNumber -> Rule -> Exp Bool 
GetRules :: Exp [Rule] 
SetVictory :: [PlayerNumber] -> Exp () 
GetPlayers :: Exp [PlayerInfo] 
Const :: a -> Exp a 
Bind :: Exp a -> (a -> Exp b) -> Exp b 
CurrentTime :: Exp UTCTime 
SelfRuleNumber :: Exp RuleNumber 

Variables

data V a Source

a container for a variable name and type

Constructors

V 

Fields

varName :: String
 

Instances

data Var Source

stores the variable's data

Constructors

forall a . (Typeable a, Show a, Eq a) => Var 

Fields

vRuleNumber :: Int
 
vName :: String
 
vData :: a
 

Instances

Events

data Player Source

events types

Constructors

Arrive 
Leave 

data Time Source

Instances

data Message m Source

Instances

data Event a whereSource

events names

Instances

Typeable1 Event 
Eq e => Eq (Event e) 
Show a => Show (Event a) 

data EventData a whereSource

data associated with each events

Instances

Rule

type OneParamRule a = a -> Exp RuleResponseSource

type of rule to assess the legality of a given parameter

type NoParamRule = Exp ()Source

type of rule that just mofify the game state

data RuleResponse Source

a rule can assess the legality either immediatly of later through a messsage

Constructors

BoolResp 

Fields

boolResp :: Bool
 
MsgResp 

Fields

msgResp :: Event (Message Bool)
 

data RuleFunc Source

the different types of rules

data Rule Source

An informationnal structure about a rule:

data RuleStatus Source

the status of a rule.

Constructors

Active 
Pending 
Reject 

Player

data PlayerInfo Source

informations on players

Game

data Game Source

The state of the game:

(===) :: (Typeable a, Typeable b, Eq b) => a -> b -> BoolSource

an equality that tests also the types.

replaceWithSource

Arguments

:: (a -> Bool)

Value to search

-> a

Value to replace it with

-> [a]

Input list

-> [a]

Output list

Replaces all instances of a value in a list by another value.