Safe Haskell | None |
---|---|
Language | Haskell2010 |
ghc-exactprint
is a library to manage manipulating Haskell
source files. There are four components.
- relativiseApiAnns :: Annotate ast => Located ast -> ApiAnns -> Anns
- relativiseApiAnnsWithComments :: Annotate ast => [Comment] -> Located ast -> ApiAnns -> Anns
- type Anns = Map AnnKey Annotation
- data Comment
- data Annotation = Ann {
- annEntryDelta :: !DeltaPos
- annPriorComments :: ![(Comment, DeltaPos)]
- annFollowingComments :: ![(Comment, DeltaPos)]
- annsDP :: ![(KeywordId, DeltaPos)]
- annSortKey :: !(Maybe [SrcSpan])
- annCapturedSpan :: !(Maybe AnnKey)
- data AnnKey = AnnKey SrcSpan AnnConName
- parseModule :: FilePath -> IO (Either (SrcSpan, String) (Anns, ParsedSource))
- module Language.Haskell.GHC.ExactPrint.Transform
- addAnnotationsForPretty :: Annotate a => [Comment] -> Located a -> Anns -> Anns
- exactPrint :: Annotate ast => Located ast -> Anns -> String
Relativising
relativiseApiAnns :: Annotate ast => Located ast -> ApiAnns -> Anns Source #
Transform concrete annotations into relative annotations which are more useful when transforming an AST.
relativiseApiAnnsWithComments :: Annotate ast => [Comment] -> Located ast -> ApiAnns -> Anns Source #
Exactly the same as relativiseApiAnns
but with the possibilty to
inject comments. This is typically used if the source has been preprocessed
by e.g. CPP, and the parts stripped out of the original source are re-added
as comments so they are not lost for round tripping.
type Anns = Map AnnKey Annotation Source #
This structure holds a complete set of annotations for an AST
A Haskell comment. The AnnKeywordId
is present if it has been converted
from an AnnKeywordId
because the annotation must be interleaved into the
stream and does not have a well-defined position
data Annotation Source #
Ann | |
|
Eq Annotation Source # | |
Show Annotation Source # | |
Outputable Annotation Source # | |
Monad m => MonadState (Anns, Int) (TransformT m) # | |
For every Located a
, use the SrcSpan
and constructor name of
a as the key, to store the standard annotation.
These are used to maintain context in the AP and EP monads
Parsing
parseModule :: FilePath -> IO (Either (SrcSpan, String) (Anns, ParsedSource)) Source #
This entry point will also work out which language extensions are required and perform CPP processing if necessary.
parseModule = parseModuleWithCpp defaultCppOptions
Note: ParsedSource
is a synonym for Located
(HsModule
GhcPs
)
Transformation
Adding default annotations
addAnnotationsForPretty :: Annotate a => [Comment] -> Located a -> Anns -> Anns Source #
Add any missing annotations so that the full AST element will exactprint properly when done.
Printing
exactPrint :: Annotate ast => Located ast -> Anns -> String Source #
Print an AST with a map of potential modified Anns
. The usual way to
generate such a map is by using one of the parsers in
Language.Haskell.GHC.ExactPrint.Parsers.