syntax-0.1.1.0: Abstract syntax descriptions for parsing and pretty-printing.

Copyright(c) Paweł Nowak
LicenseMIT
MaintainerPaweł Nowak <pawel834@gmail.com>
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Data.Syntax

Contents

Description

Abstract syntax descriptions based on semi-isomorphisms.

Synopsis

Syntax.

class (SemiIsoAlternative syn, IsSequence seq, Eq seq, Eq (Element seq)) => Syntax syn seq | syn -> seq where Source

An abstract syntax description based on semi-isomorphisms.

This class can be implemented by both parsers and printers (and maybe more?).

The usual use is to write a polymorphic syntax description and instantiate it both as a parser and a printer. An example syntax description:

| A simple untyped lambda calculus.
data AST = Var Text
         | App AST AST
         | Abs Text AST
    deriving (Show)

$(makePrisms ''AST)

-- | A variable name.
name :: Syntax syn Text => syn Text
name = S.takeWhile1 isAlphaNum

-- | Encloses a symbol in parentheses.
parens :: Syntax syn Text => syn a -> syn a
parens m = S.char '(' */ S.spaces_ */ m /* S.spaces_ /* S.char ')'

-- | An atom is a variable or an expression in parentheses.
atom :: Syntax syn Text => syn AST
atom =  _Var /$/ name
    /|/ parens expr

--| Parses a list of applications.
apps :: Syntax syn Text => syn AST
apps = bifoldl1 (attemptAp_ _App) /$/ S.sepBy1 atom S.spaces1

-- | An expression of our lambda calculus.
expr :: Syntax syn Text => syn AST
expr =  _Abs /$/ S.char '\\'   /* S.spaces_
              */ name          /* S.spaces
             /*  S.string "->" /* S.spaces
             /*/ expr
    /|/ apps

Methods of this class try to mimic Data.Attoparsec.Text interface.

Minimal complete definition

anyChar

Methods

anyChar :: syn (Element seq) Source

Any character.

char :: Element seq -> syn () Source

A specific character.

notChar :: Element seq -> syn (Element seq) Source

Any character except the given one.

satisfy :: (Element seq -> Bool) -> syn (Element seq) Source

Any character satisfying a predicate.

satisfyWith :: ASemiIso' a (Element seq) -> (a -> Bool) -> syn a Source

Transforms a character using a SemiIso and filters out values not satisfying the predicate.

string :: seq -> syn () Source

A specific string.

take :: Int -> syn seq Source

A string of length n.

takeWhile :: (Element seq -> Bool) -> syn seq Source

Maximal string which elements satisfy a predicate.

takeWhile1 :: (Element seq -> Bool) -> syn seq Source

Maximal non-empty string which elements satisfy a predicate.

takeTill :: (Element seq -> Bool) -> syn seq Source

Maximal string which elements do not satisfy a predicate.

takeTill1 :: (Element seq -> Bool) -> syn seq Source

Maximal non-empty string which elements do not satisfy a predicate.

Common isomorphisms.

packed :: IsSequence seq => Iso' seq [Element seq] Source

An isomorphism between a sequence and a list of its elements.