ghc-exactprint-0.5.0.0: ExactPrint for GHC

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.GHC.ExactPrint.Annotate

Description

annotate is a function which given a GHC AST fragment, constructs a syntax tree which indicates which annotations belong to each specific part of the fragment.

Delta and Print provide two interpreters for this structure. You should probably use those unless you know what you're doing!

The functor AnnotationF has a number of constructors which correspond to different sitations which annotations can arise. It is hoped that in future versions of GHC these can be simplified by making suitable modifications to the AST.

Synopsis

Documentation

annotate :: Annotate ast => Located ast -> Annotated () Source

Construct a syntax tree which represent which KeywordIds must appear where.

data AnnotationF next where Source

MarkPrim
The main constructor. Marks that a specific AnnKeywordId could appear with an optional String which is used when printing.
MarkEOF
Special constructor which marks the end of file marker.
MarkExternal
TODO
MarkOutside
A AnnKeywordId which is precisely located but not inside the current context. This is usually used to reassociated located RdrName which are more naturally associated with their parent than in their own annotation.
MarkInside
The dual of MarkOutside. If we wish to mark a non-separating comma or semi-colon then we must use this constructor.
MarkMany
Some syntax elements allow an arbritary number of puncuation marks without reflection in the AST. This construction greedily takes all of the specified AnnKeywordId.
MarkOffsetPrim
Some syntax elements have repeated AnnKeywordId which are seperated by different AnnKeywordId. Thus using MarkMany is unsuitable and instead we provide an index to specify which specific instance to choose each time.
WithAST
TODO
CountAnns
Sometimes the AST does not reflect the concrete source code and the only way to tell what the concrete source was is to count a certain kind of AnnKeywordId.
WithSortKey
There are many places where the syntactic ordering of elements is thrown away by the AST. This constructor captures the original ordering and reflects any changes in ordered as specified by the annSortKey field in Annotation.
SetLayoutFlag
It is important to know precisely where layout rules apply. This constructor wraps a computation to indicate that LayoutRules apply to the corresponding construct.
StoreOriginalSrcSpan
TODO
GetSrcSpanFromKw
TODO
StoreString
TODO
AnnotationsToComments
Used when the AST is sufficiently vague that there is no other option but to convert a fragment of source code into a comment. This means it is impossible to edit such a fragment but means that processing files with such fragments is still possible.

Constructors

MarkPrim :: AnnKeywordId -> Maybe String -> next -> AnnotationF next 
MarkEOF :: next -> AnnotationF next 
MarkExternal :: SrcSpan -> AnnKeywordId -> String -> next -> AnnotationF next 
MarkOutside :: AnnKeywordId -> KeywordId -> next -> AnnotationF next 
MarkInside :: AnnKeywordId -> next -> AnnotationF next 
MarkMany :: AnnKeywordId -> next -> AnnotationF next 
MarkOffsetPrim :: AnnKeywordId -> Int -> Maybe String -> next -> AnnotationF next 
WithAST :: Data a => Located a -> Annotated b -> next -> AnnotationF next 
CountAnns :: AnnKeywordId -> (Int -> next) -> AnnotationF next 
WithSortKey :: [(SrcSpan, Annotated ())] -> next -> AnnotationF next 
SetLayoutFlag :: Rigidity -> Annotated () -> next -> AnnotationF next 
StoreOriginalSrcSpan :: AnnKey -> (AnnKey -> next) -> AnnotationF next 
GetSrcSpanForKw :: AnnKeywordId -> (SrcSpan -> next) -> AnnotationF next 
StoreString :: String -> SrcSpan -> next -> AnnotationF next 
AnnotationsToComments :: [AnnKeywordId] -> next -> AnnotationF next 

Instances

Functor AnnotationF Source 

Methods

fmap :: (a -> b) -> AnnotationF a -> AnnotationF b

(<$) :: a -> AnnotationF b -> AnnotationF a

class Data ast => Annotate ast where Source

Methods

markAST :: SrcSpan -> ast -> Annotated () Source

