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

Scyther.Theory.Parser

Contents

Synopsis

Lexing

type Token = (SourcePos, Keyword)Source

The tokens delivered by our Alex based scanner

scanString :: FilePath -> String -> [Token]Source

Scan a string using the given filename in the error messages.

NOTE: Lexical errors are thrown using error.

scanFile :: FilePath -> IO [Token]Source

Scan a file

Parsing

type Parser s a = Parsec [Token] s aSource

A parser with an arbitrary user state for a stream of tokens.

parseFile :: Parser s a -> s -> FilePath -> IO aSource

Parser s a theory file.

Additional combinators

liftMaybe :: MonadPlus m => Maybe a -> m aSource

Lift a maybe to a monad plus action.

liftMaybe' :: Monad m => String -> Maybe a -> m aSource

Lift a maybe to a monad action with the given failure message.

token :: (Keyword -> Maybe a) -> Parser s aSource

Parse a token based on the acceptance condition

Keyword combinations

kw :: Keyword -> Parser s ()Source

Parse a term.

betweenKWs :: Keyword -> Keyword -> Parser s a -> Parser s aSource

Parse content between keywords.

commaSep :: Parser s a -> Parser s [a]Source

A comma separated list of elements.

commaSep1 :: Parser s a -> Parser s [a]Source

A comma separated non-empty list of elements.

list :: Parser s a -> Parser s [a]Source

Parse a list of items '[' item ',' ... ',' item ']'

braced :: Parser s a -> Parser s aSource

Between braces.

parens :: Parser s a -> Parser s aSource

Between parentheses.

brackets :: Parser s a -> Parser s aSource

Between parentheses.

singleQuoted :: Parser s a -> Parser s aSource

Between single quotes.

doubleQuoted :: Parser s a -> Parser s aSource

Between double quotes.

identifier :: Parser s StringSource

Parse an identifier as a string

string :: String -> Parser s ()Source

Parse a fixed string which could be an identifier.

strings :: [String] -> Parser s ()Source

Parse a sequence of fixed strings.

integer :: Parser s IntSource

Parse an integer.

genFunOpen :: Parser s a -> Parser s b -> Parser s aSource

Left-hand-side of a function application written with the given delimiter.

genFunApp :: Parser s a -> Parser s b -> Parser s d -> Parser s c -> Parser s cSource

Left-hand-side of a function application.

funOpen :: String -> Parser s ()Source

Left-hand-side of a function application.

funApp :: String -> Parser s a -> Parser s aSource

A function application.

Security protocol theorys for the free-algebra

protocol :: Parser s ProtocolSource

Parse a protocol.

claims :: (String -> Maybe Protocol) -> Parser s [ThyItem]Source

Parse a claim.

theory :: Parser s TheorySource

Parse a theory.

parseTheory :: FilePath -> IO TheorySource

Parse a security protocol theory given as a string using the given filename for the error messages

Extended patterns