| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Language.Haskell.GHC.ExactPrint.Transform
Contents
Description
This module is currently under heavy development, and no promises are made about API stability. Use with care.
We weclome any feedback / contributions on this, as it is the main point of the library.
- type Transform a = RWS () [String] (Anns, Int) a
- runTransform :: Anns -> Transform a -> (a, (Anns, Int), [String])
- logTr :: String -> Transform ()
- getAnnsT :: Transform Anns
- putAnnsT :: Anns -> Transform ()
- modifyAnnsT :: (Anns -> Anns) -> Transform ()
- uniqueSrcSpanT :: Transform SrcSpan
- wrapSigT :: LSig RdrName -> Transform (LHsDecl RdrName)
- wrapDeclT :: LHsBind RdrName -> Transform (LHsDecl RdrName)
- pushDeclAnnT :: LHsDecl RdrName -> Transform (LHsDecl RdrName)
- decl2BindT :: LHsDecl RdrName -> Transform [LHsBind RdrName]
- decl2SigT :: LHsDecl RdrName -> Transform [LSig RdrName]
- getEntryDPT :: Data a => Located a -> Transform DeltaPos
- addSimpleAnnT :: Data a => Located a -> DeltaPos -> [(KeywordId, DeltaPos)] -> Transform ()
- class Data t => HasDecls t where
- insertAtStart :: (Data ast, HasDecls (Located ast)) => Located ast -> LHsDecl RdrName -> Transform (Located ast)
- insertAtEnd :: (Data ast, HasDecls (Located ast)) => Located ast -> LHsDecl RdrName -> Transform (Located ast)
- insertAfter :: (Data ast, HasDecls (Located ast)) => Located old -> Located ast -> LHsDecl RdrName -> Transform (Located ast)
- insertBefore :: (Data ast, HasDecls (Located ast)) => Located old -> Located ast -> LHsDecl RdrName -> Transform (Located ast)
- balanceComments :: (Data a, Data b) => Located a -> Located b -> Transform ()
- balanceTrailingComments :: (Data a, Data b) => Located a -> Located b -> Transform [(Comment, DeltaPos)]
- moveTrailingComments :: (Data a, Data b) => Located a -> Located b -> Transform ()
- captureOrder :: Data a => Located a -> [Located b] -> Anns -> Anns
- captureOrderAnnKey :: AnnKey -> [Located b] -> Anns -> Anns
- isUniqueSrcSpan :: SrcSpan -> Bool
- declFun :: (forall a. Data a => Located a -> b) -> LHsDecl RdrName -> b
- mergeAnns :: Anns -> Anns -> Anns
- mergeAnnList :: [Anns] -> Anns
- setPrecedingLinesDecl :: LHsDecl RdrName -> Int -> Int -> Anns -> Anns
- setPrecedingLines :: Data a => Located a -> Int -> Int -> Anns -> Anns
- getEntryDP :: Data a => Anns -> Located a -> DeltaPos
The Transform Monad
type Transform a = RWS () [String] (Anns, Int) a Source
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.
Transform monad operations
wrapSigT :: LSig RdrName -> Transform (LHsDecl RdrName) Source
Convert a LSig into a LHsDecl, duplicating the LSig
annotation for the LHsDecl. This needs to be set up so that the
original annotation is restored after a pushDeclAnnT call.
wrapDeclT :: LHsBind RdrName -> Transform (LHsDecl RdrName) Source
Convert a LHsBind into a LHsDecl, duplicating the LHsBind
annotation for the LHsDecl. This needs to be set up so that the
original annotation is restored after a pushDeclAnnT call.
pushDeclAnnT :: LHsDecl RdrName -> Transform (LHsDecl RdrName) Source
Copy the top level annotation to a new SrcSpan and the unwrapped decl. This
is required so that decl2Sig and decl2Bind will produce values that have
the required annotations.
getEntryDPT :: Data a => Located a -> Transform DeltaPos Source
Transform monad version of getEntryDP
addSimpleAnnT :: Data a => Located a -> DeltaPos -> [(KeywordId, DeltaPos)] -> Transform () Source
Create a simple Annotation without comments, and attach it to the first
parameter.
Managing lists, Transform monad
class Data t => HasDecls t where Source
Methods
hsDecls :: t -> Transform [LHsDecl RdrName] Source
Return the HsDecls that are directly enclosed in the
given syntax phrase. They are always returned in the wrapped HsDecl
form, even if orginating in local decls.
replaceDecls :: t -> [LHsDecl RdrName] -> Transform t Source
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
insertAtStart :: (Data ast, HasDecls (Located ast)) => Located ast -> LHsDecl RdrName -> Transform (Located ast) Source
insertAtEnd :: (Data ast, HasDecls (Located ast)) => Located ast -> LHsDecl RdrName -> Transform (Located ast) Source
insertAfter :: (Data ast, HasDecls (Located ast)) => Located old -> Located ast -> LHsDecl RdrName -> Transform (Located ast) Source
insertBefore :: (Data ast, HasDecls (Located ast)) => Located old -> Located ast -> LHsDecl RdrName -> Transform (Located ast) Source
Low level operations used in HasDecls
balanceComments :: (Data a, Data b) => Located a -> Located b -> Transform () Source
Prior to moving an AST element, make sure any trailing comments belonging to it are attached to it, and not the following element. Of necessity this is a heuristic process, to be tuned later. Possibly a variant should be provided with a passed-in decision function.
balanceTrailingComments :: (Data a, Data b) => Located a -> Located b -> Transform [(Comment, DeltaPos)] Source
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.
moveTrailingComments :: (Data a, Data b) => Located a -> Located b -> Transform () Source
Move any annFollowingComments values from the Annotation associated to
the first parameter to that of the second.
Managing lists, pure functions
captureOrder :: Data a => Located a -> [Located b] -> Anns -> Anns Source
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.
captureOrderAnnKey :: AnnKey -> [Located b] -> Anns -> Anns Source
If a list has been re-ordered or had items added, capture the new order in
the appropriate annSortKey item of the supplied AnnKey
Operations
isUniqueSrcSpan :: SrcSpan -> Bool Source
Test whether a given SrcSpan was generated by uniqueSrcSpanT
Managing decls
Pure functions
mergeAnnList :: [Anns] -> Anns Source
Combine a list of annotations
setPrecedingLinesDecl :: LHsDecl RdrName -> Int -> Int -> Anns -> Anns Source
Unwrap a HsDecl and call setPrecedingLines on it