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

HIndent.Pretty.NodeComments

Description

Comment handling around an AST node

Synopsis

Documentation

class CommentExtraction a where Source #

An interface to extract comments from an AST node.

Instances

Instances details
CommentExtraction Role Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction HsSrcBang Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction SrcStrictness Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction SrcUnpackedness Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction HsModule Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction XViaStrategyPs Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction Anchor Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction EpaComment Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction EpaCommentTok Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction InlinePragma Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction InlineSpec Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction OverlapMode Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction Fixity Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction FixityDirection Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction CCallConv Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction CExportSpec Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction Safety Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction OccName Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction RdrName Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction FractionalLit Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction IntegralLit Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction StringLiteral Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction SrcSpan Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction ModuleName Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction ForeignExport Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction ForeignImport Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction OverLitVal Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction HsIPName Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction HsTyLit Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction SigBindFamily Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction Context Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction DataFamInstDecl' Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction DeclSig Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction DoExpression Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction FamEqn' Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction GRHSExpr Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction GRHSProc Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction GRHSsExpr Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction HorizontalContext Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction HsSigType' Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction HsType' Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction InfixApp Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction InfixExpr Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction InfixOp Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction LambdaCase Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction LetIn Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction ListComprehension Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction ModuleDeprecatedPragma Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction ModuleNameWithPrefix Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction ParStmtBlockInsideVerticalList Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction PatInsidePatDecl Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction PrefixOp Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction RecConField Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction RecConPat Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction StmtLRInsideVerticalList Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction TopLevelTyFamInstDecl Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction VerticalContext Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (BooleanFormula a) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (IE GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (IEWrappedName RdrName) Source #

Pretty for 'LIEWrappedName (IdP GhcPs)'

Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (ImportDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (EpAnn a) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (SrcAnn a) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (FixitySig GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsBind GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsIPBinds GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsPatSynDir GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (IPBind GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (RecordPatSynField GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (Sig GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (AnnDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (ClsInstDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (ConDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (DataFamInstDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (DefaultDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (DerivClauseTys GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (DerivDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (DerivStrategy GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (FamilyDecl GhcPs) Source #

This instance is for type family declarations inside a class declaration.

Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (FamilyResultSig GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (ForeignDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsDataDefn GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsDerivingClause GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (InjectivityAnn GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (InstDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (RoleAnnotDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (RuleBndr GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (RuleDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (RuleDecls GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (SpliceDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (StandaloneKindSig GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (TyClDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (TyFamInstDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (WarnDecl GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (WarnDecls GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (ArithSeqInfo GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (DotFieldOcc GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (FieldLabelStrings GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsCmd GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsCmdTop GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsExpr GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsMatchContext GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsPragE GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsQuote GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsSplice GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsTupArg GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsLit GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsOverLit GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (Pat GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (AmbiguousFieldOcc GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (ConDeclField GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (FieldOcc GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsForAllTelescope GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsOuterSigTyVarBndrs GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsPatSigType GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsSigType GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsType GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (WithHsDocIdentifiers StringLiteral GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction l => CommentExtraction (GenLocated l e) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsLocalBindsLR GhcPs GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsValBindsLR GhcPs GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (PatSynBind GhcPs GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (FamEqn GhcPs (GenLocated SrcSpanAnnA (HsType GhcPs))) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (FamEqn GhcPs (HsDataDefn GhcPs)) Source #

Pretty-print a data instance.

Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (GRHS GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (GRHSs GhcPs a) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (Match GhcPs a) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (MatchGroup GhcPs a) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (ParStmtBlock GhcPs GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsFieldBind (GenLocated (SrcAnn NoEpAnns) (FieldOcc GhcPs)) (GenLocated SrcSpanAnnA (HsExpr GhcPs))) Source #

For record updates.

Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsFieldBind (GenLocated (SrcAnn NoEpAnns) (FieldOcc GhcPs)) (GenLocated SrcSpanAnnA (Pat GhcPs))) Source #

For pattern matchings against records.

Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsRecFields GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))) Source #

For record updates

Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsRecFields GhcPs (GenLocated SrcSpanAnnA (Pat GhcPs))) Source #

For pattern matching.

Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsArg (GenLocated SrcSpanAnnA (HsType GhcPs)) (GenLocated SrcSpanAnnA (HsType GhcPs))) Source #

HsArg (LHsType GhcPs) (LHsType GhcPs)

Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsScaled GhcPs a) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsTyVarBndr a GhcPs) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsWildCardBndrs GhcPs (GenLocated SrcSpanAnnA (HsSigType GhcPs))) Source #

Pretty for 'LHsSigWcType GhcPs'.

Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsWildCardBndrs GhcPs (GenLocated SrcSpanAnnA (HsType GhcPs))) Source #

Pretty for LHsWcType

Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsCmd GhcPs))) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (StmtLR GhcPs GhcPs (GenLocated SrcSpanAnnA (HsExpr GhcPs))) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsConDetails Void (GenLocated SrcSpanAnnN RdrName) [RecordPatSynField GhcPs]) Source #

Pretty for HsPatSynDetails.

Instance details

Defined in HIndent.Pretty.NodeComments

CommentExtraction (HsConDetails Void (HsScaled GhcPs (GenLocated SrcSpanAnnA (BangType GhcPs))) (GenLocated SrcSpanAnnL [GenLocated SrcSpanAnnA (ConDeclField GhcPs)])) Source # 
Instance details

Defined in HIndent.Pretty.NodeComments

emptyNodeComments :: NodeComments Source #

A NodeComment with no comments.