floskell-0.9.0: A flexible Haskell source code pretty printer

Safe HaskellNone
LanguageHaskell98

Floskell.Pretty

Synopsis

Documentation

run :: (a -> a -> Bool) -> [a] -> ([a], [a]) Source #

Like span, but comparing adjacent items.

runs :: (a -> a -> Bool) -> [a] -> [[a]] Source #

Like groupBy, but comparing adjacent items.

flattenApp :: Annotated ast => (ast NodeInfo -> Maybe (ast NodeInfo, ast NodeInfo)) -> ast NodeInfo -> [ast NodeInfo] Source #

flattenInfix :: (Annotated ast1, Annotated ast2) => (ast1 NodeInfo -> Maybe (ast1 NodeInfo, ast2 NodeInfo, ast1 NodeInfo)) -> ast1 NodeInfo -> (ast1 NodeInfo, [(ast2 NodeInfo, ast1 NodeInfo)]) Source #

type PrettyPrinter f = f NodeInfo -> Printer () Source #

Syntax shortcut for Pretty Printers.

prettyHSE :: Pretty (ast NodeInfo) => PrettyPrinter ast Source #

Pretty printing prettyHSE using haskell-src-exts pretty printer

class Pretty ast where Source #

Type class for pretty-printable types.

Minimal complete definition

Nothing

Instances
Pretty ModuleName Source # 
Instance details

Defined in Floskell.Pretty

Pretty QName Source # 
Instance details

Defined in Floskell.Pretty

Pretty Name Source # 
Instance details

Defined in Floskell.Pretty

Pretty IPName Source # 
Instance details

Defined in Floskell.Pretty

Pretty QOp Source # 
Instance details

Defined in Floskell.Pretty

Pretty Op Source # 
Instance details

Defined in Floskell.Pretty

Pretty Module Source # 
Instance details

Defined in Floskell.Pretty

Pretty ModuleHead Source # 
Instance details

Defined in Floskell.Pretty

Pretty ExportSpecList Source # 
Instance details

Defined in Floskell.Pretty

Pretty ExportSpec Source # 
Instance details

Defined in Floskell.Pretty

Pretty ImportDecl Source # 
Instance details

Defined in Floskell.Pretty

Pretty ImportSpecList Source # 
Instance details

Defined in Floskell.Pretty

Pretty ImportSpec Source # 
Instance details

Defined in Floskell.Pretty

Pretty Assoc Source # 
Instance details

Defined in Floskell.Pretty

Pretty Decl Source # 
Instance details

Defined in Floskell.Pretty

Pretty TypeEqn Source # 
Instance details

Defined in Floskell.Pretty

Pretty Annotation Source # 
Instance details

Defined in Floskell.Pretty

Pretty BooleanFormula Source # 
Instance details

Defined in Floskell.Pretty

Pretty DataOrNew Source # 
Instance details

Defined in Floskell.Pretty

Pretty InjectivityInfo Source # 
Instance details

Defined in Floskell.Pretty

Pretty ResultSig Source # 
Instance details

Defined in Floskell.Pretty

Pretty DeclHead Source # 
Instance details

Defined in Floskell.Pretty

Pretty InstRule Source # 
Instance details

Defined in Floskell.Pretty

Pretty InstHead Source # 
Instance details

Defined in Floskell.Pretty

Pretty Deriving Source # 
Instance details

Defined in Floskell.Pretty

Pretty DerivStrategy Source # 
Instance details

Defined in Floskell.Pretty

Pretty Binds Source # 
Instance details

Defined in Floskell.Pretty

Pretty IPBind Source # 
Instance details

Defined in Floskell.Pretty

Pretty Match Source # 
Instance details

Defined in Floskell.Pretty

Pretty QualConDecl Source # 
Instance details

Defined in Floskell.Pretty

Pretty ConDecl Source # 
Instance details

Defined in Floskell.Pretty

Pretty FieldDecl Source # 
Instance details

Defined in Floskell.Pretty

Pretty GadtDecl Source # 
Instance details

Defined in Floskell.Pretty

Pretty ClassDecl Source # 
Instance details

Defined in Floskell.Pretty

Pretty InstDecl Source # 
Instance details

Defined in Floskell.Pretty

Pretty BangType Source # 
Instance details

Defined in Floskell.Pretty

Pretty Unpackedness Source # 
Instance details

Defined in Floskell.Pretty

