retrie-0.1.0.0: A powerful, easy-to-use codemodding tool for Haskell.

Safe HaskellNone
LanguageHaskell2010

Retrie.ExactPrint

Contents

Description

Provides consistent interface with ghc-exactprint.

Synopsis

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

parseDecl :: String -> IO AnnotatedHsDecl Source #

Parse a top-level HsDecl.

parseImports :: [String] -> IO AnnotatedImports Source #

Parse import statements. Each string must be a full import statement, including the keyword 'import'. Supports full import syntax.

Primitive Transformations

addAllAnnsT :: (Data a, Data b, Monad m) => Located a -> Located b -> TransformT m () Source #

cloneT :: (Data a, Typeable a, Monad m) => a -> TransformT m a 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 #

transferEntryDPT :: (Data a, Data b, Monad m) => Located a -> Located b -> TransformT m () Source #

Transform monad version of transferEntryDP

Utils

Annotated AST

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) #

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.

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

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.

hasDeclsSybTransform #

Arguments

:: (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.

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

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

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

mergeAnns :: Anns -> Anns -> Anns #

Left bias pair union

setPrecedingLinesT :: (Data a, Monad m) => Located a -> Int -> Int -> TransformT m () #

Transform monad version of setPrecedingLines

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.

wrapSig :: LSig GhcPs -> LHsDecl GhcPs #

Convert a LSig into a LHsDecl

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.

graftT :: (Data a, Monad m) => Anns -> a -> TransformT m a #

Slightly more general form of cloneT

isUniqueSrcSpan :: SrcSpan -> Bool #

Test whether a given SrcSpan was generated by uniqueSrcSpanT

uniqueSrcSpanT :: Monad m => TransformT m SrcSpan #

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.

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

Change the stored Anns

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

Replace the Anns after any changes

getAnnsT :: Monad m => TransformT m Anns #

Access the Anns being modified in this transformation

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

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

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.

runTransformT :: Anns -> TransformT m a -> m (a, (Anns, Int), [String]) #

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

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

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

Constructors

TransformT 

Fields

Instances
MonadTrans TransformT 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

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

Monad m => MonadReader () (TransformT m) 
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 => Monad (TransformT m) 
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 #

fail :: String -> TransformT m a #

Functor m => Functor (TransformT m) 
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 #

MonadFail m => MonadFail (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

fail :: String -> TransformT m a #

Monad m => Applicative (TransformT m) 
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 #

Monad m => HasTransform (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

liftT :: Transform a -> TransformT m a #

Monad m => MonadWriter [String] (TransformT m) 
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 #

Monad m => MonadState (Anns, Int) (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

get :: TransformT m (Anns, Int) #

put :: (Anns, Int) -> TransformT m () #

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

class Data t => HasDecls t where #

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

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 #

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

class Monad m => HasTransform (m :: Type -> Type) where #

Used to integrate a Transform into other Monad stacks

Methods

liftT :: Transform a -> m a #

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

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

liftT :: Transform a -> TransformT m a #

data Comment #

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 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Methods

(==) :: Comment -> Comment -> Bool #

(/=) :: Comment -> Comment -> Bool #

Data Comment 
Instance details

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 :: (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 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Show Comment 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Outputable Comment 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Methods

ppr :: Comment -> SDoc #

pprPrec :: Rational -> Comment -> SDoc #

data Annotation #

Constructors

Ann 

Fields

  • annEntryDelta :: !DeltaPos

    Offset used to get to the start of the SrcSpan, from whatever the prior output was, including all annPriorComments (field below).

  • annPriorComments :: ![(Comment, DeltaPos)]

    Comments coming after the last non-comment output of the preceding element but before the SrcSpan being annotated by this Annotation. If these are changed then annEntryDelta (field above) must also change to match.

  • annFollowingComments :: ![(Comment, DeltaPos)]

    Comments coming after the last output for the element subject to this Annotation. These will only be added by AST transformations, and care must be taken not to disturb layout of following elements.

  • annsDP :: ![(KeywordId, DeltaPos)]

    Annotations associated with this element.

  • annSortKey :: !(Maybe [SrcSpan])

    Captures the sort order of sub elements. This is needed when the sub-elements have been split (as in a HsLocalBind which holds separate binds and sigs) or for infix patterns where the order has been re-arranged. It is captured explicitly so that after the Delta phase a SrcSpan is used purely as an index into the annotations, allowing transformations of the AST including the introduction of new Located items or re-arranging existing ones.

  • annCapturedSpan :: !(Maybe AnnKey)

    Occasionally we must calculate a SrcSpan for an unlocated list of elements which we must remember for the Print phase. e.g. the statements in a HsLet or HsDo. These must be managed as a group because they all need eo be vertically aligned for the Haskell layout rules, and this guarantees this property in the presence of AST edits.

Instances
Eq Annotation 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Show Annotation 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Outputable Annotation 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Monad m => MonadState (Anns, Int) (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

get :: TransformT m (Anns, Int) #

put :: (Anns, Int) -> TransformT m () #

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

type Anns = Map AnnKey Annotation #

This structure holds a complete set of annotations for an AST

data AnnKey #

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

Constructors

AnnKey SrcSpan AnnConName 
Instances
Eq AnnKey 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Methods

(==) :: AnnKey -> AnnKey -> Bool #

(/=) :: AnnKey -> AnnKey -> Bool #

Data AnnKey 
Instance details

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) -> 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 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Show AnnKey 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Outputable AnnKey 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Methods

ppr :: AnnKey -> SDoc #

pprPrec :: Rational -> AnnKey -> SDoc #

Monad m => MonadState (Anns, Int) (TransformT m) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Transform

Methods

get :: TransformT m (Anns, Int) #

put :: (Anns, Int) -> TransformT m () #

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

class Data ast => Annotate ast #

Minimal complete definition

markAST

Instances
Annotate DocDecl 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> DocDecl -> Annotated () #

Annotate HsIPName 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> HsIPName -> Annotated () #

Annotate RdrName 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> RdrName -> Annotated () #

Annotate HsDocString 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate Safety 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Safety -> Annotated () #

Annotate CExportSpec 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate CCallConv 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> CCallConv -> Annotated () #

Annotate CType 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> CType -> Annotated () #

Annotate StringLiteral 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate WarningTxt 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> WarningTxt -> Annotated () #

Annotate OverlapMode 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate ModuleName 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> ModuleName -> Annotated () #

Annotate FastString 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> FastString -> Annotated () #

Annotate ResTyGADTHook 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> ResTyGADTHook -> Annotated () #

Annotate WildCardAnon 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> WildCardAnon -> Annotated () #

Annotate [ExprLStmt GhcPs]

Used for declarations that need to be aligned together, e.g. in a do or let .. in statement/expr

Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [ExprLStmt GhcPs] -> Annotated () #

Annotate [LHsDerivingClause GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate [LHsType GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [LHsType GhcPs] -> Annotated () #

Annotate [LHsSigType GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [LHsSigType GhcPs] -> Annotated () #

Annotate [LConDeclField GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate [LIE GhcPs] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [LIE GhcPs] -> Annotated () #

Annotate body => Annotate [Located (Match GhcPs (Located body))] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> [Located (Match GhcPs (Located body))] -> Annotated () #

Annotate [Located (StmtLR GhcPs GhcPs (LHsCmd GhcPs))] 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (Maybe Role) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Maybe Role -> Annotated () #

Annotate (HsModule GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsTupArg GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsCmdTop GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> HsDecl GhcPs -> Annotated () #

Annotate (SpliceDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (TyClDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (FamilyResultSig GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (FamilyDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (InjectivityAnn GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsDerivingClause GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (ConDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> ConDecl GhcPs -> Annotated () #

Annotate (TyFamInstEqn GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (TyFamDefltEqn GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (TyFamInstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (DataFamInstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (ClsInstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (InstDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (DerivDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (DerivStrategy GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (DefaultDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (ForeignDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (RuleDecls GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (RuleDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (RuleBndr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (WarnDecls GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (WarnDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (AnnDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> AnnDecl GhcPs -> Annotated () #

Annotate (RoleAnnotDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsRecUpdField GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsLocalBinds GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsBind GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> HsBind GhcPs -> Annotated () #

Annotate (IPBind GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> IPBind GhcPs -> Annotated () #

Annotate (Sig GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Sig GhcPs -> Annotated () #

Annotate (HsTyVarBndr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsType GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> HsType GhcPs -> Annotated () #

Annotate (ConDeclField GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (FieldOcc GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (AmbiguousFieldOcc GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsLit GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> HsLit GhcPs -> Annotated () #

Annotate (HsOverLit GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (FunDep (Located RdrName)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsExpr GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> HsExpr GhcPs -> Annotated () #

Annotate (HsCmd GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> HsCmd GhcPs -> Annotated () #

Annotate (HsSplice GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (ImportDecl GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (IEWrappedName RdrName) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (IE GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> IE GhcPs -> Annotated () #

Annotate (Pat GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Pat GhcPs -> Annotated () #

Annotate name => Annotate (BooleanFormula (Located name)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> BooleanFormula (Located name) -> Annotated () #

Annotate (SourceText, FastString) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate body => Annotate (Match GhcPs (Located body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Match GhcPs (Located body) -> Annotated () #

Annotate body => Annotate (GRHS GhcPs (Located body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> GRHS GhcPs (Located body) -> Annotated () #

Annotate body => Annotate (Stmt GhcPs (Located body)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Methods

markAST :: SrcSpan -> Stmt GhcPs (Located body) -> Annotated () #

Annotate (ParStmtBlock GhcPs GhcPs) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsRecField GhcPs (LHsExpr GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate (HsRecField GhcPs (LPat GhcPs)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

Annotate arg => Annotate (HsImplicitBndrs GhcPs (Located arg)) 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Annotater

mkAnnKey :: Data a => Located a -> AnnKey #

Make an unwrapped AnnKey for the LHsDecl case, a normal one otherwise.

newtype DeltaPos #

A relative positions, row then column

Constructors

DP (Int, Int) 
Instances
Eq DeltaPos 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Data DeltaPos 
Instance details

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) -> 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 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Show DeltaPos 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Outputable DeltaPos 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

data AnnConName #

Constructors

CN 

Fields

Instances
Eq AnnConName 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Data AnnConName 
Instance details

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) -> AnnConName -> c AnnConName #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c AnnConName #

toConstr :: AnnConName -> Constr #

dataTypeOf :: AnnConName -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c AnnConName) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c AnnConName) #

gmapT :: (forall b. Data b => b -> b) -> AnnConName -> AnnConName #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> AnnConName -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> AnnConName -> r #

gmapQ :: (forall d. Data d => d -> u) -> AnnConName -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> AnnConName -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> AnnConName -> m AnnConName #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnConName -> m AnnConName #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> AnnConName -> m AnnConName #

Ord AnnConName 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Show AnnConName 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Outputable AnnConName 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

data KeywordId #

The different syntactic elements which are not represented in the AST.

Constructors

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 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Data KeywordId 
Instance details

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) -> 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 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Show KeywordId 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

Outputable KeywordId 
Instance details

Defined in Language.Haskell.GHC.ExactPrint.Types

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