Safe Haskell | None |
---|---|
Language | Haskell2010 |
Provides consistent interface with ghc-exactprint.
Synopsis
- fix :: (Data ast, Monad m) => FixityEnv -> ast -> TransformT m ast
- parseContent :: FixityEnv -> FilePath -> String -> IO AnnotatedModule
- parseContentNoFixity :: FilePath -> String -> IO AnnotatedModule
- parseDecl :: String -> IO AnnotatedHsDecl
- parseExpr :: String -> IO AnnotatedHsExpr
- parseImports :: [String] -> IO AnnotatedImports
- parsePattern :: String -> IO AnnotatedPat
- parseStmt :: String -> IO AnnotatedStmt
- parseType :: String -> IO AnnotatedHsType
- addAllAnnsT :: (Data a, Data b, Monad m) => Located a -> Located b -> TransformT m ()
- cloneT :: (Data a, Typeable a, Monad m) => a -> TransformT m a
- setEntryDPT :: (Data a, Monad m) => Located a -> DeltaPos -> TransformT m ()
- swapEntryDPT :: (Data a, Data b, Monad m) => Located a -> Located b -> TransformT m ()
- transferAnnsT :: (Data a, Data b, Monad m) => (KeywordId -> Bool) -> Located a -> Located b -> TransformT m ()
- transferEntryAnnsT :: (Data a, Data b, Monad m) => (KeywordId -> Bool) -> Located a -> Located b -> TransformT m ()
- transferEntryDPT :: (Data a, Data b, Monad m) => Located a -> Located b -> TransformT m ()
- debugDump :: Annotate a => Annotated (Located a) -> IO ()
- debugParse :: String -> IO ()
- hasComments :: (Data a, Monad m) => Located a -> TransformT m Bool
- isComma :: KeywordId -> Bool
- module Retrie.ExactPrint.Annotated
- parseModule :: FilePath -> IO (Either (SrcSpan, String) (Anns, ParsedSource))
- relativiseApiAnnsWithComments :: Annotate ast => [Comment] -> Located ast -> ApiAnns -> Anns
- relativiseApiAnns :: Annotate ast => Located ast -> ApiAnns -> Anns
- addAnnotationsForPretty :: Annotate a => [Comment] -> Located a -> Anns -> Anns
- exactPrint :: Annotate ast => Located ast -> Anns -> String
- modifyDeclsT :: (HasDecls t, HasTransform m) => ([LHsDecl GhcPs] -> m [LHsDecl GhcPs]) -> t -> m t
- modifyValD :: HasTransform m => SrcSpan -> Decl -> (Match -> [Decl] -> m ([Decl], Maybe t)) -> m (Decl, Maybe t)
- replaceDeclsValbinds :: Monad m => HsLocalBinds GhcPs -> [LHsDecl GhcPs] -> TransformT m (HsLocalBinds GhcPs)
- hsDeclsValBinds :: Monad m => HsLocalBinds GhcPs -> TransformT m [LHsDecl GhcPs]
- hsDeclsGeneric :: (Data t, Monad m) => t -> TransformT m [LHsDecl GhcPs]
- hasDeclsSybTransform :: (Data t2, Monad m) => (forall t. HasDecls t => t -> m t) -> (LHsBind GhcPs -> m (LHsBind GhcPs)) -> t2 -> m t2
- replaceDeclsPatBind :: Monad m => LHsBind GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsBind GhcPs)
- replaceDeclsPatBindD :: Monad m => LHsDecl GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsDecl GhcPs)
- hsDeclsPatBind :: Monad m => LHsBind GhcPs -> TransformT m [LHsDecl GhcPs]
- hsDeclsPatBindD :: Monad m => LHsDecl GhcPs -> TransformT m [LHsDecl GhcPs]
- insertBefore :: HasDecls (Located ast) => Located old -> Located ast -> LHsDecl GhcPs -> Transform (Located ast)
- insertAfter :: HasDecls (Located ast) => Located old -> Located ast -> LHsDecl GhcPs -> Transform (Located ast)
- insertAtEnd :: HasDecls (Located ast) => Located ast -> LHsDecl GhcPs -> Transform (Located ast)
- insertAtStart :: HasDecls (Located ast) => Located ast -> LHsDecl GhcPs -> Transform (Located ast)
- moveTrailingComments :: (Data a, Data b) => Located a -> Located b -> Transform ()
- balanceTrailingComments :: (Monad m, Data a, Data b) => Located a -> Located b -> TransformT m [(Comment, DeltaPos)]
- balanceComments :: (Data a, Data b, Monad m) => Located a -> Located b -> TransformT m ()
- addTrailingComma :: Data a => Located a -> DeltaPos -> Anns -> Anns
- getEntryDP :: Data a => Anns -> Located a -> DeltaPos
- setPrecedingLines :: Data a => Located a -> Int -> Int -> Anns -> Anns
- setPrecedingLinesDecl :: LHsDecl GhcPs -> Int -> Int -> Anns -> Anns
- mergeAnnList :: [Anns] -> Anns
- mergeAnns :: Anns -> Anns -> Anns
- setPrecedingLinesT :: (Data a, Monad m) => Located a -> Int -> Int -> TransformT m ()
- setPrecedingLinesDeclT :: Monad m => LHsDecl GhcPs -> Int -> Int -> TransformT m ()
- getEntryDPT :: (Data a, Monad m) => Located a -> TransformT m DeltaPos
- removeTrailingCommaT :: (Data a, Monad m) => Located a -> TransformT m ()
- addTrailingCommaT :: (Data a, Monad m) => Located a -> TransformT m ()
- addSimpleAnnT :: (Constraints a, Monad m) => Located a -> DeltaPos -> [(KeywordId, DeltaPos)] -> TransformT m ()
- wrapDecl :: LHsBind GhcPs -> LHsDecl GhcPs
- wrapSig :: LSig GhcPs -> LHsDecl GhcPs
- decl2Sig :: LHsDecl name -> [LSig name]
- decl2Bind :: LHsDecl name -> [LHsBind name]
- captureOrderAnnKey :: AnnKey -> [Located b] -> Anns -> Anns
- captureOrder :: Data a => Located a -> [Located b] -> Anns -> Anns
- graftT :: (Data a, Monad m) => Anns -> a -> TransformT m a
- isUniqueSrcSpan :: SrcSpan -> Bool
- uniqueSrcSpanT :: Monad m => TransformT m SrcSpan
- modifyAnnsT :: Monad m => (Anns -> Anns) -> TransformT m ()
- putAnnsT :: Monad m => Anns -> TransformT m ()
- getAnnsT :: Monad m => TransformT m Anns
- logDataWithAnnsTr :: (Monad m, Data a) => String -> a -> TransformT m ()
- logTr :: Monad m => String -> TransformT m ()
- hoistTransform :: (forall x. m x -> n x) -> TransformT m a -> TransformT n a
- runTransformFromT :: Int -> Anns -> TransformT m a -> m (a, (Anns, Int), [String])
- runTransformFrom :: Int -> Anns -> Transform a -> (a, (Anns, Int), [String])
- runTransformT :: Anns -> TransformT m a -> m (a, (Anns, Int), [String])
- runTransform :: Anns -> Transform a -> (a, (Anns, Int), [String])
- type Transform = TransformT Identity
- newtype TransformT (m :: Type -> Type) a = TransformT {
- unTransformT :: RWST () [String] (Anns, Int) m a
- class Data t => HasDecls t where
- hsDecls :: Monad m => t -> TransformT m [LHsDecl GhcPs]
- replaceDecls :: Monad m => t -> [LHsDecl GhcPs] -> TransformT m t
- class Monad m => HasTransform (m :: Type -> Type) where
- data Comment
- data Annotation = Ann {
- annEntryDelta :: !DeltaPos
- annPriorComments :: ![(Comment, DeltaPos)]
- annFollowingComments :: ![(Comment, DeltaPos)]
- annsDP :: ![(KeywordId, DeltaPos)]
- annSortKey :: !(Maybe [SrcSpan])
- annCapturedSpan :: !(Maybe AnnKey)
- type Anns = Map AnnKey Annotation
- data AnnKey = AnnKey SrcSpan AnnConName
- class Data ast => Annotate ast
- annGetConstr :: Data a => a -> AnnConName
- mkAnnKey :: Data a => Located a -> AnnKey
- emptyAnns :: Anns
- annNone :: Annotation
- newtype DeltaPos = DP (Int, Int)
- data AnnConName = CN {}
- data KeywordId
- annLeadingCommentEntryDelta :: Annotation -> DeltaPos
- showGhc :: Outputable a => a -> String
Fixity re-association
fix :: (Data ast, Monad m) => FixityEnv -> ast -> TransformT m ast Source #
Re-associate AST using given FixityEnv
. (The GHC parser has no knowledge
of operator fixity, because that requires running the renamer, so it parses
all operators as left-associated.)
Parsers
parseContent :: FixityEnv -> FilePath -> String -> IO AnnotatedModule Source #
parseContentNoFixity :: FilePath -> String -> IO AnnotatedModule Source #
parseImports :: [String] -> IO AnnotatedImports Source #
Parse import statements. Each string must be a full import statement, including the keyword 'import'. Supports full import syntax.
parsePattern :: String -> IO AnnotatedPat Source #
Parse a Pat
.
Primitive Transformations
addAllAnnsT :: (Data a, Data b, Monad m) => Located a -> Located b -> TransformT m () Source #
setEntryDPT :: (Data a, Monad m) => Located a -> DeltaPos -> TransformT m () Source #
Transform
monad version of getEntryDP
swapEntryDPT :: (Data a, Data b, Monad m) => Located a -> Located b -> TransformT m () Source #
transferAnnsT :: (Data a, Data b, Monad m) => (KeywordId -> Bool) -> Located a -> Located b -> TransformT m () Source #
transferEntryAnnsT :: (Data a, Data b, Monad m) => (KeywordId -> Bool) -> Located a -> Located b -> TransformT m () Source #
transferEntryDPT :: (Data a, Data b, Monad m) => Located a -> Located b -> TransformT m () Source #
Transform
monad version of transferEntryDP
Utils
debugParse :: String -> IO () Source #
hasComments :: (Data a, Monad m) => Located a -> TransformT m Bool Source #
Annotated AST
module Retrie.ExactPrint.Annotated
ghc-exactprint re-exports
parseModule :: FilePath -> IO (Either (SrcSpan, String) (Anns, ParsedSource)) #
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
)
relativiseApiAnnsWithComments :: Annotate ast => [Comment] -> Located ast -> ApiAnns -> Anns #
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.
relativiseApiAnns :: Annotate ast => Located ast -> ApiAnns -> Anns #
Transform concrete annotations into relative annotations which are more useful when transforming an AST.
addAnnotationsForPretty :: Annotate a => [Comment] -> Located a -> Anns -> Anns #
Add any missing annotations so that the full AST element will exactprint properly when done.
exactPrint :: Annotate ast => Located ast -> Anns -> String #
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.
modifyDeclsT :: (HasDecls t, HasTransform m) => ([LHsDecl GhcPs] -> m [LHsDecl GhcPs]) -> t -> m t #
Apply a transformation to the decls contained in t
modifyValD :: HasTransform m => SrcSpan -> Decl -> (Match -> [Decl] -> m ([Decl], Maybe t)) -> m (Decl, Maybe t) #
replaceDeclsValbinds :: Monad m => HsLocalBinds GhcPs -> [LHsDecl GhcPs] -> TransformT m (HsLocalBinds GhcPs) #
Utility function for returning decls to HsLocalBinds
. Use with
care, as this does not manage the declaration order, the
ordering should be done by the calling function from the HsLocalBinds
context in the AST.
hsDeclsValBinds :: Monad m => HsLocalBinds GhcPs -> TransformT m [LHsDecl GhcPs] #
Utility function for extracting decls from HsLocalBinds
. Use with
care, as this does not necessarily return the declarations in order, the
ordering should be done by the calling function from the HsLocalBinds
context in the AST.
hsDeclsGeneric :: (Data t, Monad m) => t -> TransformT m [LHsDecl GhcPs] #
:: (Data t2, Monad m) | |
=> (forall t. HasDecls t => t -> m t) | Worker function for the general case |
-> (LHsBind GhcPs -> m (LHsBind GhcPs)) | Worker function for FunBind/PatBind |
-> t2 | Item to be updated |
-> m t2 |
Do a transformation on an AST fragment by providing a function to process
the general case and one specific for a LHsBind
. This is required
because a FunBind
may have multiple Match
items, so we cannot
gurantee that replaceDecls
after hsDecls
is idempotent.
replaceDeclsPatBind :: Monad m => LHsBind GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsBind GhcPs) #
Replace the immediate declarations for a PatBind
. This
cannot be a member of HasDecls
because a FunBind
is not idempotent
for hsDecls
/ replaceDecls
. hsDeclsPatBind
/ replaceDeclsPatBind
is
idempotent.
replaceDeclsPatBindD :: Monad m => LHsDecl GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsDecl GhcPs) #
Replace the immediate declarations for a PatBind
wrapped in a ValD
. This
cannot be a member of HasDecls
because a FunBind
is not idempotent
for hsDecls
/ replaceDecls
. hsDeclsPatBindD
/ replaceDeclsPatBindD
is
idempotent.
hsDeclsPatBind :: Monad m => LHsBind GhcPs -> TransformT m [LHsDecl GhcPs] #
Extract the immediate declarations for a PatBind
. This
cannot be a member of HasDecls
because a FunBind
is not idempotent
for hsDecls
/ replaceDecls
. hsDeclsPatBind
/ replaceDeclsPatBind
is
idempotent.
hsDeclsPatBindD :: Monad m => LHsDecl GhcPs -> TransformT m [LHsDecl GhcPs] #
Extract the immediate declarations for a PatBind
wrapped in a ValD
. This
cannot be a member of HasDecls
because a FunBind
is not idempotent
for hsDecls
/ replaceDecls
. hsDeclsPatBindD
/ replaceDeclsPatBindD
is
idempotent.
insertBefore :: HasDecls (Located ast) => Located old -> Located ast -> LHsDecl GhcPs -> Transform (Located ast) #
Insert a declaration at a specific location in the subdecls of the given AST item
insertAfter :: HasDecls (Located ast) => Located old -> Located ast -> LHsDecl GhcPs -> Transform (Located ast) #
Insert a declaration at a specific location in the subdecls of the given AST item
insertAtEnd :: HasDecls (Located ast) => Located ast -> LHsDecl GhcPs -> Transform (Located ast) #
Insert a declaration at the beginning or end of the subdecls of the given AST item
insertAtStart :: HasDecls (Located ast) => Located ast -> LHsDecl GhcPs -> Transform (Located ast) #
Insert a declaration at the beginning or end of the subdecls of the given AST item
moveTrailingComments :: (Data a, Data b) => Located a -> Located b -> Transform () #
Move any annFollowingComments
values from the Annotation
associated to
the first parameter to that of the second.
balanceTrailingComments :: (Monad m, Data a, Data b) => Located a -> Located b -> TransformT m [(Comment, DeltaPos)] #
After moving an AST element, make sure any comments that may belong with the following element in fact do. Of necessity this is a heuristic process, to be tuned later. Possibly a variant should be provided with a passed-in decision function.
balanceComments :: (Data a, Data b, Monad m) => Located a -> Located b -> TransformT m () #
The relatavise phase puts all comments appearing between the end of one AST
item and the beginning of the next as annPriorComments
for the second one.
This function takes two adjacent AST items and moves any annPriorComments
from the second one to the annFollowingComments
of the first if they belong
to it instead. This is typically required before deleting or duplicating
either of the AST elements.
setPrecedingLines :: Data a => Located a -> Int -> Int -> Anns -> Anns #
Adjust the entry annotations to provide an n
line preceding gap
setPrecedingLinesDecl :: LHsDecl GhcPs -> Int -> Int -> Anns -> Anns #
Unwrap a HsDecl and call setPrecedingLines on it ++AZ++ TODO: get rid of this, it is a synonym only
mergeAnnList :: [Anns] -> Anns #
Combine a list of annotations
setPrecedingLinesT :: (Data a, Monad m) => Located a -> Int -> Int -> TransformT m () #
Transform
monad version of setPrecedingLines
setPrecedingLinesDeclT :: Monad m => LHsDecl GhcPs -> Int -> Int -> TransformT m () #
Transform
monad version of setPrecedingLinesDecl
getEntryDPT :: (Data a, Monad m) => Located a -> TransformT m DeltaPos #
Transform
monad version of getEntryDP
removeTrailingCommaT :: (Data a, Monad m) => Located a -> TransformT m () #
Remove a trailing comma annotation, if there is one one
addTrailingCommaT :: (Data a, Monad m) => Located a -> TransformT m () #
Add a trailing comma annotation, unless there is already one
addSimpleAnnT :: (Constraints a, Monad m) => Located a -> DeltaPos -> [(KeywordId, DeltaPos)] -> TransformT m () #
Create a simple Annotation
without comments, and attach it to the first
parameter.
decl2Sig :: LHsDecl name -> [LSig name] #
Pure function to convert a LSig
to a LHsBind
. This does
nothing to any annotations that may be attached to either of the elements.
It is used as a utility function in replaceDecls
decl2Bind :: LHsDecl name -> [LHsBind name] #
Pure function to convert a LHsDecl
to a LHsBind
. This does
nothing to any annotations that may be attached to either of the elements.
It is used as a utility function in replaceDecls
captureOrderAnnKey :: AnnKey -> [Located b] -> Anns -> Anns #
If a list has been re-ordered or had items added, capture the new order in
the appropriate annSortKey
item of the supplied AnnKey
captureOrder :: Data a => Located a -> [Located b] -> Anns -> Anns #
If a list has been re-ordered or had items added, capture the new order in
the appropriate annSortKey
attached to the Annotation
for the first
parameter.
isUniqueSrcSpan :: SrcSpan -> Bool #
Test whether a given SrcSpan
was generated by uniqueSrcSpanT
uniqueSrcSpanT :: Monad m => TransformT m SrcSpan #
modifyAnnsT :: Monad m => (Anns -> Anns) -> TransformT m () #
Change the stored Anns
logDataWithAnnsTr :: (Monad m, Data a) => String -> a -> TransformT m () #
Log a representation of the given AST with annotations to the output of the Monad
logTr :: Monad m => String -> TransformT m () #
Log a string to the output of the Monad
hoistTransform :: (forall x. m x -> n x) -> TransformT m a -> TransformT n a #
Change inner monad of TransformT
.
runTransformFromT :: Int -> Anns -> TransformT m a -> m (a, (Anns, Int), [String]) #
Run a monad transformer stack for the TransformT
monad transformer
runTransformT :: Anns -> TransformT m a -> m (a, (Anns, Int), [String]) #
type Transform = TransformT Identity #
Monad type for updating the AST and managing the annotations at the same time. The W state is used to generate logging information if required.
newtype TransformT (m :: Type -> Type) a #
Monad transformer version of Transform
monad
TransformT | |
|
Instances
class Data t => HasDecls t where #
Provide a means to get and process the immediate child declartions of a given AST element.
hsDecls :: Monad m => t -> TransformT m [LHsDecl GhcPs] #
Return the HsDecl
s that are directly enclosed in the
given syntax phrase. They are always returned in the wrapped HsDecl
form, even if orginating in local decls. This is safe, as annotations
never attach to the wrapper, only to the wrapped item.
replaceDecls :: Monad m => t -> [LHsDecl GhcPs] -> TransformT m t #
Replace the directly enclosed decl list by the given
decl list. Runs in the Transform
monad to be able to update list order
annotations, and rebalance comments and other layout changes as needed.
For example, a call on replaceDecls for a wrapped FunBind
having no
where clause will convert
-- |This is a function foo = x -- comment1
in to
-- |This is a function foo = x -- comment1 where nn = 2
Instances
HasDecls ParsedSource | |
Defined in Language.Haskell.GHC.ExactPrint.Transform hsDecls :: Monad m => ParsedSource -> TransformT m [LHsDecl GhcPs] # replaceDecls :: Monad m => ParsedSource -> [LHsDecl GhcPs] -> TransformT m ParsedSource # | |
HasDecls (LHsExpr GhcPs) | |
Defined in Language.Haskell.GHC.ExactPrint.Transform | |
HasDecls (LMatch GhcPs (LHsExpr GhcPs)) | |
HasDecls (LStmt GhcPs (LHsExpr GhcPs)) | |
class Monad m => HasTransform (m :: Type -> Type) where #
Used to integrate a Transform
into other Monad stacks
Instances
Monad m => HasTransform (TransformT m) | |
Defined in Language.Haskell.GHC.ExactPrint.Transform liftT :: Transform a -> TransformT m a # |
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 | |
Data Comment | |
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 :: (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 | |
Defined in Language.Haskell.GHC.ExactPrint.Types | |
Show Comment | |
Outputable Comment | |
data Annotation #
Ann | |
|
Instances
Eq Annotation | |
Defined in Language.Haskell.GHC.ExactPrint.Types (==) :: Annotation -> Annotation -> Bool # (/=) :: Annotation -> Annotation -> Bool # | |
Show Annotation | |
Defined in Language.Haskell.GHC.ExactPrint.Types showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # | |
Outputable Annotation | |
Defined in Language.Haskell.GHC.ExactPrint.Types ppr :: Annotation -> SDoc # pprPrec :: Rational -> Annotation -> SDoc # | |
Monad m => MonadState (Anns, Int) (TransformT m) | |
Defined in Language.Haskell.GHC.ExactPrint.Transform |
type Anns = Map AnnKey Annotation #
This structure holds a complete set of annotations for an AST
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 | |
Data AnnKey | |
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 :: (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 | |
Show AnnKey | |
Outputable AnnKey | |
Monad m => MonadState (Anns, Int) (TransformT m) | |
Defined in Language.Haskell.GHC.ExactPrint.Transform |
class Data ast => Annotate ast #
Instances
annGetConstr :: Data a => a -> AnnConName #
mkAnnKey :: Data a => Located a -> AnnKey #
Make an unwrapped AnnKey
for the LHsDecl
case, a normal one otherwise.
annNone :: Annotation #
A relative positions, row then column
Instances
Eq DeltaPos | |
Data DeltaPos | |
Defined in Language.Haskell.GHC.ExactPrint.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> DeltaPos -> c DeltaPos # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c DeltaPos # toConstr :: DeltaPos -> Constr # dataTypeOf :: DeltaPos -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c DeltaPos) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c DeltaPos) # gmapT :: (forall b. Data b => b -> b) -> DeltaPos -> DeltaPos # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> DeltaPos -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> DeltaPos -> r # gmapQ :: (forall d. Data d => d -> u) -> DeltaPos -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> DeltaPos -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> DeltaPos -> m DeltaPos # | |
Ord DeltaPos | |
Defined in Language.Haskell.GHC.ExactPrint.Types | |
Show DeltaPos | |
Outputable DeltaPos | |
data AnnConName #
Instances
The different syntactic elements which are not represented in the AST.
G AnnKeywordId | A normal keyword |
AnnSemiSep | A separating comma |
AnnTypeApp | Visible type application annotation |
AnnComment Comment | |
AnnString String | Used to pass information from Delta to Print when we have to work out details from the original SrcSpan. |
Instances
Eq KeywordId | |
Data KeywordId | |
Defined in Language.Haskell.GHC.ExactPrint.Types gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> KeywordId -> c KeywordId # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c KeywordId # toConstr :: KeywordId -> Constr # dataTypeOf :: KeywordId -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c KeywordId) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c KeywordId) # gmapT :: (forall b. Data b => b -> b) -> KeywordId -> KeywordId # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> KeywordId -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> KeywordId -> r # gmapQ :: (forall d. Data d => d -> u) -> KeywordId -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> KeywordId -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> KeywordId -> m KeywordId # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> KeywordId -> m KeywordId # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> KeywordId -> m KeywordId # | |
Ord KeywordId | |
Defined in Language.Haskell.GHC.ExactPrint.Types | |
Show KeywordId | |
Outputable KeywordId | |
annLeadingCommentEntryDelta :: Annotation -> DeltaPos #
Return the DP of the first item that generates output, either a comment or the entry DP
showGhc :: Outputable a => a -> String #
Show a GHC.Outputable structure