ghc-exactprint-0.4.0.0: ExactPrint for GHC

Safe HaskellNone
LanguageHaskell2010

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 welcome any feedback / contributions on this, as it is the main point of the library.

Synopsis

The Transform Monad

type Transform = TransformT Identity 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.

newtype TransformT m a Source

Monad transformer version of Transform monad

Constructors

TransformT 

Fields

runTransformT :: RWST () [String] (Anns, Int) m a
 

runTransform :: Anns -> Transform a -> (a, (Anns, Int), [String]) Source

Run a transformation in the Transform monad, returning the updated annotations and any logging generated via logTr

runTransformFrom :: Int -> Anns -> Transform a -> (a, (Anns, Int), [String]) Source

Run a transformation in the Transform monad, returning the updated annotations and any logging generated via logTr, allocating any new SrcSpans from the provided initial value.

runTransformFromT :: Monad m => Int -> Anns -> TransformT m a -> m (a, (Anns, Int), [String]) Source

Run a monad transformer stack for the TransformT monad transformer

Transform monad operations

logTr :: Monad m => String -> TransformT m () Source

Log a string to the output of the Monad

logDataWithAnnsTr :: Monad m => Data a => String -> a -> TransformT m () Source

Log a representation of the given AST with annotations to the output of the Monad

getAnnsT :: Monad m => TransformT m Anns Source

Access the Anns being modified in this transformation

putAnnsT :: Monad m => Anns -> TransformT m () Source

Replace the Anns after any changes

modifyAnnsT :: Monad m => (Anns -> Anns) -> TransformT m () Source

Change the stored Anns

uniqueSrcSpanT :: Transform SrcSpan Source

Once we have Anns, a SrcSpan is used purely as part of an AnnKey to index into the Anns. If we need to add new elements to the AST, they need their own SrcSpan for this.

cloneT :: (Data a, Typeable a) => a -> Transform (a, [(SrcSpan, SrcSpan)]) Source

Make a copy of an AST element, replacing the existing SrcSpans with new ones, and duplicating the matching annotations.

addSimpleAnnT :: Data a => Located a -> DeltaPos -> [(KeywordId, DeltaPos)] -> Transform () Source

Create a simple Annotation without comments, and attach it to the first parameter.

addTrailingCommaT :: Data a => Located a -> Transform () Source

Add a trailing comma annotation, unless there is already one

removeTrailingCommaT :: Data a => Located a -> Transform () Source

Remove a trailing comma annotation, if there is one one

Managing declarations, in Transform monad

class Monad m => HasTransform m where Source

Used to integrate a Transform into other Monad stacks

Methods

liftT :: Transform a -> m a Source

class Data t => HasDecls t where Source

Provide a means to get and process the immediate child declartions of a given AST element.

Methods

hsDecls :: Monad m => t -> TransformT m [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. This is safe, as annotations never attach to the wrapper, only to the wrapped item.

replaceDecls :: Monad m => t -> [LHsDecl RdrName] -> TransformT m 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

hasDeclsSybTransform Source

Arguments

:: (Data t2, Typeable t2, Monad m) 
=> (forall t. HasDecls t => t -> m t)

Worker function for the general case

-> (LHsBind RdrName -> m (LHsBind RdrName))

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.

hsDeclsGeneric :: (Data t, Typeable t) => t -> Transform [LHsDecl RdrName] Source

A FunBind wraps up one or more Match items. hsDecls cannot return anything for these as there is not meaningful replaceDecls for it. This function provides a version of hsDecls that returns the FunBind decls too, where they are needed for analysis only.

hsDeclsPatBind :: Monad m => LHsBind RdrName -> TransformT m [LHsDecl RdrName] Source

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 RdrName -> TransformT m [LHsDecl RdrName] Source

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.

replaceDeclsPatBind :: Monad m => LHsBind RdrName -> [LHsDecl RdrName] -> TransformT m (LHsBind RdrName) Source

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 RdrName -> [LHsDecl RdrName] -> TransformT m (LHsDecl RdrName) Source

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.

modifyDeclsT :: (HasDecls t, HasTransform m) => ([LHsDecl RdrName] -> m [LHsDecl RdrName]) -> t -> m t Source

Apply a transformation to the decls contained in t

modifyValD :: forall m t. HasTransform m => SrcSpan -> Decl -> (Match -> [Decl] -> m ([Decl], Maybe t)) -> m (Decl, Maybe t) Source

Modify a LHsBind wrapped in a ValD. For a PatBind the declarations are extracted and returned after modification. For a FunBind the supplied SrcSpan is used to identify the specific Match to be transformed, for when there are multiple of them.

Utility, does not manage layout

hsDeclsValBinds :: Monad m => HsLocalBinds RdrName -> TransformT m [LHsDecl RdrName] Source

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.

replaceDeclsValbinds :: Monad m => HsLocalBinds RdrName -> [LHsDecl RdrName] -> TransformT m (HsLocalBinds RdrName) Source

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.

Managing lists, Transform monad

insertAtStart :: (Data ast, HasDecls (Located ast)) => Located ast -> LHsDecl RdrName -> Transform (Located ast) Source

Insert a declaration at the beginning or end of the subdecls of the given AST item

insertAtEnd :: (Data ast, HasDecls (Located ast)) => Located ast -> LHsDecl RdrName -> Transform (Located ast) Source

Insert a declaration at the beginning or end of the subdecls of the given AST item

insertAfter :: (Data ast, HasDecls (Located ast)) => Located old -> Located ast -> LHsDecl RdrName -> Transform (Located ast) Source

Insert a declaration at a specific location in the subdecls of the given AST item

insertBefore :: (Data ast, HasDecls (Located ast)) => Located old -> Located ast -> LHsDecl RdrName -> Transform (Located ast) Source

Insert a declaration at a specific location in the subdecls of the given AST item

Low level operations used in HasDecls

balanceComments :: (Data a, Data b) => Located a -> Located b -> Transform () Source

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.

balanceTrailingComments :: Monad m => (Data a, Data b) => Located a -> Located b -> TransformT m [(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

Pure functions

mergeAnns :: Anns -> Anns -> Anns Source

Left bias pair union

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 ++AZ++ TODO: get rid of this, it is a synonym only

setPrecedingLines :: Data a => Located a -> Int -> Int -> Anns -> Anns Source

Adjust the entry annotations to provide an n line preceding gap

getEntryDP :: Data a => Anns -> Located a -> DeltaPos Source

Return the true entry DeltaPos from the annotation for a given AST element. This is the DeltaPos ignoring any comments.

setEntryDP :: Data a => Located a -> DeltaPos -> Anns -> Anns Source

Set the true entry DeltaPos from the annotation for a given AST element. This is the DeltaPos ignoring any comments.

transferEntryDP :: (Data a, Data b) => Located a -> Located b -> Anns -> Anns Source

Take the annEntryDelta associated with the first item and associate it with the second. Also transfer any comments occuring before it.

decl2Sig :: LHsDecl name -> [LSig name] Source

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] Source

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