Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Lang.Crucible.Syntax.SExpr
Synopsis
- pattern A :: Syntactic a b => b -> a
- pattern L :: Syntactic a b => [Syntax b] -> a
- pattern (:::) :: Syntactic a b => Syntax b -> [Syntax b] -> a
- newtype Syntax a = Syntax {}
- newtype Datum a = Datum {}
- class Syntactic a b | a -> b where
- type Parser = Parsec Void Text
- syntaxPos :: Syntax a -> Position
- withPosFrom :: Syntax a -> b -> Posd b
- sexp :: Parser a -> Parser (Syntax a)
- identifier :: Parser Text
- toText :: (Syntactic expr a, IsAtom a) => PrintRules a -> expr -> Text
- datumToText :: IsAtom a => PrintRules a -> Datum a -> Text
- skipWhitespace :: Parser ()
- newtype PrintRules a = PrintRules (a -> Maybe PrintStyle)
- data PrintStyle = Special Int
- data Layer f a
- class IsAtom a where
Documentation
pattern (:::) :: Syntactic a b => Syntax b -> [Syntax b] -> a Source #
Match the head and tail of a list-like structure
Syntax objects, in which each layer is annotated with a source position.
Syntax objects divorced of their source-code context, without source positions.
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
Monoid (PrintRules a) Source # | |
Defined in Lang.Crucible.Syntax.SExpr Methods mempty :: PrintRules a # mappend :: PrintRules a -> PrintRules a -> PrintRules a # mconcat :: [PrintRules a] -> PrintRules a # | |
Semigroup (PrintRules a) Source # | |
Defined in Lang.Crucible.Syntax.SExpr Methods (<>) :: PrintRules a -> PrintRules a -> PrintRules a # sconcat :: NonEmpty (PrintRules a) -> PrintRules a # stimes :: Integral b => b -> PrintRules a -> PrintRules a # |
data PrintStyle Source #
Styles of printing
The pattern functor for syntax, used both for Syntax
and
Datum
. In Syntax
, it is composed with another structure that
adds source positions.