Safe Haskell | None |
---|---|
Language | Haskell2010 |
ghc-exactprint
is a library to manage manipulating Haskell
source files. There are four components.
Synopsis
- relativiseApiAnns :: (Data (SrcSpanLess ast), Annotate ast, HasSrcSpan ast) => ast -> ApiAnns -> Anns
- relativiseApiAnnsWithComments :: (Data (SrcSpanLess ast), Annotate ast, HasSrcSpan ast) => [Comment] -> 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 AnnSpan AnnConName
- parseModule :: FilePath -> IO (ParseResult ParsedSource)
- module Language.Haskell.GHC.ExactPrint.Transform
- addAnnotationsForPretty :: Annotate a => [Comment] -> Located a -> Anns -> Anns
- exactPrint :: Annotate ast => Located ast -> Anns -> String
Relativising
relativiseApiAnns :: (Data (SrcSpanLess ast), Annotate ast, HasSrcSpan ast) => ast -> ApiAnns -> Anns Source #
Transform concrete annotations into relative annotations which are more useful when transforming an AST.
relativiseApiAnnsWithComments :: (Data (SrcSpanLess ast), Annotate ast, HasSrcSpan ast) => [Comment] -> 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
Instances
Eq Comment Source # | |
Data Comment Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Comment -> c Comment # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Comment # toConstr :: Comment -> Constr # dataTypeOf :: Comment -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Comment) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Comment) # gmapT :: (forall b. Data b => b -> b) -> Comment -> Comment # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Comment -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Comment -> r # gmapQ :: (forall d. Data d => d -> u) -> Comment -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Comment -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Comment -> m Comment # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment -> m Comment # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Comment -> m Comment # | |
Ord Comment Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types | |
Show Comment Source # | |
Outputable Comment Source # | |
data Annotation Source #
Ann | |
|
Instances
Eq Annotation Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types (==) :: Annotation -> Annotation -> Bool # (/=) :: Annotation -> Annotation -> Bool # | |
Show Annotation Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |
Outputable Annotation Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types ppr :: Annotation -> SDoc # pprPrec :: Rational -> Annotation -> SDoc # | |
Monad m => MonadState (Anns, Int) (TransformT m) Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Transform |
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
Instances
Eq AnnKey Source # | |
Data AnnKey Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> AnnKey -> c AnnKey # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnKey # toConstr :: AnnKey -> Constr # dataTypeOf :: AnnKey -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnKey) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnKey) # gmapT :: (forall b. Data b => b -> b) -> AnnKey -> AnnKey # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnKey -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnKey -> r # gmapQ :: (forall d. Data d => d -> u) -> AnnKey -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnKey -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnKey -> m AnnKey # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnKey -> m AnnKey # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnKey -> m AnnKey # | |
Ord AnnKey Source # | |
Show AnnKey Source # | |
Outputable AnnKey Source # | |
Monad m => MonadState (Anns, Int) (TransformT m) Source # | |
Defined in Language.Haskell.GHC.ExactPrint.Transform |
Parsing
parseModule :: FilePath -> IO (ParseResult 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.