BNFC3-3.0: A compiler front-end generator.
Safe HaskellNone
LanguageHaskell2010

BNFC.Check.Pass1

Description

First pass of processing a LBNF file.

  • Find all the categories defined in a LBNF grammar.
  • Complain about duplicate categories, e.g. defined both by rules and list or token pragmas.
  • Drops errorneous definitions, returning a list of errors. It is possible to continue into pass 2 with the remaining definitions, should the user desire so (switch --force).
  • Produces a map whose keys are the grammar categories parsed into ICat intermediate format and whose values are their first defining occurrences plus kind information.

This pass does not transform the list of parsed definitions into an intermediate format, e.g. for saving the translations of category names to ICat. This could be done, but the translation is cheap and deterministic, so it can be repeated in pass 2.

Synopsis

Documentation

data Pass1 Source #

The state and result of pass1.

Constructors

Pass1 

Fields

Instances

Instances details
Show Pass1 Source # 
Instance details

Defined in BNFC.Check.Pass1

data CatKind Source #

The kind of a category definition.

Constructors

KRules (List1 RuleKind)

given by rules and/or rules pragma

KList

given by separator or terminator pragma

KToken PositionToken

given by token pragma

Instances

Instances details
Show CatKind Source # 
Instance details

Defined in BNFC.Check.Pass1

data RuleKind Source #

The kind of a rule definition.

Constructors

ROrdinary Parseable

ordinary or internal rule

RRules

rules pragma

RCoercion

coercion pragma

Instances

Instances details
Show RuleKind Source # 
Instance details

Defined in BNFC.Check.Pass1

checkLBNF :: Grammar -> Check (Grammar, Pass1) Source #

Entry point for pass 1.

Pass 1 checker

type M = StateT Pass1 Check Source #

The monad for pass 1, manipulates Pass1.

checkGrammar :: Grammar -> M Grammar Source #

Check a whole grammar, swallowing errorneous definitions.

checkDef :: Def -> M (Maybe Def) Source #

Check a definition. Swallow it if it produces a recoverable error.

Collecting categories

useCats :: AddCategories a => a -> M () Source #

class AddCategories a where Source #

Collect categories used in something.

Instances

Instances details
AddCategories RHS Source # 
Instance details

Defined in BNFC.Check.Pass1

AddCategories Cat Source #

Also adds for each list category its element category, transitively.

Instance details

Defined in BNFC.Check.Pass1

AddCategories Item Source # 
Instance details

Defined in BNFC.Check.Pass1

AddCategories a => AddCategories [a] Source # 
Instance details

Defined in BNFC.Check.Pass1

Methods

addCategories :: [a] -> ReaderT Parseable M () Source #

AddCategories (WithPosition ICat) Source #

Directly add to _stUsedCats.

Instance details

Defined in BNFC.Check.Pass1

Collecting keywords

class AddKeywords a where Source #

Methods

addKeywords :: a -> M () Source #

Instances

Instances details
AddKeywords RHS Source # 
Instance details

Defined in BNFC.Check.Pass1

Methods

addKeywords :: RHS -> M () Source #

AddKeywords Item Source # 
Instance details

Defined in BNFC.Check.Pass1

Methods

addKeywords :: Item -> M () Source #

AddKeywords a => AddKeywords [a] Source # 
Instance details

Defined in BNFC.Check.Pass1

Methods

addKeywords :: [a] -> M () Source #

ToPosition p => AddKeywords (p, String) Source # 
Instance details

Defined in BNFC.Check.Pass1

Methods

addKeywords :: (p, String) -> M () Source #

Utilities

Trash

data WithDefinition a Source #

Constructors

WithDefinition 

Fields

Instances

Instances details
Functor WithDefinition Source # 
Instance details

Defined in BNFC.Check.Pass1

Methods

fmap :: (a -> b) -> WithDefinition a -> WithDefinition b Source #

(<$) :: a -> WithDefinition b -> WithDefinition a Source #

Foldable WithDefinition Source # 
Instance details

Defined in BNFC.Check.Pass1

Methods

fold :: Monoid m => WithDefinition m -> m Source #

foldMap :: Monoid m => (a -> m) -> WithDefinition a -> m Source #

foldMap' :: Monoid m => (a -> m) -> WithDefinition a -> m Source #

foldr :: (a -> b -> b) -> b -> WithDefinition a -> b Source #

foldr' :: (a -> b -> b) -> b -> WithDefinition a -> b Source #

foldl :: (b -> a -> b) -> b -> WithDefinition a -> b Source #

foldl' :: (b -> a -> b) -> b -> WithDefinition a -> b Source #

foldr1 :: (a -> a -> a) -> WithDefinition a -> a Source #

foldl1 :: (a -> a -> a) -> WithDefinition a -> a Source #

toList :: WithDefinition a -> [a] Source #

null :: WithDefinition a -> Bool Source #

length :: WithDefinition a -> Int Source #

elem :: Eq a => a -> WithDefinition a -> Bool Source #

maximum :: Ord a => WithDefinition a -> a Source #

minimum :: Ord a => WithDefinition a -> a Source #

sum :: Num a => WithDefinition a -> a Source #

product :: Num a => WithDefinition a -> a Source #

Traversable WithDefinition Source # 
Instance details

Defined in BNFC.Check.Pass1

Methods

traverse :: Applicative f => (a -> f b) -> WithDefinition a -> f (WithDefinition b) Source #

sequenceA :: Applicative f => WithDefinition (f a) -> f (WithDefinition a) Source #

mapM :: Monad m => (a -> m b) -> WithDefinition a -> m (WithDefinition b) Source #

sequence :: Monad m => WithDefinition (m a) -> m (WithDefinition a) Source #

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

Defined in BNFC.Check.Pass1

data CatOrigin Source #

Constructors

ORule

ordinary or internal rule

ORules

rules pragma

OList

separator or terminator pragma

OToken

token definition (exclusive)

data CatInfo Source #

Constructors

CatInfo 

Fields

Instances

Instances details
Show CatInfo Source # 
Instance details

Defined in BNFC.Check.Pass1