smcdel-1.3.0: Symbolic Model Checking for Dynamic Epistemic Logic
Safe HaskellSafe-Inferred
LanguageHaskell2010

SMCDEL.Language

Description

This module defines the language of Dynamic Epistemic Logic (DEL). Keeping the syntax definition separate from the semantics allows us to use the same language throughout the whole report, for both the explicit and the symbolic model checkers.

Synopsis

Propositions and Agents

Propositions are represented as integers in Haskell. Agents are strings.

newtype Prp Source #

Constructors

P Int 

Instances

Instances details
Arbitrary Prp Source # 
Instance details

Defined in SMCDEL.Language

Methods

arbitrary :: Gen Prp #

shrink :: Prp -> [Prp] #

Enum Prp Source # 
Instance details

Defined in SMCDEL.Language

Methods

succ :: Prp -> Prp #

pred :: Prp -> Prp #

toEnum :: Int -> Prp #

fromEnum :: Prp -> Int #

enumFrom :: Prp -> [Prp] #

enumFromThen :: Prp -> Prp -> [Prp] #

enumFromTo :: Prp -> Prp -> [Prp] #

enumFromThenTo :: Prp -> Prp -> Prp -> [Prp] #

Show Prp Source # 
Instance details

Defined in SMCDEL.Language

Methods

showsPrec :: Int -> Prp -> ShowS #

show :: Prp -> String #

showList :: [Prp] -> ShowS #

Eq Prp Source # 
Instance details

Defined in SMCDEL.Language

Methods

(==) :: Prp -> Prp -> Bool #

(/=) :: Prp -> Prp -> Bool #

Ord Prp Source # 
Instance details

Defined in SMCDEL.Language

Methods

compare :: Prp -> Prp -> Ordering #

(<) :: Prp -> Prp -> Bool #

(<=) :: Prp -> Prp -> Bool #

(>) :: Prp -> Prp -> Bool #

(>=) :: Prp -> Prp -> Bool #

max :: Prp -> Prp -> Prp #

min :: Prp -> Prp -> Prp #

TexAble Prp Source # 
Instance details

Defined in SMCDEL.Language

TexAble BelScene Source # 
Instance details

Defined in SMCDEL.Symbolic.K

TexAble Event Source # 
Instance details

Defined in SMCDEL.Symbolic.K

TexAble Event Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

TexAble KnowScene Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

TexAble Event Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

TexAble KnowScene Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

HasPrecondition Event Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Methods

preOf :: Event -> Form Source #

HasPrecondition Event Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Methods

preOf :: Event -> Form Source #

HasPrecondition Event Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Methods

preOf :: Event -> Form Source #

HasPrecondition Event Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Methods

preOf :: Event -> Form Source #

Optimizable KnowScene Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Optimizable KnowScene Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Semantics BelScene Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Methods

isTrue :: BelScene -> Form -> Bool Source #

Semantics BelScene Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Methods

isTrue :: BelScene -> Form -> Bool Source #

Semantics KnowScene Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Methods

isTrue :: KnowScene -> Form -> Bool Source #

Semantics KnowScene Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Methods

isTrue :: KnowScene -> Form -> Bool Source #

Pointed BelStruct State Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Pointed Transformer State Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Pointed BelStruct State Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Pointed Transformer State Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Pointed KnowStruct State Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Pointed KnowTransformer State Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Pointed KnowStruct State Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Pointed KnowTransformer State Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Update BelScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Update BelScene Event Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Update BelScene MultipointedEvent Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Update BelScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Update BelScene Event Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Update BelScene MultipointedEvent Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Update KnowScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Update KnowScene Event Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Update KnowScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Update KnowScene Event Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Convertable KnowScene BelScene Source #

