| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Language.Haskell.GHC.ExactPrint
Description
ghc-exactprint is a library to manage manipulating Haskell
 source files. There are four components.
Synopsis
- data Comment
- parseModule :: LibDir -> FilePath -> IO (ParseResult ParsedSource)
- module Language.Haskell.GHC.ExactPrint.Transform
- class Typeable a => ExactPrint a where- getAnnotationEntry :: a -> Entry
- setAnnotationAnchor :: a -> Anchor -> EpAnnComments -> a
- exact :: (Monad m, Monoid w) => a -> EP w m a
 
- exactPrint :: ExactPrint ast => ast -> String
- makeDeltaAst :: ExactPrint ast => ast -> ast
- showAst :: Data a => a -> String
- showAstData :: Data a => BlankSrcSpan -> BlankEpAnnotations -> a -> SDoc
- data BlankSrcSpan
- data BlankEpAnnotations
Types
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
| Data Comment Source # | |
| Defined in Language.Haskell.GHC.ExactPrint.Types Methods 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 # | |
| Show Comment Source # | |
| Outputable Comment Source # | |
| Defined in Language.Haskell.GHC.ExactPrint.Types | |
| Eq Comment Source # | |
| Ord Comment Source # | |
| Defined in Language.Haskell.GHC.ExactPrint.Types | |
Parsing
parseModule :: LibDir -> 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
Printing
class Typeable a => ExactPrint a where Source #
An AST fragment with an annotation must be able to return the
 requirements for nesting another one, captured in an Entry, and
 to be able to use the rest of the exactprint machinery to print the
 element.  In the analogy to Outputable, exact plays the role of
 ppr.
Methods
getAnnotationEntry :: a -> Entry Source #
setAnnotationAnchor :: a -> Anchor -> EpAnnComments -> a Source #
Instances
exactPrint :: ExactPrint ast => ast -> String Source #
Relativising
makeDeltaAst :: ExactPrint ast => ast -> ast Source #
Transform concrete annotations into relative annotations which
 are more useful when transforming an AST. This corresponds to the
 earlier relativiseApiAnns.
Dumping ASTs
Temporary copy from GHC, shows AnchorOps embedded in SrcSpan
showAstData :: Data a => BlankSrcSpan -> BlankEpAnnotations -> a -> SDoc Source #
Show a GHC syntax tree. This parameterised because it is also used for comparing ASTs in ppr roundtripping tests, where the SrcSpan's are blanked out, to avoid comparing locations, only structure
data BlankSrcSpan Source #
Constructors
| BlankSrcSpan | |
| BlankSrcSpanFile | |
| NoBlankSrcSpan | 
Instances
| Show BlankSrcSpan Source # | |
| Defined in Language.Haskell.GHC.ExactPrint.Dump Methods showsPrec :: Int -> BlankSrcSpan -> ShowS # show :: BlankSrcSpan -> String # showList :: [BlankSrcSpan] -> ShowS # | |
| Eq BlankSrcSpan Source # | |
| Defined in Language.Haskell.GHC.ExactPrint.Dump | |
data BlankEpAnnotations Source #
Constructors
| BlankEpAnnotations | |
| NoBlankEpAnnotations | 
Instances
| Show BlankEpAnnotations Source # | |
| Defined in Language.Haskell.GHC.ExactPrint.Dump Methods showsPrec :: Int -> BlankEpAnnotations -> ShowS # show :: BlankEpAnnotations -> String # showList :: [BlankEpAnnotations] -> ShowS # | |
| Eq BlankEpAnnotations Source # | |
| Defined in Language.Haskell.GHC.ExactPrint.Dump Methods (==) :: BlankEpAnnotations -> BlankEpAnnotations -> Bool # (/=) :: BlankEpAnnotations -> BlankEpAnnotations -> Bool # | |