Instances

Annotate DocDecl Source 
Annotate HsIPName Source 
Annotate HsLit Source 

Methods

markAST :: SrcSpan -> HsLit -> Annotated () Source

Annotate RdrName Source 
Annotate HsDocString Source 
Annotate Safety Source 
Annotate CExportSpec Source 
Annotate CCallConv Source 
Annotate CType Source 

Methods

markAST :: SrcSpan -> CType -> Annotated () Source

Annotate WarningTxt Source 
Annotate OverlapMode Source 
Annotate Name Source 

Methods

markAST :: SrcSpan -> Name -> Annotated () Source

Annotate FastString Source 
Annotate ModuleName Source 
(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate [ExprLStmt name] Source

Used for declarations that need to be aligned together, e.g. in a do or let .. in statement/expr

Methods

markAST :: SrcSpan -> [ExprLStmt name] -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate [LHsType name] Source 

Methods

markAST :: SrcSpan -> [LHsType name] -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate [LConDeclField name] Source 

Methods

markAST :: SrcSpan -> [LConDeclField name] -> Annotated () Source

(DataId name, Annotate name) => Annotate [LIE name] Source 

Methods

markAST :: SrcSpan -> [LIE name] -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name, Annotate body) => Annotate [Located (Match name (Located body))] Source 

Methods

markAST :: SrcSpan -> [Located (Match name (Located body))] -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate [Located (StmtLR name name (LHsCmd name))] Source 

Methods

markAST :: SrcSpan -> [Located (StmtLR name name (LHsCmd name))] -> Annotated () Source