Pretty Rhs Source # 
Instance details

Defined in Floskell.Pretty

Pretty GuardedRhs Source # 
Instance details

Defined in Floskell.Pretty

Pretty Type Source # 
Instance details

Defined in Floskell.Pretty

Pretty TyVarBind Source # 
Instance details

Defined in Floskell.Pretty

Pretty Kind Source # 
Instance details

Defined in Floskell.Pretty

Pretty FunDep Source # 
Instance details

Defined in Floskell.Pretty

Pretty Context Source # 
Instance details

Defined in Floskell.Pretty

Pretty Asst Source # 
Instance details

Defined in Floskell.Pretty

Pretty Literal Source # 
Instance details

Defined in Floskell.Pretty

Pretty Exp Source # 
Instance details

Defined in Floskell.Pretty

Pretty XName Source # 
Instance details

Defined in Floskell.Pretty

Pretty XAttr Source # 
Instance details

Defined in Floskell.Pretty

Pretty Bracket Source # 
Instance details

Defined in Floskell.Pretty

Pretty Splice Source # 
Instance details

Defined in Floskell.Pretty

Pretty Safety Source # 
Instance details

Defined in Floskell.Pretty

Pretty CallConv Source # 
Instance details

Defined in Floskell.Pretty

Pretty ModulePragma Source # 
Instance details

Defined in Floskell.Pretty

Pretty Overlap Source # 
Instance details

Defined in Floskell.Pretty

Pretty Activation Source # 
Instance details

Defined in Floskell.Pretty

Pretty Rule Source # 
Instance details

Defined in Floskell.Pretty

Pretty RuleVar Source # 
Instance details

Defined in Floskell.Pretty

Pretty WarningText Source # 
Instance details

Defined in Floskell.Pretty

Pretty Pat Source # 
Instance details

Defined in Floskell.Pretty

Pretty PXAttr Source # 
Instance details

Defined in Floskell.Pretty

Pretty RPat Source # 
Instance details

Defined in Floskell.Pretty

Pretty PatField Source # 
Instance details

Defined in Floskell.Pretty

Pretty Stmt Source # 
Instance details

Defined in Floskell.Pretty

Pretty QualStmt Source # 
Instance details

Defined in Floskell.Pretty

Pretty FieldUpdate Source # 
Instance details

Defined in Floskell.Pretty

Pretty Alt Source # 
Instance details

Defined in Floskell.Pretty

Pretty CompactBinds Source # 
Instance details

Defined in Floskell.Pretty

Pretty GuardedAlts Source # 
Instance details

Defined in Floskell.Pretty

Pretty GuardedAlt Source # 
Instance details

Defined in Floskell.Pretty

(Annotated a, Pretty a) => Pretty (MayAst a) Source # 
Instance details

Defined in Floskell.Pretty

pretty :: (Annotated ast, Pretty ast) => PrettyPrinter ast Source #

Pretty print a syntax tree with annotated comments

noNodeInfo :: NodeInfo Source #

Empty NodeInfo

compareAST :: (Functor ast, Ord (ast ())) => ast NodeInfo -> ast NodeInfo -> Ordering Source #

Compare two AST nodes ignoring the annotation

filterComments :: Annotated a => (Maybe Location -> Bool) -> a NodeInfo -> [ComInfo] Source #

Return comments with matching location.

copyComments :: (Annotated ast1, Annotated ast2) => Location -> ast1 NodeInfo -> ast2 NodeInfo -> ast2 NodeInfo Source #

Copy comments from one AST node to another.

printComment :: Maybe SrcSpan -> Comment -> Printer () Source #

Pretty print a comment.

printComments :: Annotated ast => Location -> ast NodeInfo -> Printer () Source #

Print comments of a node.

opName :: QOp a -> ByteString Source #

Return the configuration name of an operator

opName' :: QName a -> ByteString Source #

Return the configuration name of an operator

lineDelta :: Annotated ast => ast NodeInfo -> ast NodeInfo -> Int Source #

linedFn :: Annotated ast => (ast NodeInfo -> Printer ()) -> [ast NodeInfo] -> Printer () Source #

lined :: (Annotated ast, Pretty ast) => [ast NodeInfo] -> Printer () Source #

linedOnside :: (Annotated ast, Pretty ast) => [ast NodeInfo] -> Printer () Source #

