tamarin-prover-term-0.8.5.1: Term manipulation library for the tamarin prover.

MaintainerBenedikt Schmidt <beschmi@gmail.com>
Safe HaskellNone

Term.Substitution

Contents

Description

Standard and fresh substitutions.

Synopsis

Composition of fresh and free substitutions

composeVFresh :: (IsConst c, Show (Lit c LVar)) => LSubstVFresh c -> LSubst c -> LSubstVFresh cSource

composeVFresh s1 s2 composes the fresh substitution s1 and the free substitution s2. The result is the fresh substitution s = s1.s2.

Conversion between fresh and free

freshToFree :: (MonadFresh m, IsConst c) => SubstVFresh c LVar -> m (Subst c LVar)Source

freshToFree s converts the bound variables in s to free variables using fresh variable names. We try to preserve variables names if possible.

freshToFreeAvoiding :: (HasFrees t, IsConst c) => SubstVFresh c LVar -> t -> Subst c LVarSource

freshToFreeAvoiding s t converts all fresh variables in the range of s to free variables avoiding free variables in t. This function tries to reuse variable names from the domain of the substitution if possible.

freshToFreeAvoidingFast :: (HasFrees t, Ord c) => LSubstVFresh c -> t -> LSubst cSource

freshToFreeAvoidingFast s t converts all fresh variables in the range of s to free variables avoiding free variables in t. This function does not try to reuse variable names from the domain of the substitution.

freeToFreshRaw :: Subst c LVar -> SubstVFresh c LVarSource

freeToFreshRaw s considers all variables in the range of s as fresh.

Convenience exports

module Term.LTerm

General Substitutions

newtype Subst c v Source

We use the data type Subst c v of substitutions. c is the type of constants and v the type of variables.

Constructors

Subst 

Fields

sMap :: Map v (VTerm c v)
 

Instances

Ord c => HasFrees (LSubst c) 
(Eq c, Eq v) => Eq (Subst c v) 
(Ord c, Ord v) => Ord (Subst c v) 
(Show v, Show c) => Show (Subst c v) 
(Binary c, Binary v) => Binary (Subst c v) 
(NFData c, NFData v) => NFData (Subst c v) 
Sized (Subst c v) 

application of substitutions

applyVTerm :: (IsConst c, IsVar v, Ord c) => Subst c v -> VTerm c v -> VTerm c vSource

applyVTerm subst t applies the substitution subst to the term t.

applyLit :: IsVar v => Subst c v -> Lit c v -> VTerm c vSource

applyLit subst l applies the substitution subst to the literal l.

smart constructors for substitutions

substFromList :: IsVar v => [(v, VTerm c v)] -> Subst c vSource

Convert a list to a substitution. The x/x mappings are removed.

substFromMap :: IsVar v => Map v (VTerm c v) -> Subst c vSource

Convert a map to a substitution. The x/x mappings are removed. FIXME: implement directly, use substFromMap for substFromList.

emptySubst :: Subst c vSource

emptySubVFree is the substitution with empty domain.

Composition of substitutions

compose :: (IsConst c, IsVar v) => Subst c v -> Subst c v -> Subst c vSource

compose s1 s2 composes the substitutions s1 and s2. The result is s1.s2, i.e., it has the same effect as (t s2) s1 = s1(s2(t)) when applied to a term t.

applySubst :: (IsConst c, IsVar v) => Subst c v -> Subst c v -> Subst c vSource

applySubst subst subst' applies the substitution subst to the range of the substitution subst'.

operations

restrict :: IsVar v => [v] -> Subst c v -> Subst c vSource

restrict vars subst restricts the domain of the substitution subst to vars.

mapRange :: (IsConst c, IsVar v, IsConst c2) => (VTerm c v -> VTerm c2 v) -> Subst c v -> Subst c2 vSource

mapRange f subst maps the function f over the range of the substitution subst.

queries

varsRange :: IsVar v => Subst c v -> [v]Source

varsRange subst returns all variables in the range of the substitution.

dom :: Subst c v -> [v]Source

dom subst returns the domain of the substitution substs.

range :: Subst c v -> [VTerm c v]Source

range subst returns the range of the substitution substs.

imageOf :: IsVar v => Subst c v -> v -> Maybe (VTerm c v)Source

Returns the image of i under subst if i is in the domain of subst.

views

substToListOn :: (IsConst c, IsVar v) => [v] -> Subst c v -> [VTerm c v]Source

substToPairOn vs sigma converts the list of variables [x1,..,xk] to [sigma(x1),..,sigma(xk)].

substToList :: Subst c v -> [(v, VTerm c v)]Source

Convert substitution to list.

Apply class

class Apply t whereSource

Types that support the application of LSubsts.

Methods

apply :: LNSubst -> t -> tSource

Instances