Annotate (Maybe Role) Source 
Annotate (HsModule RdrName) Source 
(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (HsTupArg name) Source 

Methods

markAST :: SrcSpan -> HsTupArg name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (HsCmdTop name) Source 

Methods

markAST :: SrcSpan -> HsCmdTop name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (HsDecl name) Source 

Methods

markAST :: SrcSpan -> HsDecl name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (SpliceDecl name) Source 

Methods

markAST :: SrcSpan -> SpliceDecl name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (TyClDecl name) Source 

Methods

markAST :: SrcSpan -> TyClDecl name -> Annotated () Source

(DataId name, Annotate name, OutputableBndr name, HasOccName name) => Annotate (FamilyDecl name) Source 

Methods

markAST :: SrcSpan -> FamilyDecl name -> Annotated () Source

(DataId name, Annotate name, OutputableBndr name, HasOccName name) => Annotate (ConDecl name) Source 

Methods

markAST :: SrcSpan -> ConDecl name -> Annotated () Source

(DataId name, Annotate name, OutputableBndr name, HasOccName name) => Annotate (TyFamInstEqn name) Source 

Methods

markAST :: SrcSpan -> TyFamInstEqn name -> Annotated () Source

(DataId name, Annotate name, OutputableBndr name, HasOccName name) => Annotate (TyFamDefltEqn name) Source 

Methods

markAST :: SrcSpan -> TyFamDefltEqn name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (TyFamInstDecl name) Source 

Methods

markAST :: SrcSpan -> TyFamInstDecl name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (DataFamInstDecl name) Source 
(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (ClsInstDecl name) Source 

Methods

markAST :: SrcSpan -> ClsInstDecl name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (InstDecl name) Source 

Methods

markAST :: SrcSpan -> InstDecl name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (DerivDecl name) Source 

Methods

markAST :: SrcSpan -> DerivDecl name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (DefaultDecl name) Source 

Methods

markAST :: SrcSpan -> DefaultDecl name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (ForeignDecl name) Source 

Methods

markAST :: SrcSpan -> ForeignDecl name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (RuleDecls name) Source 

Methods

markAST :: SrcSpan -> RuleDecls name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (RuleDecl name) Source 

Methods

markAST :: SrcSpan -> RuleDecl name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (RuleBndr name) Source 

Methods

markAST :: SrcSpan -> RuleBndr name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (VectDecl name) Source 

Methods

markAST :: SrcSpan -> VectDecl name -> Annotated () Source

Annotate name => Annotate (WarnDecls name) Source 

Methods

markAST :: SrcSpan -> WarnDecls name -> Annotated () Source

Annotate name => Annotate (WarnDecl name) Source 

Methods

markAST :: SrcSpan -> WarnDecl name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (AnnDecl name) Source 

Methods

markAST :: SrcSpan -> AnnDecl name -> Annotated () Source

Annotate name => Annotate (RoleAnnotDecl name) Source 

Methods

markAST :: SrcSpan -> RoleAnnotDecl name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (HsLocalBinds name) Source 

Methods

markAST :: SrcSpan -> HsLocalBinds name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (HsBind name) Source 

Methods

markAST :: SrcSpan -> HsBind name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (IPBind name) Source 

Methods

markAST :: SrcSpan -> IPBind name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (Sig name) Source 

Methods

markAST :: SrcSpan -> Sig name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (HsQuasiQuote name) Source 

Methods

markAST :: SrcSpan -> HsQuasiQuote name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (HsTyVarBndr name) Source 

Methods

markAST :: SrcSpan -> HsTyVarBndr name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (HsType name) Source 

Methods

markAST :: SrcSpan -> HsType name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (ConDeclField name) Source 

Methods

markAST :: SrcSpan -> ConDeclField name -> Annotated () Source

DataId name => Annotate (HsOverLit name) Source 

Methods

markAST :: SrcSpan -> HsOverLit name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (HsExpr name) Source 

Methods

markAST :: SrcSpan -> HsExpr name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (HsCmd name) Source 

Methods

markAST :: SrcSpan -> HsCmd name -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (HsSplice name) Source 

Methods

markAST :: SrcSpan -> HsSplice name -> Annotated () Source

(DataId name, Annotate name, OutputableBndr name, HasOccName name) => Annotate (Pat name) Source 

Methods

markAST :: SrcSpan -> Pat name -> Annotated () Source

(DataId name, Annotate name) => Annotate (FunDep (Located name)) Source 

Methods

markAST :: SrcSpan -> FunDep (Located name) -> Annotated () Source

(DataId name, Annotate name) => Annotate (ImportDecl name) Source 

Methods

markAST :: SrcSpan -> ImportDecl name -> Annotated () Source

(DataId name, Annotate name) => Annotate (IE name) Source 

Methods

markAST :: SrcSpan -> IE name -> Annotated () Source

Annotate name => Annotate (BooleanFormula (Located name)) Source 
Annotate (SourceText, FastString) Source 
(DataId name, OutputableBndr name, HasOccName name, Annotate name, Annotate body) => Annotate (Match name (Located body)) Source 

Methods

markAST :: SrcSpan -> Match name (Located body) -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name, Annotate body) => Annotate (GRHS name (Located body)) Source 

Methods

markAST :: SrcSpan -> GRHS name (Located body) -> Annotated () Source

(DataId name, OutputableBndr name, Annotate name, HasOccName name, Annotate body) => Annotate (Stmt name (Located body)) Source 

Methods

markAST :: SrcSpan -> Stmt name (Located body) -> Annotated () Source

(DataId name, OutputableBndr name, HasOccName name, Annotate name) => Annotate (ParStmtBlock name name) Source 

Methods

markAST :: SrcSpan -> ParStmtBlock name name -> Annotated () Source

(Annotate name, DataId name, OutputableBndr name, HasOccName name) => Annotate (HsRecField name (LHsExpr name)) Source 

Methods

markAST :: SrcSpan -> HsRecField name (LHsExpr name) -> Annotated () Source

(Annotate name, DataId name, OutputableBndr name, HasOccName name) => Annotate (HsRecField name (LPat name)) Source 

Methods

markAST :: SrcSpan -> HsRecField name (LPat name) -> Annotated () Source

(DataId name, Annotate arg) => Annotate (HsWithBndrs name (Located arg)) Source 

Methods

markAST :: SrcSpan -> HsWithBndrs name (Located arg) -> Annotated () Source