hindent-6.0.0: Extensible Haskell pretty printer
Safe HaskellSafe-Inferred
LanguageHaskell2010

HIndent.Pretty.Types

Description

Types to pretty-print certain parts of Haskell codes.

We define new types to pretty-print AST nodes rather than define functions to print comments easily using the Pretty implementation of GenLocated.

Synopsis

Documentation

newtype InfixExpr Source #

LHsExpr used as a infix operator

Constructors

InfixExpr (LHsExpr GhcPs) 

Instances

Instances details
CommentExtraction InfixExpr Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

newtype InfixOp Source #

Constructors

InfixOp RdrName 

Instances

Instances details
CommentExtraction InfixOp Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

newtype PrefixOp Source #

A wrapper type for printing an identifier as a prefix operator.

Printing a PrefixOp value containing a symbol operator wraps it with parentheses.

Constructors

PrefixOp RdrName 

Instances

Instances details
CommentExtraction PrefixOp Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

data InfixApp Source #

An infix operator application.

immediatelyAfterDo is True if an application is next to a `do` keyword. It needs an extra indent in such cases because

do a
* b

is not a valid Haskell code.

Instances

Instances details
CommentExtraction InfixApp Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

data GRHSsExpr Source #

GRHSs with a label indicating in which context the RHS is located in.

Instances

Instances details
CommentExtraction GRHSsExpr Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

data GRHSExpr Source #

GRHS for a normal binding.

Instances

Instances details
CommentExtraction GRHSExpr Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

newtype GRHSProc Source #

GRHS for a proc binding.

Constructors

GRHSProc (GRHS GhcPs (LHsCmd GhcPs)) 

Instances

Instances details
CommentExtraction GRHSProc Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

newtype RecConPat Source #

A pattern match against a record.

Instances

Instances details
CommentExtraction RecConPat Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

newtype RecConField Source #

A record field in a pattern match.

Instances

Instances details
CommentExtraction RecConField Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

data HsSigType' Source #

A wrapper for HsSigType.

Constructors

HsSigType' 

Fields

Instances

Instances details
CommentExtraction HsSigType' Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

pattern HsSigTypeInsideInstDecl :: HsSigType GhcPs -> HsSigType' Source #

HsSigType' for instance declarations.

pattern HsSigTypeInsideVerticalFuncSig :: HsSigType GhcPs -> HsSigType' Source #

HsSigType' for function declarations; printed horizontally.

pattern HsSigTypeInsideDeclSig :: HsSigType GhcPs -> HsSigType' Source #

HsSigType' for a top-level function signature.

data HsType' Source #

A wrapper for HsType.

Constructors

HsType' 

Fields

Instances

Instances details
CommentExtraction HsType' Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

pattern HsTypeInsideVerticalFuncSig :: HsType GhcPs -> HsType' Source #

HsType' inside a function signature declaration; printed horizontally.

pattern HsTypeInsideDeclSig :: HsType GhcPs -> HsType' Source #

HsType' inside a top-level function signature declaration.

pattern HsTypeInsideInstDecl :: HsType GhcPs -> HsType' Source #

HsType' inside a instance signature declaration.

pattern HsTypeWithVerticalAppTy :: HsType GhcPs -> HsType' Source #

HsType' to pretty-print a HsAppTy vertically.

data DataFamInstDecl' Source #

A wrapper of DataFamInstDecl.

Constructors

DataFamInstDecl' 

Fields

Instances

Instances details
CommentExtraction DataFamInstDecl' Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

pattern DataFamInstDeclTopLevel :: DataFamInstDecl GhcPs -> DataFamInstDecl' Source #

DataFamInstDecl' wrapping a DataFamInstDecl representing a top-level data family instance.

pattern DataFamInstDeclInsideClassInst :: DataFamInstDecl GhcPs -> DataFamInstDecl' Source #

DataFamInstDecl' wrapping a DataFamInstDecl representing a data family instance inside a class instance.

data FamEqn' Source #

A wrapper for FamEqn.

Constructors

FamEqn' 

Fields

Instances

Instances details
CommentExtraction FamEqn' Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

pattern FamEqnTopLevel :: FamEqn GhcPs (HsDataDefn GhcPs) -> FamEqn' Source #

FamEqn' wrapping a FamEqn representing a top-level data family instance.

pattern FamEqnInsideClassInst :: FamEqn GhcPs (HsDataDefn GhcPs) -> FamEqn' Source #

FamEqn' wrapping a FamEqn representing a data family instance inside a class instance.

newtype DeclSig Source #

A top-level function signature.

Constructors

DeclSig (Sig GhcPs) 

Instances

Instances details
CommentExtraction DeclSig Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

newtype TopLevelTyFamInstDecl Source #

A top-level type family instance declaration.

newtype Context Source #

A wrapper type for type class constraints; e.g., (Eq a, Ord a) of (Eq a, Ord a) => [a] -> [a]. Either HorizontalContext or VerticalContext is used internally.

Constructors

Context (LHsContext GhcPs) 

Instances

Instances details
CommentExtraction Context Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

newtype HorizontalContext Source #

A wrapper type for printing a context horizontally.

newtype VerticalContext Source #

A wrapper type for printing a context vertically.

Instances

Instances details
CommentExtraction VerticalContext Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

newtype ModuleNameWithPrefix Source #

A wrapper type for pretty-printing a value of ModuleName with the module prefix.

Pretty-printing it via (string "module " >> pretty (name :: ModuleName)) locates comments before name in the same line as module and the name will be in the next line. This type is to avoid the problem.

newtype PatInsidePatDecl Source #

A wrapper for LPat inside a pattern declaration. Here, all infix patterns have extra spaces around the operators, like x : xs.

Constructors

PatInsidePatDecl (Pat GhcPs) 

Instances

Instances details
CommentExtraction PatInsidePatDecl Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

data LambdaCase Source #

Lambda case.

Instances

Instances details
CommentExtraction LambdaCase Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

newtype ModuleDeprecatedPragma Source #

A deprecation pragma for a module.

data ListComprehension Source #

Use this type to pretty-print a list comprehension.

Constructors

ListComprehension 

Fields

data DoExpression Source #

Use this type to pretty-print a do expression.

Constructors

DoExpression 

Instances

Instances details
CommentExtraction DoExpression Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

data DoOrMdo Source #

Values indicating whether `do` or mdo is used.

Constructors

Do 
Mdo 

data LetIn Source #

Use this type to pretty-print a let ... in ... expression.

Constructors

LetIn 

Instances

Instances details
CommentExtraction LetIn Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

data NodeComments Source #

Comments belonging to an AST node.

data GRHSExprType Source #

Values indicating in which context a RHS is located.

Instances

Instances details
Eq GRHSExprType Source # 
Instance details

Defined in HIndent.Pretty.Types

data GRHSProcType Source #

Values indicating in which context a RHS in a proc expression is located.

data HsTypeFor Source #

Values indicating in which context a HsType is located.

data HsTypeDir Source #

Values indicating how a node should be printed; either horizontally or vertically.

data CaseOrCases Source #

Values indicating whether `case` or cases is used.

Constructors

Case 
Cases 

data DataFamInstDeclFor Source #

Values indicating where a data family instance is declared.