withComputedTabStop :: TabStop -> (AlignConfig -> Bool) -> (a -> Printer (Maybe [Int])) -> [a] -> Printer b -> Printer b Source #

moduleName :: ModuleName a -> String Source #

Extract the name as a String from a ModuleName

skipBlank :: Annotated ast => (ast NodeInfo -> ast NodeInfo -> Bool) -> ast NodeInfo -> ast NodeInfo -> Bool Source #

prettyDecls :: (Annotated ast, Pretty ast) => (ast NodeInfo -> ast NodeInfo -> Bool) -> [ast NodeInfo] -> Printer () Source #

prettySimpleDecl :: (Annotated ast1, Pretty ast1, Annotated ast2, Pretty ast2) => ast1 NodeInfo -> ByteString -> ast2 NodeInfo -> Printer () Source #

prettyConDecls :: (Annotated ast, Pretty ast) => [ast NodeInfo] -> Printer () Source #

prettyForall :: (Annotated ast, Pretty ast) => [ast NodeInfo] -> Printer () Source #

prettyApp :: (Annotated ast1, Annotated ast2, Pretty ast1, Pretty ast2) => ast1 NodeInfo -> [ast2 NodeInfo] -> Printer () Source #

prettyInfixApp :: (Annotated ast, Pretty ast, Pretty (op NodeInfo)) => (op NodeInfo -> ByteString) -> LayoutContext -> (ast NodeInfo, [(op NodeInfo, ast NodeInfo)]) -> Printer () Source #

prettyRecord :: (Annotated ast1, Pretty ast1, Annotated ast2, Pretty ast2) => (ast2 NodeInfo -> Printer (Maybe Int)) -> LayoutContext -> ast1 NodeInfo -> [ast2 NodeInfo] -> Printer () Source #

newtype GuardedAlt l Source #

Constructors

GuardedAlt (GuardedRhs l) 
Instances
Functor GuardedAlt Source # 
Instance details

Defined in Floskell.Pretty

Methods

fmap :: (a -> b) -> GuardedAlt a -> GuardedAlt b #

(<$) :: a -> GuardedAlt b -> GuardedAlt a #

Annotated GuardedAlt Source # 
Instance details

Defined in Floskell.Pretty

Methods

ann :: GuardedAlt l -> l #

amap :: (l -> l) -> GuardedAlt l -> GuardedAlt l #

Pretty GuardedAlt Source # 
Instance details

Defined in Floskell.Pretty

newtype GuardedAlts l Source #

Constructors

GuardedAlts (Rhs l) 
Instances
Functor GuardedAlts Source # 
Instance details

Defined in Floskell.Pretty

Methods

fmap :: (a -> b) -> GuardedAlts a -> GuardedAlts b #

(<$) :: a -> GuardedAlts b -> GuardedAlts a #

Annotated GuardedAlts Source # 
Instance details

Defined in Floskell.Pretty

Methods

ann :: GuardedAlts l -> l #

amap :: (l -> l) -> GuardedAlts l -> GuardedAlts l #

Pretty GuardedAlts Source # 
Instance details

Defined in Floskell.Pretty

newtype CompactBinds l Source #

Constructors

CompactBinds (Binds l) 
Instances
Functor CompactBinds Source # 
Instance details

Defined in Floskell.Pretty

Methods

fmap :: (a -> b) -> CompactBinds a -> CompactBinds b #

(<$) :: a -> CompactBinds b -> CompactBinds a #

Annotated CompactBinds Source # 
Instance details

Defined in Floskell.Pretty

Methods

ann :: CompactBinds l -> l #

amap :: (l -> l) -> CompactBinds l -> CompactBinds l #

Pretty CompactBinds Source # 
Instance details

Defined in Floskell.Pretty

newtype MayAst a l Source #

Constructors

MayAst (Maybe (a l)) 
Instances
Functor a => Functor (MayAst a) Source # 
Instance details

Defined in Floskell.Pretty

Methods

fmap :: (a0 -> b) -> MayAst a a0 -> MayAst a b #

(<$) :: a0 -> MayAst a b -> MayAst a a0 #

Annotated a => Annotated (MayAst a) Source # 
Instance details

Defined in Floskell.Pretty

Methods

ann :: MayAst a l -> l #

amap :: (l -> l) -> MayAst a l -> MayAst a l #

(Annotated a, Pretty a) => Pretty (MayAst a) Source # 
Instance details

Defined in Floskell.Pretty