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

BNFC.Check.Monad

Description

The checker monad.

Responsible for throwing errors and accumulating warnings.

Synopsis

Specification

class Monad m => MonadCheck m where Source #

Monad for error reporting and warnings.

Minimal complete definition

Nothing

Methods

fatalError :: FatalError -> m a Source #

default fatalError :: (MonadTrans t, MonadCheck n, t n ~ m) => FatalError -> m a Source #

recoverableError :: RecoverableError -> m () Source #

default recoverableError :: (MonadTrans t, MonadCheck n, t n ~ m) => RecoverableError -> m () Source #

warn :: Warning -> m () Source #

default warn :: (MonadTrans t, MonadCheck n, t n ~ m) => Warning -> m () Source #

atPosition :: ToPosition' p => p -> m a -> m a Source #

Set the file position for subsequent errors.

default atPosition :: (MonadTransControl t, MonadCheck n, t n ~ m) => ToPosition' p => p -> m a -> m a Source #

askPosition :: m Position' Source #

Retrieve the stored position.

default askPosition :: (MonadTrans t, MonadCheck n, t n ~ m) => m Position' Source #

Warnings and errors

data FatalError Source #

Fatal errors (check cannot continue).

Constructors

FatalError 
UndefinedLabel LabelName

The given label isn't contained in the Signature.

ListsDontInhabitType Type

A list expression was found at the given type, which isn't a ListType.

Instances

Instances details
Show FatalError Source # 
Instance details

Defined in BNFC.Check.Monad

data RecoverableError Source #

Any of these errors allows to continue BNFC, but may result in undesired/illformed output.

Constructors

DelimitersNotSupported

The pragma delimiters has been removed in BNFC 2.9. Pragma is ignored.

IncompatibleDefinition ICat Position

E.g. trying to mix ordinary rules with list pragmas or token definitions. Redefinition is ignored.

CoercionsOfCoerceCat

Trying to apply coercions pragma to a CoerceCat, e.g. coercions Exp3 2. Pragma is ignored. Pass 2 errors

CoercionsOfBuiltinCat

Trying to apply coercions pragma to a BuiltinCat, e.g. coercions Integer 2. Pragma is ignored.

CoercionsOfIdentCat

Trying to apply coercions pragma to a IdentCat, e.g. coercions Ident 2. Pragma is ignored.

CoercionsOfTokenCat

Trying to apply coercions pragma to a TokenCat, e.g. coercions Id 2. Pragma is ignored.

UnknownCatName CatName

This base category is not defined.

CoerceBuiltinCat BuiltinCat

Tried to make a precedence variant of a builtin category, like Char3.

CoerceIdentCat IdentCat

Tried to make a precedence variant of an ident category, like Ident3.

CoerceListCat CatName

Tried to make a precedence variant of a list category, like [Arg3].

CoerceTokenCat CatName

Tried to make a precedence variant of a token category, like Id3.

DuplicateLabel LabelName Position

The label LabelName has been defined already, at Position.

DuplicateRHS Position

The same BNF rule already exists, at Position.

InvalidListRule LabelName

Cannot use ordinary or defined labels to construct a list category.

InvalidListLabel Type

List label to construct non-list category.

InvalidLabelNil FunType

Invalid type for label [].

InvalidLabelCons FunType

Invalid type for label (:).

InvalidLabelSg FunType

Invalid type for label (:[]).

InvalidLabelWild FunType

Invalid type for label _.

IgnoringUndeclaredFunction

define pragma with unused label is skipped, since we don't have its type.

NotEnoughParameters (List1 String1)

Type checker added missing parameters in a define.

DroppingSpuriousParameters (List1 Arg)

These parameters were ignored since they are too many, according to the type.

MissingArguments LabelName (List1 Type)

A constructor/function misses arguments of the given types.

DroppingSpuriousArguments LabelName (List1 Exp)

A constructor/function was given (these) more arguments than needed.

ExpectedVsInferredType Type Type

An expression of the first type was expected, but it has the second type.

NullableToken CatName Regex

Defined token category matches the empty string. Such a token can be produced by the lexer when nothing else can be produced, but then it can be produced infinitely often without making progress. This may result in a loop in the lexer. Token definition is kept.

IllformedBlockComment

One of the delimiters of a block comment is empty.

ConflictingUsesOfLayoutKeyword Keyword Position

A keyword appears both in layout and layout stop. The redefinition is ignored. Final checks

EmptyGrammar

No entrypoints have been defined. This is an error that does not block any other checks, so it is "recoverable". But it makes flags failure of the check phase, because later phases (e.g. parser generation) will crash.

Instances

Instances details
Show RecoverableError Source # 
Instance details

Defined in BNFC.Check.Monad

data Warning Source #

Any of these warnings drops the useless or redundant definition.

Constructors

FooWarning 
LabelClashesWithCategory LabelName Position

The label LabelName clashes with a category of the same name defined at Position.

IgnoringNullCoercions

coercions _ 0 does not add any rules.

NonUniformListRule Cat [Cat]

A list rule with different coercion levels of the base category. Cannot implement faithful printer for such rules.

ParameterShouldBeLowerCase VarName

Grammar permits upper case parameters, but this isn't Haskell-style (which is the model for BNFC's expression syntax otherwise).

ShadowingParameter VarName

A parameter shadows a previous one.

ShadowedByParameter VarName

The given label is shadowed by a parameter, which looks confusing.

EmptyToken CatName Regex

Defined token category may not match anything.

IgnoringEmptyLineComment

comment "" is ignored.

IgnoringEmptyBlockComment

comment "" "" is ignored.

EmptyLayoutKeyword

layout [stop] "" is simply ignored

UndefinedLayoutKeyword Keyword

layout [stop] kw but kw is not mentioned in the grammar.

DuplicateLayoutKeyword Keyword Position

This layout keyword already occurred in a pragma of the same kind.

DuplicateLayoutTop Position

layout toplevel already appeared at Position.

Instances

Instances details
Show Warning Source # 
Instance details

Defined in BNFC.Check.Monad

Types used only in the checker

type ICat = Cat' CatName Source #

Intermediated form of categories. (No builtins/token types recognized yet.)

Implementation

newtype Check a Source #

The LBNF checker monad.

Instances

Instances details
Monad Check Source # 
Instance details

Defined in BNFC.Check.Monad

Methods

(>>=) :: Check a -> (a -> Check b) -> Check b Source #

(>>) :: Check a -> Check b -> Check b Source #

return :: a -> Check a Source #

Functor Check Source # 
Instance details

Defined in BNFC.Check.Monad

Methods

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

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

Applicative Check Source # 
Instance details

Defined in BNFC.Check.Monad

Methods

pure :: a -> Check a Source #

(<*>) :: Check (a -> b) -> Check a -> Check b Source #

liftA2 :: (a -> b -> c) -> Check a -> Check b -> Check c Source #

(*>) :: Check a -> Check b -> Check b Source #

(<*) :: Check a -> Check b -> Check a Source #

MonadCheck Check Source # 
Instance details

Defined in BNFC.Check.Monad