fortran-src-0.15.1: Parsers and analyses for Fortran standards 66, 77, 90, 95 and 2003 (partial).
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Fortran.Parser

Description

Common interface to various Fortran parsers.

Each parser exports various Happy-generated functions. All export a top-level ProgramFile parser. Most also export intermediate parsers e.g. for Statements and Expressions. Fixed form and free form parsers use different lexing schemes. And, due to headaches with Fortran's syntax, we usually want to enforce some post-parse transformations.

This module provides a common wrapper over all that functionality. Internal combinators are exposed to assist in manually configuring parsers.

Synopsis

Main parsers (ProgramFile, with transformation)

Main parsers without post-parse transformation

Other parsers

byVerFromFilename :: Parser (ProgramFile A0) Source #

Obtain a Fortran parser by assuming the version from the filename provided.

Statement

Various combinators

defaultTransformation :: Data a => FortranVersion -> Transform a () Source #

The default post-parse AST transformation for each Fortran version.

Formed by composing transformations end-to-end.

Note that some transformations are noncommutative e.g. labeled DO grouping must be done before block DO grouping.

type Parser a = String -> ByteString -> Either ParseErrorSimple a Source #

Our common Fortran parser type takes a filename and input, and returns either a normalized error (tokens are printed) or an untransformed ProgramFile.

type ParserMaker ai tok a = Parse ai tok a -> FortranVersion -> Parser a Source #

makeParser :: (Loc ai, LastToken ai tok, Show tok) => StateInit ai -> ParserMaker ai tok a Source #

initParseStateFreeExpr :: StateInit AlexInput Source #

Initialize free-form parser state with the lexer configured for standalone expression parsing.

The free-form lexer needs a non-default start code for lexing standaloe expressions.

parseUnsafe :: Parser a -> ByteString -> a Source #

Convenience wrapper to easily use a parser unsafely.

This throws a catchable runtime IO exception, which is used in the tests.

collectTokensSafe :: forall a b. (Loc b, Tok a, LastToken b a, Show a) => Parse b a a -> ParseState b -> Maybe [a] Source #

collectTokens :: forall a b. (Loc b, Tok a, LastToken b a, Show a) => Parse b a a -> ParseState b -> [a] Source #

throwIOLeft :: (Exception e, MonadIO m) => Either e a -> m a Source #

May be used to lift parse results into IO and force unwrap.

F77 with inlined includes

The Fortran 77 parser can parse and inline includes at parse time. Parse errors are thrown as IO exceptions.

Can be cleaned up and generalized to use for other parsers.