Every knowledge structure is also a belief structure. We replace each \(O_i\) with \(\Omega_i := \bigwedge_{p \in O_i} (p \leftrightarrow p')\).

Instance details

Defined in SMCDEL.Translations.Convert

Pointed Transformer [State] Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

TexAble [Prp] Source # 
Instance details

Defined in SMCDEL.Language

Methods

tex :: [Prp] -> String Source #

texTo :: [Prp] -> String -> IO () Source #

texDocumentTo :: [Prp] -> String -> IO () Source #

pdfTo :: [Prp] -> String -> IO () Source #

disp :: [Prp] -> IO () Source #

svgViaTex :: [Prp] -> String Source #

class HasVocab a where Source #

Methods

vocabOf :: a -> [Prp] Source #

Instances

Instances details
HasVocab KripkeModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

Methods

vocabOf :: KripkeModel -> [Prp] Source #

HasVocab KripkeModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

HasVocab BelStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Methods

vocabOf :: BelStruct -> [Prp] Source #

HasVocab BelStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Methods

vocabOf :: BelStruct -> [Prp] Source #

HasVocab KnowStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Methods

vocabOf :: KnowStruct -> [Prp] Source #

HasVocab KnowStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Methods

vocabOf :: KnowStruct -> [Prp] Source #

(HasVocab a, Pointed a b) => HasVocab (a, b) Source # 
Instance details

Defined in SMCDEL.Language

Methods

vocabOf :: (a, b) -> [Prp] Source #

defaultAgents :: [Agent] Source #

Five default agents given by `"1"` to `"5"`.

newtype AgAgent Source #

Constructors

Ag Agent 

Instances

Instances details
Arbitrary AgAgent Source # 
Instance details

Defined in SMCDEL.Language

Show AgAgent Source # 
Instance details

Defined in SMCDEL.Language

Eq AgAgent Source # 
Instance details

Defined in SMCDEL.Language

Methods

(==) :: AgAgent -> AgAgent -> Bool #

(/=) :: AgAgent -> AgAgent -> Bool #

Ord AgAgent Source # 
Instance details

Defined in SMCDEL.Language

newtype Group Source #

Constructors

Group [Agent] 

Instances

Instances details
Arbitrary Group Source # 
Instance details

Defined in SMCDEL.Language

Methods

arbitrary :: Gen Group #

shrink :: Group -> [Group] #

Show Group Source # 
Instance details

Defined in SMCDEL.Language

Methods

showsPrec :: Int -> Group -> ShowS #

show :: Group -> String #

showList :: [Group] -> ShowS #

Eq Group Source # 
Instance details

Defined in SMCDEL.Language

Methods

(==) :: Group -> Group -> Bool #

(/=) :: Group -> Group -> Bool #

Ord Group Source # 
Instance details

Defined in SMCDEL.Language

Methods

compare :: Group -> Group -> Ordering #

(<) :: Group -> Group -> Bool #

(<=) :: Group -> Group -> Bool #

(>) :: Group -> Group -> Bool #

(>=) :: Group -> Group -> Bool #

max :: Group -> Group -> Group #

min :: Group -> Group -> Group #

Formulas

The language \( \mathcal{L}(V) \) for a set of propositions \(V\) and a finite set of agents \(I\) is given by \[ \phi ::= \top \mid \bot \mid p \mid \lnot \phi \mid \bigwedge \Phi \mid \bigvee \Phi \mid \bigoplus \Phi \mid \phi \rightarrow \phi \mid \phi \leftrightarrow \phi \mid \forall P \phi \mid \exists P \phi \mid K_i \phi \mid C_\Delta \phi \mid D_\Delta \phi \mid [!\phi] \phi \mid [\Delta ! \phi] \phi \] where \(p \in V\), \(P \subseteq V\), \(|P|<\omega\), \(\Phi\subseteq\mathcal{L}(V)\), \(|\Phi|<\omega\), \(i \in I\) and \(\Delta \subset I\). We also write \(\phi \land \psi\) for \(\bigwedge \{ \phi,\psi \}\) and \(\phi \lor \psi\) for \(\bigvee \{ \phi,\psi \}\). The emph{boolean} formulas are those without \(K_i\), \(C_\Delta\), \(D_\Delta\), \([!\phi]\) and \([\Delta!\phi]\).

Hence, a formula can be (in this order): The constant top or bottom, an atomic proposition, a negation, a conjunction, a disjunction, an exclusive or, an implication, a bi-implication, a universal or existential quantification over a set of propositions, or a statement about knowledge, common-knowledge, distributed knowledge, a public announcement or an announcement to a group.

Some of these connectives are inter-definable, for example \(\phi\leftrightarrow\psi\) and \(\bigwedge \{ \psi\rightarrow\phi,\phi\rightarrow\psi \}\) are equivalent according to all semantics which we will use here. Hence we could shorten Definition~ref{def-dellang} and treat some connectives as abbreviations. This would lead to brevity and clarity in the formal definitions, but also to a decrease in performance of our model checking implementations. To continue with the first example: If we have Binary Decision Diagrams (BDDs) for \(\phi\) and \(\psi\), computing the BDD for \(\phi\leftrightarrow\psi\) in one operation by calling the appropriate method of a BDD package will be faster than rewriting it to a conjunction of two implications and then making three calls to these corresponding functions of the BDD package.

We extend our language with abbreviations for "knowing whether" and "announcing whether".

\[ K^?_i \phi := \bigvee \{ K_i \phi , K_i (\lnot \phi) \} \]

\[ D^?_i \phi := \bigvee \{ D_i \phi , D_i (\lnot \phi) \} \]

\[ [?! \phi] \psi := \bigwedge \{ \phi \rightarrow [!\phi]\psi , \lnot \phi \rightarrow [!\lnot\phi]\psi \} \]

\[ [I ?! \phi] \psi := \bigwedge \{ \phi \rightarrow [I ! \phi]\psi , \lnot \phi \rightarrow [I !\lnot\phi]\psi \} \]

Note that - also for performance reasons - the three "whether" operators occur as primitives and not as abbreviations.

data Form Source #

Formulas

Constructors

Top

True Constant

Bot

False Constant

PrpF Prp

Atomic Proposition

Neg Form

Negation

Conj [Form]

Conjunction

Disj [Form]

Disjunction

Xor [Form]

n-ary X-OR

Impl Form Form

Implication

Equi Form Form

Bi-Implication

Forall [Prp] Form

Boolean Universal Quantification

Exists [Prp] Form

Boolean Existential Quantification

K Agent Form

Knowing that

Ck [Agent] Form

Common knowing that

Dk [Agent] Form

Distributed knowing that

Kw Agent Form

Knowing whether

Ckw [Agent] Form

Common knowing whether

Dkw [Agent] Form

Distributed knowing whether

PubAnnounce Form Form

Public announcement that

PubAnnounceW Form Form

Public announcement whether

Announce [Agent] Form Form

(Semi-)Private announcement that

AnnounceW [Agent] Form Form

(Semi-)Private announcement whether

Dia DynamicOp Form

Dynamic Diamond

Instances

Instances details
Arbitrary Form Source #

A general Arbitrary instance for formulas. It is used heavily in the automated tests.

Instance details

Defined in SMCDEL.Language

Methods

arbitrary :: Gen Form #

shrink :: Form -> [Form] #

Show Form Source # 
Instance details

Defined in SMCDEL.Language

Methods

showsPrec :: Int -> Form -> ShowS #

show :: Form -> String #

showList :: [Form] -> ShowS #

Eq Form Source # 
Instance details

Defined in SMCDEL.Language

Methods

(==) :: Form -> Form -> Bool #

(/=) :: Form -> Form -> Bool #

Ord Form Source # 
Instance details

Defined in SMCDEL.Language

Methods

compare :: Form -> Form -> Ordering #

(<) :: Form -> Form -> Bool #

(<=) :: Form -> Form -> Bool #

(>) :: Form -> Form -> Bool #

(>=) :: Form -> Form -> Bool #

max :: Form -> Form -> Form #

min :: Form -> Form -> Form #

TexAble Form Source # 
Instance details

Defined in SMCDEL.Language

HasPrecondition Form Source #

Formulas used as public announcements are their own precondition.

Instance details

Defined in SMCDEL.Language

Methods

preOf :: Form -> Form Source #

IsPlan OfflinePlan Source # 
Instance details

Defined in SMCDEL.Other.Planning

Update KripkeModel Form Source # 
Instance details

Defined in SMCDEL.Explicit.K

Update MultipointedModel Form Source # 
Instance details

Defined in SMCDEL.Explicit.K

Update PointedModel Form Source # 
Instance details

Defined in SMCDEL.Explicit.K

Update KripkeModelS5 Form Source #

Public announcements on Kripke models.

Instance details

Defined in SMCDEL.Explicit.S5

Update MultipointedModelS5 Form Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Update PointedModelS5 Form Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Update BelScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Update BelStruct Form Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Update BelScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Update BelStruct Form Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Update KnowScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Update KnowStruct Form Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Update KnowScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Update KnowStruct Form Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

IsPlan (Plan Form) Source # 
Instance details

Defined in SMCDEL.Other.Planning

Methods

reaches :: Plan Form -> Form -> Form Source #

reachesOn :: Semantics o => Plan Form -> Form -> o -> Bool Source #

Abbreviations

ite :: Form -> Form -> Form -> Form Source #

If-Then-Else

pubAnnounceStack :: [Form] -> Form -> Form Source #

Abbreviation for a sequence of announcements using.

booloutofForm :: [Prp] -> [Prp] -> Form Source #

Abbreviation to say that exactly a given subset of a set of propositions is true.

Dynamic Operators

data DynamicOp Source #

Constructors

Dyn !String !Dynamic 

Instances

Instances details
Show DynamicOp Source # 
Instance details

Defined in SMCDEL.Language

Eq DynamicOp Source # 
Instance details

Defined in SMCDEL.Language

Ord DynamicOp Source # 
Instance details

Defined in SMCDEL.Language

box :: DynamicOp -> Form -> Form Source #

The dynamic box operator

Typeclasses for Semantics

class HasAgents a where Source #

Methods

agentsOf :: a -> [Agent] Source #

Instances

Instances details
HasAgents ActionModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

HasAgents KripkeModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

HasAgents ActionModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

HasAgents KripkeModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

HasAgents BelStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.K

HasAgents Transformer Source # 
Instance details

Defined in SMCDEL.Symbolic.K

HasAgents BelStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

HasAgents Transformer Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

HasAgents KnowStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

HasAgents KnowTransformer Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

HasAgents KnowStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

HasAgents KnowTransformer Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

(HasAgents a, Pointed a b) => HasAgents (a, b) Source # 
Instance details

Defined in SMCDEL.Language

Methods

agentsOf :: (a, b) -> [Agent] Source #

class Pointed a b Source #

Instances

Instances details
Pointed ActionModel Action Source # 
Instance details

Defined in SMCDEL.Explicit.K

Pointed KripkeModel World Source # 
Instance details

Defined in SMCDEL.Explicit.K

Pointed ActionModelS5 Action Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Pointed KripkeModelS5 World Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Pointed BelStruct Bdd Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Pointed BelStruct State Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Pointed Transformer Bdd Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Pointed Transformer State Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Pointed BelStruct Bdd Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Pointed BelStruct State Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Pointed Transformer State Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Pointed KnowStruct Bdd Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Pointed KnowStruct State Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Pointed KnowTransformer Bdd Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Pointed KnowTransformer State Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Pointed KnowStruct Bdd Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Pointed KnowStruct State Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Pointed KnowTransformer Bdd Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Pointed KnowTransformer State Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Pointed ActionModel [Action] Source # 
Instance details

Defined in SMCDEL.Explicit.K

Pointed KripkeModel [World] Source # 
Instance details

Defined in SMCDEL.Explicit.K

Pointed ActionModelS5 [Action] Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Pointed KripkeModelS5 [World] Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Pointed Transformer [State] Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

class HasVocab a => Semantics a where Source #

Methods

isTrue :: a -> Form -> Bool Source #

Instances

Instances details
Semantics KripkeModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

Semantics MultipointedModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

Semantics PointedModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

Semantics KripkeModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Semantics MultipointedModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Semantics PointedModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Semantics BelScene Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Methods

isTrue :: BelScene -> Form -> Bool Source #

Semantics BelStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Methods

isTrue :: BelStruct -> Form -> Bool Source #

Semantics MultipointedBelScene Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Semantics BelScene Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Methods

isTrue :: BelScene -> Form -> Bool Source #

Semantics BelStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Methods

isTrue :: BelStruct -> Form -> Bool Source #

Semantics MultipointedBelScene Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Semantics KnowScene Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Methods

isTrue :: KnowScene -> Form -> Bool Source #

Semantics KnowStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Methods

isTrue :: KnowStruct -> Form -> Bool Source #

Semantics MultipointedKnowScene Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Semantics KnowScene Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Methods

isTrue :: KnowScene -> Form -> Bool Source #

Semantics KnowStruct Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Methods

isTrue :: KnowStruct -> Form -> Bool Source #

Semantics MultipointedKnowScene Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

(|=) :: Semantics a => a -> Form -> Bool Source #

The \(\vDash\) symbol for semantics.

Type classes for Updates

class HasPrecondition a where Source #

Methods

preOf :: a -> Form Source #

Instances

Instances details
HasPrecondition ActionModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

HasPrecondition MultipointedActionModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

HasPrecondition PointedActionModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

HasPrecondition ActionModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

HasPrecondition MultipointedActionModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

HasPrecondition PointedActionModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

HasPrecondition Form Source #

Formulas used as public announcements are their own precondition.

Instance details

Defined in SMCDEL.Language

Methods

preOf :: Form -> Form Source #

HasPrecondition Event Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Methods

preOf :: Event -> Form Source #

HasPrecondition MultipointedEvent Source # 
Instance details

Defined in SMCDEL.Symbolic.K

HasPrecondition Transformer Source # 
Instance details

Defined in SMCDEL.Symbolic.K

HasPrecondition Event Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Methods

preOf :: Event -> Form Source #

HasPrecondition MultipointedEvent Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

HasPrecondition Transformer Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

HasPrecondition Event Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Methods

preOf :: Event -> Form Source #

HasPrecondition KnowTransformer Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

HasPrecondition MultipointedEvent Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

HasPrecondition Event Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Methods

preOf :: Event -> Form Source #

HasPrecondition KnowTransformer Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

HasPrecondition MultipointedEvent Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

class (Show a, Show b, HasAgents a, Semantics a, HasPrecondition b) => Update a b where Source #

Minimal complete definition

unsafeUpdate

Methods

unsafeUpdate :: a -> b -> a Source #

checks :: [a -> b -> Bool] Source #

preCheck :: a -> b -> Bool Source #

update :: a -> b -> a Source #

Instances

Instances details
Update KripkeModel ActionModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

Update KripkeModel Form Source # 
Instance details

Defined in SMCDEL.Explicit.K

Update MultipointedModel MultipointedActionModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

Update MultipointedModel PointedActionModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

Update MultipointedModel Form Source # 
Instance details

Defined in SMCDEL.Explicit.K

Update PointedModel MultipointedActionModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

Update PointedModel PointedActionModel Source # 
Instance details

Defined in SMCDEL.Explicit.K

Update PointedModel Form Source # 
Instance details

Defined in SMCDEL.Explicit.K

Update KripkeModelS5 ActionModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Update KripkeModelS5 Form Source #

Public announcements on Kripke models.

Instance details

Defined in SMCDEL.Explicit.S5

Update MultipointedModelS5 MultipointedActionModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Update MultipointedModelS5 PointedActionModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Update MultipointedModelS5 Form Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Update PointedModelS5 MultipointedActionModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Update PointedModelS5 PointedActionModelS5 Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Update PointedModelS5 Form Source # 
Instance details

Defined in SMCDEL.Explicit.S5

Update BelScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Update BelScene Event Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Update BelScene MultipointedEvent Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Update BelStruct Form Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Update BelStruct Transformer Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Update MultipointedBelScene MultipointedEvent Source # 
Instance details

Defined in SMCDEL.Symbolic.K

Update BelScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Update BelScene Event Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Update BelScene MultipointedEvent Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Update BelStruct Form Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Update BelStruct Transformer Source # 
Instance details

Defined in SMCDEL.Symbolic.Ki

Update KnowScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Update KnowScene Event Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Update KnowStruct Form Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Update KnowStruct KnowTransformer Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Update MultipointedKnowScene MultipointedEvent Source # 
Instance details

Defined in SMCDEL.Symbolic.S5

Update KnowScene Form Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Update KnowScene Event Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Update KnowStruct Form Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Update KnowStruct KnowTransformer Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

Update MultipointedKnowScene MultipointedEvent Source # 
Instance details

Defined in SMCDEL.Symbolic.S5_DD

updates :: Update a b => a -> [b] -> a Source #

Execute a list of updates, return the final resulting state.

updateSequence :: Update a b => a -> [b] -> [a] Source #

Execute a list of updates, return the list of starting, intermediate and final result states.

haveSameAgents :: (HasAgents a, HasAgents b) => a -> b -> Bool Source #

Check that two modelsactionsetc. have the same agents.

Pretty-printing

showSet :: Show a => [a] -> String Source #

ppForm :: Form -> String Source #

Pretty-print a formula.

ppFormWith :: (Prp -> String) -> Form -> String Source #

Pretty-print a formula with a translation for atomic propositions.

texForm :: Form -> String Source #

Generates LaTeX code for a formula.

Subformulas and Shrinking

subformulas :: Form -> [Form] Source #

List of subformulas, including the given formula itself. In particular this is used in the shrink function for QuickCheck.

Substitution

substit :: Prp -> Form -> Form -> Form Source #

Substitute a formula for a proposition in a formula. As a safety measure this method will fail whenever the proposition to be replaced occurs in a quantifier. All other cases are done by recursion.

substitSet :: [(Prp, Form)] -> Form -> Form Source #

Apply multiple substitutions after each other. Note: in general this is *not* the same as simultaneous substitution. It is equivalent to simultaneous substitution if none of the replaced propositions occurs in the replacement formulas.

substitOutOf :: [Prp] -> [Prp] -> Form -> Form Source #

The "out of" substitution \([A \sqsubseteq B]\phi\).

replPsInP :: [(Prp, Prp)] -> Prp -> Prp Source #

replPsInF :: [(Prp, Prp)] -> Form -> Form Source #

Replace propositions in a formula. In contrast to the previous substitution function this *is* simultaneous.

Vocabulary of a formula

propsInForm :: Form -> [Prp] Source #

List of all propositions occurring in a formula.

agentsInForm :: Form -> [Agent] Source #

List of all agents occurring in a formula.

Simplification

simplify :: Form -> Form Source #

Simplify a formula using boolean equivalences. For example, remove double negations and ``bubble up'' \(\bot\) and \(\top\) in conjunctions and disjunctions, respectively.

Example for simplify

Expand

Consider this rather unnatural formula:

>>> let testForm = Forall [P 3] $ Equi (Disj [ Bot, PrpF $ P 3, Bot ]) (Conj [ Top , Xor [Top,Kw alice (PrpF (P 4))] , AnnounceW [alice,bob] (PrpF (P 5)) (Kw bob $ PrpF (P 5)) ])
>>> testForm
Forall [P 3] (Equi (Disj [Bot,PrpF (P 3),Bot]) (Conj [Top,Xor [Top,Kw "Alice" (PrpF (P 4))],AnnounceW ["Alice","Bob"] (PrpF (P 5)) (Kw "Bob" (PrpF (P 5)))]))
>>> simplify testForm
Forall [P 3] (Equi (PrpF (P 3)) (Conj [Xor [Top,Kw "Alice" (PrpF (P 4))],AnnounceW ["Alice","Bob"] (PrpF (P 5)) (Kw "Bob" (PrpF (P 5)))]))

Generating random formulas

newtype BF Source #

Boolean Formulas

Constructors

BF Form 

Instances

Instances details
Arbitrary BF Source # 
Instance details

Defined in SMCDEL.Language

Methods

arbitrary :: Gen BF #

shrink :: BF -> [BF] #

Show BF Source # 
Instance details

Defined in SMCDEL.Language

Methods

showsPrec :: Int -> BF -> ShowS #

show :: BF -> String #

showList :: [BF] -> ShowS #

Eq BF Source # 
Instance details

Defined in SMCDEL.Language

Methods

(==) :: BF -> BF -> Bool #

(/=) :: BF -> BF -> Bool #

Ord BF Source # 
Instance details

Defined in SMCDEL.Language

Methods

compare :: BF -> BF -> Ordering #

(<) :: BF -> BF -> Bool #

(<=) :: BF -> BF -> Bool #

(>) :: BF -> BF -> Bool #

(>=) :: BF -> BF -> Bool #

max :: BF -> BF -> BF #

min :: BF -> BF -> BF #