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

Language.Fortran.PrettyPrint

Synopsis

Documentation

olderThan :: FortranVersion -> String -> FortranVersion -> a -> a Source #

Continue only if the given version is equal to or older than a "maximum" version, or emit a runtime error.

(<?>) :: Doc -> Doc -> Doc infixl 7 Source #

(<?+>) :: Doc -> Doc -> Doc infixl 7 Source #

printMaybe :: (a -> Doc) -> Maybe a -> Doc Source #

class IndentablePretty t where Source #

Instances

Instances details
Pretty a => IndentablePretty a Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

IndentablePretty (Block a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

IndentablePretty (ProgramFile a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

IndentablePretty (ProgramUnit a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

IndentablePretty (StructureItem a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

IndentablePretty (UnionMap a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

IndentablePretty a => IndentablePretty (Maybe a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

IndentablePretty [Block a] Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

IndentablePretty [ProgramUnit a] Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

class Pretty t where Source #

Methods

pprint' :: FortranVersion -> t -> Doc Source #

Instances

Instances details
Pretty BaseType Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty BinaryOp Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty Intent Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty Only Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty UnaryOp Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty SemType Source # 
Instance details

Defined in Language.Fortran.Analysis.SemanticTypes

Pretty String Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (AllocOpt a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (Argument a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (ArgumentExpression a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (Attribute a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (CommonGroup a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (ControlPair a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (DataGroup a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (Declarator a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (DimensionDeclarator a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (DoSpecification a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (Expression a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (FlushSpec a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (FormatItem a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (ImpElement a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (ImpList a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (Index a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (Namelist a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (ProcDecl a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (ProcInterface a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (Selector a) Source #

Note that this instance is tightly bound with TypeSpec due to Selector appending information on where TypeSpec should have been prettied. By itself, this instance is less sensible.

Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (Statement a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (Suffix a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (TypeSpec a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (Use a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Methods

pprint' :: FortranVersion -> Use a -> Doc Source #

Pretty (Value a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (KindParam a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (ComplexLit a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (ComplexPart a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty a => Pretty (Maybe a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Pretty (e a) => Pretty (AList e a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Methods

pprint' :: FortranVersion -> AList e a -> Doc Source #

(Pretty (t1 a), Pretty (t2 a)) => Pretty (ATuple t1 t2 a) Source # 
Instance details

Defined in Language.Fortran.PrettyPrint

Methods

pprint' :: FortranVersion -> ATuple t1 t2 a -> Doc Source #

noParensLit :: FortranVersion -> Expression a -> Doc Source #

Pretty print an Expression inside parentheses, _except_ if the Expression is an integer literal, in which case print without the parens.

data ReformatState Source #

Constructors

RefmtStNewline Int

Unsure yet whether current line it's a comment or statement.

RefmtStComment

Current line is a comment; no need to track column number.

RefmtStStmt Int

Current line is a statement.

reformatMixedFormInsertContinuations :: String -> String Source #

Add continuations where required to a pretty-printed program.

Ensures that no non-comment line exceeds 72 columns.

The reformatting should be compatible with fixed and free-form Fortran standards. See: http://fortranwiki.org/fortran/show/Continuation+lines

This is a simple, delicate algorithm that must only be used on pretty printer output, due to relying on particular parser & pretty printer behaviour. In particular, comments not beginning a line (e.g. after a statement or continuation) won't be picked up as a comment, so could wreck that line. Be warned if you're using it on piles of funky-looking code!

prettyError :: String -> a Source #

error wrapper to make it easier to swap this out for a monad later.