ghc-exactprint-0.5.6.1: 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.
MarkPPOptional
Used to flag elements, such as optional braces, that are not used in the pretty printer. This functions identically to MarkPrim for the other interpreters.
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 
MarkPPOptional :: AnnKeywordId -> Maybe String -> next -> AnnotationF next 
MarkEOF :: next -> AnnotationF next 
MarkExternal :: SrcSpan -> AnnKeywordId -> String -> next -> AnnotationF next 
MarkInstead :: AnnKeywordId -> KeywordId -> next -> AnnotationF next 
MarkOutside :: AnnKeywordId -> KeywordId -> next -> AnnotationF next 
MarkInside :: AnnKeywordId -> next -> AnnotationF next 
MarkMany :: AnnKeywordId -> next -> AnnotationF next 
MarkManyOptional :: AnnKeywordId -> next -> AnnotationF next 
MarkOffsetPrim :: AnnKeywordId -> Int -> Maybe String -> next -> AnnotationF next 
MarkOffsetPrimOptional :: 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 
MarkAnnBeforeAnn :: AnnKeywordId -> AnnKeywordId -> next -> AnnotationF next 
StoreOriginalSrcSpan :: SrcSpan -> AnnKey -> (AnnKey -> next) -> AnnotationF next 
GetSrcSpanForKw :: SrcSpan -> AnnKeywordId -> (SrcSpan -> next) -> AnnotationF next 
AnnotationsToComments :: [AnnKeywordId] -> next -> AnnotationF next 
SetContextLevel :: Set AstContext -> Int -> Annotated () -> next -> AnnotationF next 
UnsetContext :: AstContext -> Annotated () -> next -> AnnotationF next 
IfInContext :: Set AstContext -> Annotated () -> Annotated () -> next -> AnnotationF next 
WithSortKeyContexts :: ListContexts -> [(SrcSpan, Annotated ())] -> next -> AnnotationF next 
TellContext :: Set AstContext -> 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 #

Minimal complete definition

markAST

Methods

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

Instances

Annotate DocDecl Source # 
Annotate HsLit Source # 

Methods

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

Annotate HsIPName Source # 
Annotate RdrName Source # 
Annotate Safety Source # 

Methods

markAST :: SrcSpan -> Safety -> Annotated () Source #

Annotate CExportSpec Source # 
Annotate CCallConv Source # 
Annotate CType Source # 

Methods

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

Annotate StringLiteral Source # 
Annotate WarningTxt Source # 
Annotate DerivStrategy Source # 
Annotate OverlapMode Source # 
Annotate HsDocString Source # 
Annotate ModuleName Source # 
Annotate FastString Source # 
Annotate Name Source # 

Methods

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

Annotate [ExprLStmt RdrName] Source #

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

Annotate [LHsDerivingClause RdrName] Source # 
Annotate [LHsType RdrName] Source # 
Annotate [LHsSigType RdrName] Source # 
Annotate [LConDeclField RdrName] Source # 
(DataId name, HasOccName name, Annotate name) => Annotate [LIE name] Source # 

Methods

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

Annotate body => Annotate [Located (Match RdrName (Located body))] Source # 

Methods

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

Annotate [Located (StmtLR RdrName RdrName (LHsCmd RdrName))] Source # 
Annotate (Maybe Role) Source # 
Annotate (HsModule RdrName) Source # 
Annotate (HsTupArg RdrName) Source # 
Annotate (HsCmdTop RdrName) Source # 
Annotate (HsDecl RdrName) Source # 
Annotate (SpliceDecl RdrName) Source # 
Annotate (TyClDecl RdrName) Source # 
Annotate (FamilyResultSig RdrName) Source # 
Annotate (FamilyDecl RdrName) Source # 
(DataId name, Annotate name) => Annotate (InjectivityAnn name) Source # 
Annotate (HsDerivingClause RdrName) Source # 
Annotate (ConDecl RdrName) Source # 
Annotate (TyFamInstEqn RdrName) Source # 
Annotate (TyFamDefltEqn RdrName) Source # 
Annotate (TyFamInstDecl RdrName) Source # 
Annotate (DataFamInstDecl RdrName) Source # 
Annotate (ClsInstDecl RdrName) Source # 
Annotate (InstDecl RdrName) Source # 
Annotate (DerivDecl RdrName) Source # 
Annotate (DefaultDecl RdrName) Source # 
Annotate (ForeignDecl RdrName) Source # 
Annotate (RuleDecls RdrName) Source # 
Annotate (RuleDecl RdrName) Source # 
Annotate (RuleBndr RdrName) Source # 
Annotate (VectDecl RdrName) 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 #

Annotate (AnnDecl RdrName) Source # 
Annotate name => Annotate (RoleAnnotDecl name) Source # 

Methods

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

Annotate (HsRecUpdField RdrName) Source # 
Annotate (HsLocalBinds RdrName) Source # 
Annotate (HsBind RdrName) Source # 
Annotate (IPBind RdrName) Source # 
Annotate (Sig RdrName) Source # 
DataId name => Annotate (HsOverLit name) Source # 

Methods

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

Annotate (HsTyVarBndr RdrName) Source # 
Annotate (HsType RdrName) Source # 
Annotate (HsAppType RdrName) Source # 
Annotate (ConDeclField RdrName) Source # 
DataId name => Annotate (FieldOcc name) Source # 

Methods

markAST :: SrcSpan -> FieldOcc name -> Annotated () Source #

DataId name => Annotate (AmbiguousFieldOcc name) Source # 
Annotate (HsExpr RdrName) Source # 
Annotate (HsCmd RdrName) Source # 
Annotate (HsSplice RdrName) Source # 
Annotate (Pat RdrName) Source # 
(DataId name, Annotate name) => Annotate (FunDep (Located name)) Source # 

Methods

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

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

Methods

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

(DataId name, HasOccName name, Annotate name) => Annotate (IEWrappedName name) Source # 

Methods

markAST :: SrcSpan -> IEWrappedName name -> Annotated () Source #

(DataId name, HasOccName 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 # 
Annotate body => Annotate (Match RdrName (Located body)) Source # 

Methods

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

Annotate body => Annotate (GRHS RdrName (Located body)) Source # 

Methods

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

Annotate body => Annotate (Stmt RdrName (Located body)) Source # 

Methods

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

Annotate (ParStmtBlock RdrName RdrName) Source # 
Annotate (HsRecField RdrName (LHsExpr RdrName)) Source # 
Annotate (HsRecField RdrName (LPat RdrName)) Source # 
(DataId name, Annotate arg) => Annotate (HsImplicitBndrs name (Located arg)) Source # 

Methods

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

withSortKeyContextsHelper :: Monad m => (Annotated () -> m ()) -> ListContexts -> [(SrcSpan, Annotated ())] -> m () Source #