language-haskell
Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Grammar

Description

This module exports the original Haskell 2010 grammar with no extensions. Apart from use of parser combinators and some minor refactorings, the grammar productions closely correspond to those documented in the Haskell 2010 Language Report.

Synopsis

Documentation

type Parser (g :: (Type -> Type) -> Type) s = ParserT ((,) [[Lexeme s]]) g s Source #

The parser keeps track of the lexemes consumed while parsing the current node.

The Haskell 2010 grammar

data HaskellGrammar l t (f :: Type -> Type) (p :: Type -> Type) Source #

Top level of the grammar, including types and expressions

Constructors

HaskellGrammar 

Fields

Instances

Instances details
(Applicative (ModuleLevelGrammar l f), Applicative (DeclarationGrammar l f)) => Applicative (HaskellGrammar l t f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

pure :: (forall a. f0 a) -> HaskellGrammar l t f f0 #

(Apply (ModuleLevelGrammar l f), Apply (DeclarationGrammar l f)) => Apply (HaskellGrammar l t f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

(<*>) :: forall (p :: Type -> Type) (q :: Type -> Type). HaskellGrammar l t f (p ~> q) -> HaskellGrammar l t f p -> HaskellGrammar l t f q #

liftA2 :: (forall a. p a -> q a -> r a) -> HaskellGrammar l t f p -> HaskellGrammar l t f q -> HaskellGrammar l t f r #

liftA3 :: (forall a. p a -> q a -> r a -> s a) -> HaskellGrammar l t f p -> HaskellGrammar l t f q -> HaskellGrammar l t f r -> HaskellGrammar l t f s #

(Distributive (ModuleLevelGrammar l f), Distributive (DeclarationGrammar l f)) => Distributive (HaskellGrammar l t f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

collect :: forall p a (q :: Type -> Type). Functor p => (a -> HaskellGrammar l t f q) -> p a -> HaskellGrammar l t f (Compose p q) #

distribute :: forall p (q :: Type -> Type). Functor p => p (HaskellGrammar l t f q) -> HaskellGrammar l t f (Compose p q) #

cotraverse :: Functor m => (forall a. m (p a) -> q a) -> m (HaskellGrammar l t f p) -> HaskellGrammar l t f q #

(DistributiveTraversable (ModuleLevelGrammar l f), DistributiveTraversable (DeclarationGrammar l f)) => DistributiveTraversable (HaskellGrammar l t f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

collectTraversable :: forall f1 a (f2 :: Type -> Type). Traversable f1 => (a -> HaskellGrammar l t f f2) -> f1 a -> HaskellGrammar l t f (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: Type -> Type). Traversable f1 => f1 (HaskellGrammar l t f f2) -> HaskellGrammar l t f (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f0 x) -> f1 (HaskellGrammar l t f f2) -> HaskellGrammar l t f f0 #

(Foldable (ModuleLevelGrammar l f), Foldable (DeclarationGrammar l f)) => Foldable (HaskellGrammar l t f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> HaskellGrammar l t f p -> m #

(Functor (ModuleLevelGrammar l f), Functor (DeclarationGrammar l f)) => Functor (HaskellGrammar l t f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

(<$>) :: (forall a. p a -> q a) -> HaskellGrammar l t f p -> HaskellGrammar l t f q #

(Logistic (ModuleLevelGrammar l f), Logistic (DeclarationGrammar l f)) => Logistic (HaskellGrammar l t f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

deliver :: forall p (q :: Type -> Type). Contravariant p => p (HaskellGrammar l t f q -> HaskellGrammar l t f q) -> HaskellGrammar l t f (Compose p (q ~> q)) #

(Traversable (ModuleLevelGrammar l f), Traversable (DeclarationGrammar l f)) => Traversable (HaskellGrammar l t f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

traverse :: Applicative m => (forall a. p a -> m (q a)) -> HaskellGrammar l t f p -> m (HaskellGrammar l t f q) #

sequence :: forall m (p :: Type -> Type). Applicative m => HaskellGrammar l t f (Compose m p) -> m (HaskellGrammar l t f p) #

data ModuleLevelGrammar l (f :: Type -> Type) (p :: Type -> Type) Source #

The grammar productions that are relevant only at the module level

Constructors

ModuleLevelGrammar 

Fields

Instances

Instances details
Applicative (ModuleLevelGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

pure :: (forall a. f0 a) -> ModuleLevelGrammar l f f0 #

Apply (ModuleLevelGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

(<*>) :: forall (p :: Type -> Type) (q :: Type -> Type). ModuleLevelGrammar l f (p ~> q) -> ModuleLevelGrammar l f p -> ModuleLevelGrammar l f q #

liftA2 :: (forall a. p a -> q a -> r a) -> ModuleLevelGrammar l f p -> ModuleLevelGrammar l f q -> ModuleLevelGrammar l f r #

liftA3 :: (forall a. p a -> q a -> r a -> s a) -> ModuleLevelGrammar l f p -> ModuleLevelGrammar l f q -> ModuleLevelGrammar l f r -> ModuleLevelGrammar l f s #

Distributive (ModuleLevelGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

collect :: forall p a (q :: Type -> Type). Functor p => (a -> ModuleLevelGrammar l f q) -> p a -> ModuleLevelGrammar l f (Compose p q) #

distribute :: forall p (q :: Type -> Type). Functor p => p (ModuleLevelGrammar l f q) -> ModuleLevelGrammar l f (Compose p q) #

cotraverse :: Functor m => (forall a. m (p a) -> q a) -> m (ModuleLevelGrammar l f p) -> ModuleLevelGrammar l f q #

DistributiveTraversable (ModuleLevelGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

collectTraversable :: forall f1 a (f2 :: Type -> Type). Traversable f1 => (a -> ModuleLevelGrammar l f f2) -> f1 a -> ModuleLevelGrammar l f (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: Type -> Type). Traversable f1 => f1 (ModuleLevelGrammar l f f2) -> ModuleLevelGrammar l f (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f0 x) -> f1 (ModuleLevelGrammar l f f2) -> ModuleLevelGrammar l f f0 #

Foldable (ModuleLevelGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> ModuleLevelGrammar l f p -> m #

Functor (ModuleLevelGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

(<$>) :: (forall a. p a -> q a) -> ModuleLevelGrammar l f p -> ModuleLevelGrammar l f q #

Logistic (ModuleLevelGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

deliver :: forall p (q :: Type -> Type). Contravariant p => p (ModuleLevelGrammar l f q -> ModuleLevelGrammar l f q) -> ModuleLevelGrammar l f (Compose p (q ~> q)) #

Traversable (ModuleLevelGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

traverse :: Applicative m => (forall a. p a -> m (q a)) -> ModuleLevelGrammar l f p -> m (ModuleLevelGrammar l f q) #

sequence :: forall m (p :: Type -> Type). Applicative m => ModuleLevelGrammar l f (Compose m p) -> m (ModuleLevelGrammar l f p) #

data DeclarationGrammar l (f :: NodeWrap) (p :: Type -> Type) Source #

The grammar productions that are only relevant inside declarations

Constructors

DeclarationGrammar 

Fields

Instances

Instances details
Applicative (DeclarationGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

pure :: (forall a. f0 a) -> DeclarationGrammar l f f0 #

Apply (DeclarationGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

(<*>) :: forall (p :: Type -> Type) (q :: Type -> Type). DeclarationGrammar l f (p ~> q) -> DeclarationGrammar l f p -> DeclarationGrammar l f q #

liftA2 :: (forall a. p a -> q a -> r a) -> DeclarationGrammar l f p -> DeclarationGrammar l f q -> DeclarationGrammar l f r #

liftA3 :: (forall a. p a -> q a -> r a -> s a) -> DeclarationGrammar l f p -> DeclarationGrammar l f q -> DeclarationGrammar l f r -> DeclarationGrammar l f s #

Distributive (DeclarationGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

collect :: forall p a (q :: Type -> Type). Functor p => (a -> DeclarationGrammar l f q) -> p a -> DeclarationGrammar l f (Compose p q) #

distribute :: forall p (q :: Type -> Type). Functor p => p (DeclarationGrammar l f q) -> DeclarationGrammar l f (Compose p q) #

cotraverse :: Functor m => (forall a. m (p a) -> q a) -> m (DeclarationGrammar l f p) -> DeclarationGrammar l f q #

DistributiveTraversable (DeclarationGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

collectTraversable :: forall f1 a (f2 :: Type -> Type). Traversable f1 => (a -> DeclarationGrammar l f f2) -> f1 a -> DeclarationGrammar l f (Compose f1 f2) #

distributeTraversable :: forall f1 (f2 :: Type -> Type). Traversable f1 => f1 (DeclarationGrammar l f f2) -> DeclarationGrammar l f (Compose f1 f2) #

cotraverseTraversable :: Traversable f1 => (forall x. f1 (f2 x) -> f0 x) -> f1 (DeclarationGrammar l f f2) -> DeclarationGrammar l f f0 #

Foldable (DeclarationGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

foldMap :: Monoid m => (forall a. p a -> m) -> DeclarationGrammar l f p -> m #

Functor (DeclarationGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

(<$>) :: (forall a. p a -> q a) -> DeclarationGrammar l f p -> DeclarationGrammar l f q #

Logistic (DeclarationGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

deliver :: forall p (q :: Type -> Type). Contravariant p => p (DeclarationGrammar l f q -> DeclarationGrammar l f q) -> DeclarationGrammar l f (Compose p (q ~> q)) #

Traversable (DeclarationGrammar l f :: (Type -> Type) -> Type) Source # 
Instance details

Defined in Language.Haskell.Grammar

Methods

traverse :: Applicative m => (forall a. p a -> m (q a)) -> DeclarationGrammar l f p -> m (DeclarationGrammar l f q) #

sequence :: forall m (p :: Type -> Type). Applicative m => DeclarationGrammar l f (Compose m p) -> m (DeclarationGrammar l f p) #

grammar :: forall l (g :: (Type -> Type) -> Type) t. (Apply g, Haskell l, Ord t, Show t, OutlineMonoid t, Foldable (Serialization (Down Int) t) (CaseAlternative l l), Foldable (Serialization (Down Int) t) (Declaration l l), Foldable (Serialization (Down Int) t) (Expression l l), Foldable (Serialization (Down Int) t) (Import l l), Foldable (Serialization (Down Int) t) (Statement l l)) => GrammarBuilder (HaskellGrammar l t (NodeWrap t)) g (ParserT ((,) [[Lexeme t]])) t Source #

Extensible grammar builder with all the syntax of Haskell 2010

grammar2010 :: (Haskell l, Ord t, Show t, OutlineMonoid t, Foldable (Serialization (Down Int) t) (CaseAlternative l l), Foldable (Serialization (Down Int) t) (Declaration l l), Foldable (Serialization (Down Int) t) (Expression l l), Foldable (Serialization (Down Int) t) (Import l l), Foldable (Serialization (Down Int) t) (Statement l l)) => Grammar (HaskellGrammar l t (NodeWrap t)) (ParserT ((,) [[Lexeme t]])) t Source #

Fixed (and thus non-extensible) grammar of Haskell 2010

Lexical layer

keyword :: forall (g :: (Type -> Type) -> Type) s. (Apply g, Ord s, Show s, TextualMonoid s) => s -> Parser g s () Source #

delimiter :: forall (g :: (Type -> Type) -> Type) t. (Apply g, Ord t, Show t, TextualMonoid t) => t -> Parser g t () Source #

terminator :: forall (g :: (Type -> Type) -> Type) t. (Apply g, Ord t, Show t, TextualMonoid t) => t -> Parser g t () Source #

moduleLexeme :: forall (g :: (Type -> Type) -> Type) l t. (Apply g, Haskell l, Ord t, Show t, TextualMonoid t) => Parser g t (NonEmpty (Name l)) Source #

moduleId :: forall (g :: (Type -> Type) -> Type) l t. (Apply g, Haskell l, Ord t, Show t, TextualMonoid t) => Parser g t (ModuleName l) Source #

nameQualifier :: forall (g :: (Type -> Type) -> Type) l t. (Apply g, Haskell l, Ord t, Show t, TextualMonoid t) => Parser g t (Name l -> QualifiedName l) Source #

nameToken :: forall (g :: (Type -> Type) -> Type) l t. (Apply g, Haskell l, Ord t, Show t, TextualMonoid t) => Parser g t t -> Parser g t (Name l) Source #

constructorSymbolLexeme :: forall (g :: (Type -> Type) -> Type) t. (Apply g, Ord t, Show t, TextualMonoid t) => Parser g t t Source #

variableSymbolLexeme :: forall (g :: (Type -> Type) -> Type) t. (Apply g, Ord t, Show t, TextualMonoid t) => Parser g t t Source #

whiteSpace :: forall (g :: (Type -> Type) -> Type) t. (Apply g, Ord t, Show t, TextualMonoid t) => Parser g t () Source #

comment :: forall (g :: (Type -> Type) -> Type) t. (Apply g, Ord t, Show t, TextualMonoid t) => Parser g t () Source #

Layout parsing

blockOf :: forall (g :: (Type -> Type) -> Type) t node. (Apply g, Ord t, Show t, OutlineMonoid t, Foldable (Serialization (Down Int) t) node) => Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t))) -> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))] Source #

The combinator turns a parser for a single block item (statement or case alternative or declaration or ...) into the parser for an aligned block of the things.

blockWith Source #

Arguments

:: forall (g :: (Type -> Type) -> Type) t node. (Apply g, Ord t, Show t, OutlineMonoid t, Foldable (Serialization (Down Int) t) node) 
=> (Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool)

test if the indent, the line and the node parsed from it are a valid block item, oneExtendedLine by default

-> Parser g t ()

parser for a keyword that can't start a valid block item, blockTerminatorKeyword by default

-> Parser g t (NodeWrap t (node (NodeWrap t) (NodeWrap t)))

parser for a single block item

-> Parser g t [NodeWrap t (node (NodeWrap t) (NodeWrap t))] 

A more general form of blockOf

blockTerminatorKeyword :: forall (g :: (Type -> Type) -> Type) t. (Apply g, Ord t, OutlineMonoid t, Show t) => Parser g t () Source #

A default argument to blockWith

oneExtendedLine :: (Ord t, Show t, OutlineMonoid t, Foldable (Serialization (Down Int) t) node) => Int -> t -> NodeWrap t (node (NodeWrap t) (NodeWrap t)) -> Bool Source #

A default argument to blockWith

verifyStatements :: forall l (g :: (Type -> Type) -> Type) t. (Haskell l, Apply g, Ord t) => [NodeWrap t (Sum (Statement l l) (Expression l l) (NodeWrap t) (NodeWrap t))] -> Parser g t (GuardedExpression l l (NodeWrap t) (NodeWrap t)) Source #

Check if the given sequence of statements and expressions ends with an expression, and if they do pack them all into a single GuardedExpression.

class TextualMonoid t => OutlineMonoid t where Source #

Class of inputs that keep track of their current position in terms of line and column

Methods

currentColumn :: t -> Int Source #

The column of the current input position, i.e. the count of characters from the position to the preceding line start

Instances

Instances details
OutlineMonoid (LinePositioned Text) Source # 
Instance details

Defined in Language.Haskell.Grammar

OutlineMonoid (Shadowed Text) Source # 
Instance details

Defined in Language.Haskell.Grammar

inputColumn :: forall (g :: (Type -> Type) -> Type) t. (Apply g, Ord t, OutlineMonoid t) => Parser g t Int Source #

Returns the column of the current input position

Node wrapping

type NodeWrap s = Wrapped (Down Int) s Source #

The wrap of every parsed AST node keeps track of the parsed input range and the lexemes consumed from it.

storeToken :: forall (g :: (Type -> Type) -> Type) t a. (Apply g, Ord t, TextualMonoid t) => Parser g t a -> Parser g t a Source #

wrap :: forall (g :: (Type -> Type) -> Type) t a. (Apply g, Ord t, TextualMonoid t) => Parser g t a -> Parser g t (NodeWrap t a) Source #

Apply the argument parser and wrap the resulting node.

rewrap :: (NodeWrap t a -> b) -> NodeWrap t a -> NodeWrap t b Source #

Rewrap the node with an empty wrap.

unwrap :: NodeWrap t a -> a Source #

Strip the wrap.

Utility functions

expressionToStatement :: Haskell l => NodeWrap t (Sum (Statement l l) (Expression l l) (NodeWrap t) (NodeWrap t)) -> NodeWrap t (Statement l l (NodeWrap t) (NodeWrap t)) Source #

Convert a tagged Sum of either Statement or Expression into a Statement.

startSepEndBy :: Alternative m => m a -> m sep -> m [a] Source #

Parses a sequence of zero or more occurrences of p, separated and optionally started or ended by one or more of sep.

Orphan instances

(Apply g, Ord t, Show t, TextualMonoid t) => LexicalParsing (Parser g t) Source # 
Instance details

(Apply g, Ord t, Show t, TextualMonoid t) => TokenParsing (Parser g t) Source # 
Instance details

Methods

someSpace :: Parser g t () #

nesting :: Parser g t a -> Parser g t a #

semi :: Parser g t Char #

highlight :: Highlight -> Parser g t a -> Parser g t a #

token :: Parser g t a -> Parser g t a #