| Safe Haskell | Safe-Inferred |
|---|---|
| Language | Haskell2010 |
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
- newtype InfixExpr = InfixExpr (LHsExpr GhcPs)
- newtype InfixOp = InfixOp RdrName
- newtype PrefixOp = PrefixOp RdrName
- data InfixApp = InfixApp {}
- data GRHSsExpr = GRHSsExpr {}
- data GRHSExpr = GRHSExpr {}
- newtype GRHSProc = GRHSProc (GRHS GhcPs (LHsCmd GhcPs))
- newtype RecConPat = RecConPat (HsRecFields GhcPs (LPat GhcPs))
- newtype RecConField = RecConField (HsFieldBind (LFieldOcc GhcPs) (LPat GhcPs))
- data HsSigType' = HsSigType' {}
- pattern HsSigTypeInsideInstDecl :: HsSigType GhcPs -> HsSigType'
- pattern HsSigTypeInsideVerticalFuncSig :: HsSigType GhcPs -> HsSigType'
- pattern HsSigTypeInsideDeclSig :: HsSigType GhcPs -> HsSigType'
- data HsType' = HsType' {}
- pattern HsTypeInsideVerticalFuncSig :: HsType GhcPs -> HsType'
- pattern HsTypeInsideDeclSig :: HsType GhcPs -> HsType'
- pattern HsTypeInsideInstDecl :: HsType GhcPs -> HsType'
- pattern HsTypeWithVerticalAppTy :: HsType GhcPs -> HsType'
- data DataFamInstDecl' = DataFamInstDecl' {}
- pattern DataFamInstDeclTopLevel :: DataFamInstDecl GhcPs -> DataFamInstDecl'
- pattern DataFamInstDeclInsideClassInst :: DataFamInstDecl GhcPs -> DataFamInstDecl'
- data FamEqn' = FamEqn' {}
- pattern FamEqnTopLevel :: FamEqn GhcPs (HsDataDefn GhcPs) -> FamEqn'
- pattern FamEqnInsideClassInst :: FamEqn GhcPs (HsDataDefn GhcPs) -> FamEqn'
- newtype StmtLRInsideVerticalList = StmtLRInsideVerticalList (StmtLR GhcPs GhcPs (LHsExpr GhcPs))
- newtype ParStmtBlockInsideVerticalList = ParStmtBlockInsideVerticalList (ParStmtBlock GhcPs GhcPs)
- newtype DeclSig = DeclSig (Sig GhcPs)
- newtype TopLevelTyFamInstDecl = TopLevelTyFamInstDecl (TyFamInstDecl GhcPs)
- newtype Context = Context (LHsContext GhcPs)
- newtype HorizontalContext = HorizontalContext (LHsContext GhcPs)
- newtype VerticalContext = VerticalContext (LHsContext GhcPs)
- newtype ModuleNameWithPrefix = ModuleNameWithPrefix ModuleName
- newtype PatInsidePatDecl = PatInsidePatDecl (Pat GhcPs)
- data LambdaCase = LambdaCase {}
- newtype ModuleDeprecatedPragma = ModuleDeprecatedPragma (WarningTxt GhcPs)
- data ListComprehension = ListComprehension {}
- data DoExpression = DoExpression {}
- data DoOrMdo
- data LetIn = LetIn {}
- data NodeComments = NodeComments {}
- data GRHSExprType
- data GRHSProcType
- data HsTypeFor
- data HsTypeDir
- data CaseOrCases
- data DataFamInstDeclFor
Documentation
LHsExpr used as a infix operator
Instances
| CommentExtraction InfixExpr Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: InfixExpr -> NodeComments Source # | |
Instances
| CommentExtraction InfixOp Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: InfixOp -> NodeComments Source # | |
A wrapper type for printing an identifier as a prefix operator.
Printing a PrefixOp value containing a symbol operator wraps it with
parentheses.
Instances
| CommentExtraction PrefixOp Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: PrefixOp -> NodeComments 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.
Constructors
| InfixApp | |
Instances
| CommentExtraction InfixApp Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: InfixApp -> NodeComments Source # | |
GRHSs with a label indicating in which context the RHS is located
in.
Constructors
| GRHSsExpr | |
Fields
| |
Instances
| CommentExtraction GRHSsExpr Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: GRHSsExpr -> NodeComments Source # | |
GRHS for a normal binding.
Constructors
| GRHSExpr | |
Fields
| |
Instances
| CommentExtraction GRHSExpr Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: GRHSExpr -> NodeComments Source # | |
GRHS for a proc binding.
Instances
| CommentExtraction GRHSProc Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: GRHSProc -> NodeComments Source # | |
A pattern match against a record.
Constructors
| RecConPat (HsRecFields GhcPs (LPat GhcPs)) |
Instances
| CommentExtraction RecConPat Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: RecConPat -> NodeComments Source # | |
newtype RecConField Source #
A record field in a pattern match.
Constructors
| RecConField (HsFieldBind (LFieldOcc GhcPs) (LPat GhcPs)) |
Instances
| CommentExtraction RecConField Source # | |
Defined in HIndent.Pretty.NodeComments Methods | |
data HsSigType' Source #
A wrapper for HsSigType.
Constructors
| HsSigType' | |
Fields
| |
Instances
| CommentExtraction HsSigType' Source # | |
Defined in HIndent.Pretty.NodeComments Methods | |
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.
A wrapper for HsType.
Constructors
| HsType' | |
Instances
| CommentExtraction HsType' Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: HsType' -> NodeComments Source # | |
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.
data DataFamInstDecl' Source #
A wrapper of DataFamInstDecl.
Constructors
| DataFamInstDecl' | |
Fields
| |
Instances
| CommentExtraction DataFamInstDecl' Source # | |
Defined in HIndent.Pretty.NodeComments Methods | |
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.
A wrapper for FamEqn.
Constructors
| FamEqn' | |
Fields
| |
Instances
| CommentExtraction FamEqn' Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: FamEqn' -> NodeComments Source # | |
pattern FamEqnTopLevel :: FamEqn GhcPs (HsDataDefn GhcPs) -> FamEqn' Source #
pattern FamEqnInsideClassInst :: FamEqn GhcPs (HsDataDefn GhcPs) -> FamEqn' Source #
newtype StmtLRInsideVerticalList Source #
StmtLR inside a vertically printed list.
Instances
| CommentExtraction StmtLRInsideVerticalList Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: StmtLRInsideVerticalList -> NodeComments Source # | |
newtype ParStmtBlockInsideVerticalList Source #
ParStmtBlock inside a vertically printed list.
Constructors
| ParStmtBlockInsideVerticalList (ParStmtBlock GhcPs GhcPs) |
Instances
A top-level function signature.
Instances
| CommentExtraction DeclSig Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: DeclSig -> NodeComments Source # | |
newtype TopLevelTyFamInstDecl Source #
A top-level type family instance declaration.
Constructors
| TopLevelTyFamInstDecl (TyFamInstDecl GhcPs) |
Instances
| CommentExtraction TopLevelTyFamInstDecl Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: TopLevelTyFamInstDecl -> NodeComments 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
| CommentExtraction Context Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: Context -> NodeComments Source # | |
newtype HorizontalContext Source #
A wrapper type for printing a context horizontally.
Constructors
| HorizontalContext (LHsContext GhcPs) |
Instances
| CommentExtraction HorizontalContext Source # | |
Defined in HIndent.Pretty.NodeComments Methods | |
newtype VerticalContext Source #
A wrapper type for printing a context vertically.
Constructors
| VerticalContext (LHsContext GhcPs) |
Instances
| CommentExtraction VerticalContext Source # | |
Defined in HIndent.Pretty.NodeComments Methods | |
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.
Constructors
| ModuleNameWithPrefix ModuleName |
Instances
| CommentExtraction ModuleNameWithPrefix Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: ModuleNameWithPrefix -> NodeComments Source # | |
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
| CommentExtraction PatInsidePatDecl Source # | |
Defined in HIndent.Pretty.NodeComments Methods | |
data LambdaCase Source #
Lambda case.
Constructors
| LambdaCase | |
Fields | |
Instances
| CommentExtraction LambdaCase Source # | |
Defined in HIndent.Pretty.NodeComments Methods | |
newtype ModuleDeprecatedPragma Source #
A deprecation pragma for a module.
Constructors
| ModuleDeprecatedPragma (WarningTxt GhcPs) |
Instances
| CommentExtraction ModuleDeprecatedPragma Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: ModuleDeprecatedPragma -> NodeComments Source # | |
data ListComprehension Source #
Use this type to pretty-print a list comprehension.
Constructors
| ListComprehension | |
Fields
| |
Instances
| CommentExtraction ListComprehension Source # | |
Defined in HIndent.Pretty.NodeComments Methods | |
data DoExpression Source #
Use this type to pretty-print a do expression.
Instances
| CommentExtraction DoExpression Source # | |
Defined in HIndent.Pretty.NodeComments Methods | |
Use this type to pretty-print a let ... in ... expression.
Instances
| CommentExtraction LetIn Source # | |
Defined in HIndent.Pretty.NodeComments Methods nodeComments :: LetIn -> NodeComments Source # | |
data NodeComments Source #
Comments belonging to an AST node.
Constructors
| NodeComments | |
Fields
| |
data GRHSExprType Source #
Values indicating in which context a RHS is located.
Constructors
| GRHSExprNormal | |
| GRHSExprCase | |
| GRHSExprMultiWayIf | |
| GRHSExprLambda |
Instances
| Eq GRHSExprType Source # | |
Defined in HIndent.Pretty.Types | |
data GRHSProcType Source #
Values indicating in which context a RHS in a proc expression is located.
Constructors
| GRHSProcCase | |
| GRHSProcLambda |
Values indicating in which context a HsType is located.
Values indicating how a node should be printed; either horizontally or vertically.
Constructors
| HsTypeNoDir | |
| HsTypeVertical |
data DataFamInstDeclFor Source #
Values indicating where a data family instance is declared.