Apply Bool 
Apply Char 
Apply Int 
Apply () 
Apply BLTerm 
Apply BLVar 
Apply LNTerm 
Apply LVar 
Apply a => Apply [a] 
Apply a => Apply (Maybe a) 
(Ord a, Apply a) => Apply (Set a) 
Apply a => Apply (Conj a) 
Apply a => Apply (Disj a) 
Apply t => Apply (Equal t) 
(Apply a, Apply b) => Apply (Either a b) 
(Apply a, Apply b) => Apply (a, b) 

Pretty printing

prettySubst :: (Ord c, Ord v, HighlightDocument d, Show c, Show v) => (v -> d) -> (Lit c v -> d) -> Subst c v -> [d]Source

Pretty print a substitution.

Substitution of LVars

type LSubst c = Subst c LVarSource

A substitution for logical variables.

type LNSubst = Subst Name LVarSource

A substitution with names and logical variables.

prettyLNSubst :: (Show (Lit c LVar), Ord c, HighlightDocument d, Show c) => LSubst c -> dSource

Pretty print a substitution with logical variables.

General Substitutions

newtype SubstVFresh c v Source

We use the data type SubstVFresh c v of substitutions. c denotes the type of constants and v the type of variables. Fresh substitutions cannot be applied directly, they have to be converted to free substitutions in a certain context (MonadFresh).

Constructors

SubstVFresh 

Fields

svMap :: Map v (VTerm c v)
 

Instances

(Eq c, Eq v) => Eq (SubstVFresh c v) 
(Ord c, Ord v) => Ord (SubstVFresh c v) 
(Show c, Show v) => Show (SubstVFresh c v) 
(Binary c, Binary v) => Binary (SubstVFresh c v) 
(NFData c, NFData v) => NFData (SubstVFresh c v) 
Sized (SubstVFresh c v) 
HasFrees (SubstVFresh n LVar) 

smart constructors for substitutions

substFromListVFresh :: IsVar v => [(v, VTerm c v)] -> SubstVFresh c vSource

Convert a list of mappings to a fresh substitution.

emptySubstVFresh :: SubstVFresh c vSource

emptySubstVFresh is the fresh substitution with empty domain.

operations

restrictVFresh :: IsVar v => [v] -> SubstVFresh c v -> SubstVFresh c vSource

restrictVFresh vars subst restricts the domain of the substitution subst to vars.

mapRangeVFresh :: (IsConst c, IsVar v, IsConst c2) => (VTerm c v -> VTerm c2 v) -> SubstVFresh c v -> SubstVFresh c2 vSource

mapRangeVFresh f subst maps the function f over the range of the substitution subst. Note that all introduced variables are considered fresh.

extendWithRenaming :: (Ord c, Show (Lit c LVar)) => [LVar] -> SubstVFresh c LVar -> SubstVFresh c LVarSource

extendWithRenaming vs s extends the substitution s with renamings (with fresh variables) for the variables in vs that are not already in dom s.

queries

varsRangeVFresh :: IsVar v => SubstVFresh c v -> [v]Source

varsRangeVFresh subst returns all variables in the range of the substitution

domVFresh :: SubstVFresh c v -> [v]Source

domVFresh subst returns the domain of the substitution substs.

rangeVFresh :: SubstVFresh c v -> [VTerm c v]Source

rangeVFresh subst returns the range of the substitution substs.

isRenaming :: LSubstVFresh c -> BoolSource

Returns True if the substitution is a renaming.

imageOfVFresh :: IsVar v => SubstVFresh c v -> v -> Maybe (VTerm c v)Source

Returns the image of i under subst if i is in the domain of subst.

views

substToListVFresh :: SubstVFresh c v -> [(v, VTerm c v)]Source

Convert substitution to list.

Pretty printing

prettySubstVFresh :: (Ord c, Ord v, HighlightDocument d, Show c, Show v) => (v -> d) -> (Lit c v -> d) -> SubstVFresh c v -> [d]Source

Pretty print a substitution.

operations on fresh substitutions

renameFresh :: (Ord c, MonadFresh m) => SubstVFresh c LVar -> m (SubstVFresh c LVar)Source

renameFresh s renames the fresh variables in s using fresh variables. This function can be used to prevent overshadowing which might make output hard to read.

renameFreshAvoiding :: (Ord c, HasFrees t) => LSubstVFresh c -> t -> SubstVFresh c LVarSource

renameFreshAvoiding s t renames the fresh variables in the range of s away from variables that are free in t. This is an internal function.

removeRenamings :: LSubstVFresh c -> LSubstVFresh cSource

removeRenamings s removes all renamings (see isRenamedVar) from s.

Substitution of LVars

type LSubstVFresh c = SubstVFresh c LVarSource

Fresh substitution with logical variables

type LNSubstVFresh = SubstVFresh Name LVarSource

Fresh substitution with logical variables and names

prettyLSubstVFresh :: (Show (Lit c LVar), Ord c, HighlightDocument d, Show c) => LSubstVFresh c -> dSource

Pretty print a substitution with logical variables.

prettyDisjLNSubstsVFresh :: Document d => Disj LNSubstVFresh -> dSource

Pretty print a disjunction of substitutions.