crucible-syntax-0.4.1: A syntax for reading and writing Crucible control-flow graphs
Safe HaskellSafe-Inferred
LanguageHaskell2010

Lang.Crucible.Syntax.SExpr

Synopsis

Documentation

pattern A :: Syntactic a b => b -> a Source #

Match an atom from a syntactic structure

pattern L :: Syntactic a b => [Syntax b] -> a Source #

Match a list from a syntactic structure

pattern (:::) :: Syntactic a b => Syntax b -> [Syntax b] -> a Source #

Match the head and tail of a list-like structure

newtype Syntax a Source #

Syntax objects, in which each layer is annotated with a source position.

Constructors

Syntax 

Fields

Instances

Instances details
Functor Syntax Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Methods

fmap :: (a -> b) -> Syntax a -> Syntax b #

(<$) :: a -> Syntax b -> Syntax a #

Show a => Show (Syntax a) Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Methods

showsPrec :: Int -> Syntax a -> ShowS #

show :: Syntax a -> String #

showList :: [Syntax a] -> ShowS #

Eq a => Eq (Syntax a) Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Methods

(==) :: Syntax a -> Syntax a -> Bool #

(/=) :: Syntax a -> Syntax a -> Bool #

Syntactic (Syntax a) a Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Methods

syntaxE :: Syntax a -> Layer Syntax a Source #

Syntactic (Layer Syntax a) a Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

newtype Datum a Source #

Syntax objects divorced of their source-code context, without source positions.

Constructors

Datum 

Fields

Instances

Instances details
Functor Datum Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Methods

fmap :: (a -> b) -> Datum a -> Datum b #

(<$) :: a -> Datum b -> Datum a #

Show a => Show (Datum a) Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Methods

showsPrec :: Int -> Datum a -> ShowS #

show :: Datum a -> String #

showList :: [Datum a] -> ShowS #

Eq a => Eq (Datum a) Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Methods

(==) :: Datum a -> Datum a -> Bool #

(/=) :: Datum a -> Datum a -> Bool #

class Syntactic a b | a -> b where Source #

Instances of Syntactic support observations using the L and A patterns.

Methods

syntaxE :: a -> Layer Syntax b Source #

Instances

Instances details
Syntactic (Syntax a) a Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Methods

syntaxE :: Syntax a -> Layer Syntax a Source #

Syntactic (Layer Syntax a) a Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

type Parser = Parsec Void Text Source #

A parser for s-expressions.

syntaxPos :: Syntax a -> Position Source #

Extract the source position from a Syntax object.

withPosFrom :: Syntax a -> b -> Posd b Source #

Use the position from a syntax object around something else.

sexp :: Parser a -> Parser (Syntax a) Source #

Given a parser for atoms, parse an s-expression that contains them.

identifier :: Parser Text Source #

Parse an identifier.

toText :: (Syntactic expr a, IsAtom a) => PrintRules a -> expr -> Text Source #

Render a syntactic structure to text, according to rules.

datumToText :: IsAtom a => PrintRules a -> Datum a -> Text Source #

Render a datum to text according to rules.

skipWhitespace :: Parser () Source #

Skip whitespace.

newtype PrintRules a Source #

Printing rules describe how to specially format expressions that begin with particular atoms.

Constructors

PrintRules (a -> Maybe PrintStyle) 

Instances

Instances details
Monoid (PrintRules a) Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Semigroup (PrintRules a) Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

data PrintStyle Source #

Styles of printing

Constructors

Special Int

Special forms should treat the first n subforms as special, and the remaining as a body. For instance, for a Lisp-like let-expression, use 'Special 1' for indentation.

data Layer f a Source #

The pattern functor for syntax, used both for Syntax and Datum. In Syntax, it is composed with another structure that adds source positions.

Constructors

List [f a] 
Atom a 

Instances

Instances details
Functor f => Functor (Layer f) Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Methods

fmap :: (a -> b) -> Layer f a -> Layer f b #

(<$) :: a -> Layer f b -> Layer f a #

(Show a, Show (f a)) => Show (Layer f a) Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Methods

showsPrec :: Int -> Layer f a -> ShowS #

show :: Layer f a -> String #

showList :: [Layer f a] -> ShowS #

(Eq a, Eq (f a)) => Eq (Layer f a) Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

Methods

(==) :: Layer f a -> Layer f a -> Bool #

(/=) :: Layer f a -> Layer f a -> Bool #

Syntactic (Layer Syntax a) a Source # 
Instance details

Defined in Lang.Crucible.Syntax.SExpr

class IsAtom a where Source #

Methods

showAtom :: a -> Text Source #

Instances

Instances details
IsAtom Atomic Source # 
Instance details

Defined in Lang.Crucible.Syntax.Atoms

Methods

showAtom :: Atomic -> Text Source #

IsAtom TrivialAtom Source # 
Instance details

Defined in Lang.Crucible.Syntax.ExprParse