ghc-exactprint-1.6.1.1: ExactPrint for GHC
Safe HaskellSafe-Inferred
LanguageHaskell2010

Language.Haskell.GHC.ExactPrint.Transform

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

Instances

Instances details
MonadTrans TransformT Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

lift :: Monad m => m a -> TransformT m a #

Monad m => MonadReader () (TransformT m) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

ask :: TransformT m () #

local :: (() -> ()) -> TransformT m a -> TransformT m a #

reader :: (() -> a) -> TransformT m a #

Monad m => MonadState Int (TransformT m) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

get :: TransformT m Int #

put :: Int -> TransformT m () #

state :: (Int -> (a, Int)) -> TransformT m a #

MonadFail m => MonadFail (TransformT m) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

fail :: String -> TransformT m a #

Monad m => Applicative (TransformT m) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

pure :: a -> TransformT m a #

(<*>) :: TransformT m (a -> b) -> TransformT m a -> TransformT m b #

liftA2 :: (a -> b -> c) -> TransformT m a -> TransformT m b -> TransformT m c #

(*>) :: TransformT m a -> TransformT m b -> TransformT m b #

(<*) :: TransformT m a -> TransformT m b -> TransformT m a #

Functor m => Functor (TransformT m) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

fmap :: (a -> b) -> TransformT m a -> TransformT m b #

(<$) :: a -> TransformT m b -> TransformT m a #

Monad m => Monad (TransformT m) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

(>>=) :: TransformT m a -> (a -> TransformT m b) -> TransformT m b #

(>>) :: TransformT m a -> TransformT m b -> TransformT m b #

return :: a -> TransformT m a #

Monad m => HasTransform (TransformT m) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

liftT :: Transform a -> TransformT m a Source #

Monad m => MonadWriter [String] (TransformT m) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

writer :: (a, [String]) -> TransformT m a #

tell :: [String] -> TransformT m () #

listen :: TransformT m a -> TransformT m (a, [String]) #

pass :: TransformT m (a, [String] -> [String]) -> TransformT m a #

hoistTransform :: (forall x. m x -> n x) -> TransformT m a -> TransformT n a Source #

Change inner monad of TransformT.

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

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

runTransformFrom :: Int -> Transform a -> (a, 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 :: Int -> TransformT m a -> m (a, 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

uniqueSrcSpanT :: Monad m => TransformT m SrcSpan Source #

If we need to add new elements to the AST, they need their own SrcSpan for this.

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 #

Instances

Instances details
Monad m => HasTransform (TransformT m) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

liftT :: Transform a -> TransformT 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 GhcPs] 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 GhcPs] -> 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

Instances

Instances details
HasDecls ParsedSource Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> TransformT m [LHsDecl GhcPs] Source #

replaceDecls :: forall (m :: Type -> Type). Monad m => ParsedSource -> [LHsDecl GhcPs] -> TransformT m ParsedSource Source #

HasDecls (LocatedA (HsExpr GhcPs)) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

hsDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> TransformT m [LHsDecl GhcPs] Source #

replaceDecls :: forall (m :: Type -> Type). Monad m => LocatedA (HsExpr GhcPs) -> [LHsDecl GhcPs] -> TransformT m (LocatedA (HsExpr GhcPs)) Source #

HasDecls (LocatedA (Match GhcPs (LocatedA (HsExpr GhcPs)))) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

HasDecls (LocatedA (Stmt GhcPs (LocatedA (HsExpr GhcPs)))) Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

hsDeclsPatBind :: Monad m => LHsBind GhcPs -> TransformT m [LHsDecl GhcPs] 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 GhcPs -> TransformT m [LHsDecl GhcPs] 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 GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsBind GhcPs) 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 GhcPs -> [LHsDecl GhcPs] -> TransformT m (LHsDecl GhcPs) 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 GhcPs] -> m [LHsDecl GhcPs]) -> t -> m t Source #

Apply a transformation to the decls contained in t

modifyValD :: forall m t. HasTransform m => SrcSpan -> Decl -> (PMatch -> [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

replaceDeclsValbinds :: Monad m => WithWhere -> HsLocalBinds GhcPs -> [LHsDecl GhcPs] -> TransformT m (HsLocalBinds GhcPs) 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.

data WithWhere Source #

Constructors

WithWhere 
WithoutWhere 

Instances

Instances details
Show WithWhere Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Eq WithWhere Source # 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

New gen functions

noAnnSrcSpanDP :: Monoid ann => SrcSpan -> DeltaPos -> SrcSpanAnn' (EpAnn ann) Source #

Create a SrcSpanAnn with a MovedAnchor operation using the given DeltaPos.

Managing lists, Transform monad

insertAt :: HasDecls ast => (LHsDecl GhcPs -> [LHsDecl GhcPs] -> [LHsDecl GhcPs]) -> ast -> LHsDecl GhcPs -> Transform ast Source #

Insert a declaration into an AST element having sub-declarations (HasDecls) according to the given location function.

insertAtStart :: HasDecls ast => ast -> LHsDecl GhcPs -> Transform ast Source #

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

insertAtEnd :: HasDecls ast => ast -> LHsDecl GhcPs -> Transform ast Source #

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

insertAfter :: HasDecls (LocatedA ast) => LocatedA old -> LocatedA ast -> LHsDecl GhcPs -> Transform (LocatedA ast) Source #

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

insertBefore :: HasDecls (LocatedA ast) => LocatedA old -> LocatedA ast -> LHsDecl GhcPs -> Transform (LocatedA ast) Source #

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

Low level operations used in HasDecls

balanceComments :: Monad m => LHsDecl GhcPs -> LHsDecl GhcPs -> TransformT m (LHsDecl GhcPs, LHsDecl GhcPs) Source #

The GHC parser 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.

Managing lists, pure functions

captureOrder :: [LocatedA b] -> AnnSortKey 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 list.

Operations

isUniqueSrcSpan :: SrcSpan -> Bool Source #

Test whether a given SrcSpan was generated by uniqueSrcSpanT

Pure functions

setEntryDP :: Default t => LocatedAn t a -> DeltaPos -> LocatedAn t a Source #

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

transferEntryDP :: (Monad m, Monoid t2, Typeable t1, Typeable t2) => LocatedAn t1 a -> LocatedAn t2 b -> TransformT m (LocatedAn t2 b) Source #

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

transferEntryDP' :: Monad m => LHsDecl GhcPs -> LHsDecl GhcPs -> TransformT m (LHsDecl GhcPs) Source #

Take the annEntryDelta associated with the first item and associate it with the second. Also transfer any comments occuring before it. TODO: call transferEntryDP, and use pushDeclDP

decl2Sig :: LHsDecl GhcPs -> [LSig GhcPs] 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 GhcPs -> [LHsBind GhcPs] 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