scyther-proof-0.3.0: Automatic generation of Isabelle/HOL correctness proofs for security protocols.

Scyther.Equalities

Contents

Synopsis

Single Equalities

type TIDEq = (TID, TID)Source

Equalities over thread identifers.

Logically these are equalities between logical thread identifier variables.

type TIDRoleEq = (TID, Role)Source

A thread to role assignment.

type RoleEq = (Role, Role)Source

The role equalities serve a double function:

type AVarEq = (AVar, AVar)Source

Equalities between different agent variables.

We do not have to reason about equalities between an agent variable and some other message because our semantics guarantees that agent variables are only instantiated with agent names. Hence, they can only be equal to other agent variables or message variables. In the latter case, we store the equality the other way round; assigning the agent variable to the message variable.

type MVarEq = (MVar, Message)Source

Equalities between message variables and arbitrary messages.

type MsgEq = (Message, Message)Source

Equalities between messages.

agentEqToMsgEq :: AgentEq -> MsgEqSource

Convert an agent equality to a message equality.

mvarEqToMsgEq :: MVarEq -> MsgEqSource

Convert a message variable equallity to a message equality.

Compound Equalities

data Equalities Source

A conjunction of equality facts.

Invariants for a value eqs = Equalities tideqs roleeqs avareqs mvareqs agnteqs:

  1. Domain and range normalized with respect to equalities. Note that this implies substitution must always consider TID substitution first.

forall tid : ran(tideqs). substTID eqs tid = tid forall tid : dom(roleeqs). substTID eqs tid = tid forall (lid, lid') : avareqs. substLocalId eqs lid = lid & substAVar eqs lid' = lid' forall (lid, m) : mvareqs. substLocalId eqs lid = lid & substMsg eqs m = m

TODO: Complete properties for Agent ID's

forall aid : dom(agnteqs). substAgentId eqs aid = Just (Left aid) forall : dom(agnteqs). substAgentId eqs aid = Just (Left aid)

  1. Origin always greater than image for symmetric eqs.

forall (tid, tid') : tideqs. tid > tid' forall (lid, lid') : avareqs. lid > lid'

  1. Range of message variable equalities normalized with respect to key inversion.

forall m : ran(mvareqs). normMsg m = m

  1. All thread identifiers are in the domain of roleeqs.
  2. All agent identifiers are in the domain of agnteqs.
  3. No cycles.

Construction

empty :: EqualitiesSource

Empty equality premises.

solve :: Monad m => [AnyEq] -> Equalities -> m EqualitiesSource

Solve a list of unification equations.

The unification is performed modulo key inversion and thread identifier equalities. Additional thread identifier equalities may result from equalities over fresh messages. Bidirectional keys are handled by delaying their solution until only one solution is possible.

trimTIDEqsSource

Arguments

:: Equalities 
-> ([TID], Equalities)

Dropped TIDs plus updated equalities

Remove the thread identifier equalities. This is logically safe iff there is no fact outside the equalities that still refers to the dropped thread identifiers.

trimAgentEqsSource

Arguments

:: Equalities 
-> ([AgentId], Equalities)

Dropped AgentIds plus updated equalities

Remove the agent identifiers equalities. This is logically safe iff there is no fact outside the equalities that still refers to the dropped agent identifiers.

Destruction

getTIDEqs :: Equalities -> [TIDEq]Source

The list of thread identifier equalities.

getTIDRoleEqs :: Equalities -> [TIDRoleEq]Source

The list of role equalities.

getAgentEqs :: Equalities -> [AgentEq]Source

The list of agent variable equalities.

getAVarEqs :: Equalities -> [AVarEq]Source

The list of agent variable equalities.

getMVarEqs :: Equalities -> [MVarEq]Source

The list of message variable equalities.

getPostEqs :: Equalities -> [MsgEq]Source

The list of postponed message equalities.

toAnyEqs :: Equalities -> [AnyEq]Source

Convert a set of equalities to a list of equalities.

POST: Order of equalities equal to order in result of toLists.

anyEqTIDs :: AnyEq -> [TID]Source

The threads occurring in an equality.

Substitution

substTID :: Equalities -> TID -> TIDSource

Substitute a thread identifier according to thread identifier equalities.

substLocalId :: Equalities -> LocalId -> LocalIdSource

Substitute a local identifier according to thread identifier equalities.

substAVar :: Equalities -> AVar -> AVarSource

Substitute a local identifier belonging to an agent variable.

substMVar :: Equalities -> MVar -> MessageSource

Substitute a local identifier belonging to a message variable.

substAgentId :: Equalities -> AgentId -> AgentEqRHSSource

Substitute an agent id representing an arbitrary agent name.

substAgentEqRHS :: Equalities -> AgentEqRHS -> AgentEqRHSSource

Substitute the right-hand-side of an agent id equality.

substMsg :: Equalities -> Message -> MessageSource

Substitute message constituents according to equalities.

POST: Message normalized w.r.t. normMsg.

substAnyEq :: Equalities -> AnyEq -> AnyEqSource

Substitute both sides of a representable equality.

Additional Queries

threadRole :: TID -> Equalities -> Maybe RoleSource

Retrieve the role of a thread.

maxMappedTID :: Equalities -> Maybe TIDSource

The maximal mapped thread identifier.

maxMappedAgentId :: Equalities -> Maybe AgentIdSource

The maximal mapped agent identifier.

reflexive :: AnyEq -> BoolSource

Check if an equality is reflexive.

null :: Equalities -> BoolSource

True if no equalities are present.

Mapping Logical Variables

emptyMapping :: MappingSource

An empty mapping.

mkMapping :: Map TID TID -> Map AgentId AgentId -> MappingSource

A mapping of logical variables and the corresponding substitution can be represented as an abstract Equalities value. However, it violates the invariant that the domain of the equalities must be invariant under substitution. This is OK, as domain and range of a mapping are from different logical contexts.

addTIDMapping :: TID -> TID -> Mapping -> MappingSource

Add a mapping from one thread identifier to another one, possibly overriding an existing mapping.

addAgentIdMapping :: AgentId -> AgentId -> Mapping -> MappingSource

Add a mapping from one thread identifier to another one, possibly overriding an existing mapping.

addTIDRoleMapping :: TID -> Role -> Mapping -> MappingSource

Add a mapping from one thread identifier to an other role, possibly overriding an existing mapping.

deleteTIDMapping :: TID -> Mapping -> MappingSource

Delete the mapping of the given thread identifier.

deleteAgentIdMapping :: AgentId -> Mapping -> MappingSource

Delete the mapping of the given agent identifier.

Pretty Printing