| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
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
- annotate :: (Annotate ast, Data (SrcSpanLess ast), HasSrcSpan ast) => ast -> Annotated ()
 - data AnnotationF next where
- 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, Data (SrcSpanLess a), HasSrcSpan a) => 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
 
 - type Annotated = FreeT AnnotationF Identity
 - class Data ast => Annotate ast where
 - withSortKeyContextsHelper :: Monad m => (Annotated () -> m ()) -> ListContexts -> [(SrcSpan, Annotated ())] -> m ()
 
Documentation
annotate :: (Annotate ast, Data (SrcSpanLess ast), HasSrcSpan ast) => 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 
MarkPrimfor the other interpreters. MarkEOF- Special constructor which marks the end of file marker.
 MarkExternal- TODO
 MarkOutside- A 
AnnKeywordIdwhich is precisely located but not inside the current context. This is usually used to reassociated locatedRdrNamewhich 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 
AnnKeywordIdwhich are seperated by differentAnnKeywordId. 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
 
annSortKeyfield inAnnotation. 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
Instances
| Functor AnnotationF Source # | |
Defined in Language.Haskell.GHC.ExactPrint.AnnotateTypes Methods fmap :: (a -> b) -> AnnotationF a -> AnnotationF b # (<$) :: a -> AnnotationF b -> AnnotationF a #  | |
class Data ast => Annotate ast where Source #
Instances
withSortKeyContextsHelper :: Monad m => (Annotated () -> m ()) -> ListContexts -> [(SrcSpan, Annotated ())] -> m () Source #