Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module hosts various abstractions and utility functions to work with ghc-exactprint.
Synopsis
- newtype Graft m a = Graft {
- runGraft :: DynFlags -> a -> TransformT m a
- graftDecls :: forall a. HasDecls a => SrcSpan -> [LHsDecl GhcPs] -> Graft (Either String) a
- graftDeclsWithM :: forall a m. (HasDecls a, MonadFail m) => SrcSpan -> (LHsDecl GhcPs -> TransformT m (Maybe [LHsDecl GhcPs])) -> Graft m a
- annotate :: (ASTElement l ast, Outputable l) => DynFlags -> Bool -> LocatedAn l ast -> TransformT (Either String) (Anns, LocatedAn l ast)
- annotateDecl :: DynFlags -> LHsDecl GhcPs -> TransformT (Either String) (LHsDecl GhcPs)
- hoistGraft :: (forall x. m x -> n x) -> Graft m a -> Graft n a
- graftWithM :: forall ast m a l. (MonadFail m, Data a, Typeable l, ASTElement l ast) => SrcSpan -> (LocatedAn l ast -> TransformT m (Maybe (LocatedAn l ast))) -> Graft m a
- graftExprWithM :: forall m a. (MonadFail m, Data a) => SrcSpan -> (LHsExpr GhcPs -> TransformT m (Maybe (LHsExpr GhcPs))) -> Graft m a
- genericGraftWithSmallestM :: forall m a ast. (Monad m, Data a, Typeable ast) => Proxy (Located ast) -> SrcSpan -> (DynFlags -> ast -> GenericM (TransformT m)) -> Graft m a
- genericGraftWithLargestM :: forall m a ast. (Monad m, Data a, Typeable ast) => Proxy (Located ast) -> SrcSpan -> (DynFlags -> ast -> GenericM (TransformT m)) -> Graft m a
- graftSmallestDeclsWithM :: forall a. HasDecls a => SrcSpan -> (LHsDecl GhcPs -> TransformT (Either String) (Maybe [LHsDecl GhcPs])) -> Graft (Either String) a
- transform :: DynFlags -> ClientCapabilities -> Uri -> Graft (Either String) ParsedSource -> Annotated ParsedSource -> Either String WorkspaceEdit
- transformM :: Monad m => DynFlags -> ClientCapabilities -> Uri -> Graft (ExceptStringT m) ParsedSource -> Annotated ParsedSource -> m (Either String WorkspaceEdit)
- class ExactPrint ast where
- makeDeltaAst :: ast -> ast
- type Anns = Map AnnKey Annotation
- class Data ast => Annotate ast
- setPrecedingLinesT :: forall a (m :: Type -> Type). (Data a, Monad m) => Located a -> Int -> Int -> TransformT m ()
- annotateParsedSource :: ParsedModule -> Annotated ParsedSource
- getAnnotatedParsedSourceRule :: Recorder (WithPriority Log) -> Rules ()
- data GetAnnotatedParsedSource = GetAnnotatedParsedSource
- class (Data ast, Typeable l, Outputable l, Outputable ast) => ASTElement l ast | ast -> l where
- newtype ExceptStringT m a = ExceptStringT {
- runExceptString :: ExceptT String m a
- data TransformT (m :: Type -> Type) a
- data Log = LogShake Log
Documentation
A transformation for grafting source trees together. Use the semigroup
instance to combine Graft
s, and run them via transform
.
Graft | |
|
graftDecls :: forall a. HasDecls a => SrcSpan -> [LHsDecl GhcPs] -> Graft (Either String) a Source #
graftDeclsWithM :: forall a m. (HasDecls a, MonadFail m) => SrcSpan -> (LHsDecl GhcPs -> TransformT m (Maybe [LHsDecl GhcPs])) -> Graft m a Source #
annotate :: (ASTElement l ast, Outputable l) => DynFlags -> Bool -> LocatedAn l ast -> TransformT (Either String) (Anns, LocatedAn l ast) Source #
Given an LHSExpr
, compute its exactprint annotations.
Note that this function will throw away any existing annotations (and format)
annotateDecl :: DynFlags -> LHsDecl GhcPs -> TransformT (Either String) (LHsDecl GhcPs) Source #
Given an LHsDecl
, compute its exactprint annotations.
hoistGraft :: (forall x. m x -> n x) -> Graft m a -> Graft n a Source #
graftWithM :: forall ast m a l. (MonadFail m, Data a, Typeable l, ASTElement l ast) => SrcSpan -> (LocatedAn l ast -> TransformT m (Maybe (LocatedAn l ast))) -> Graft m a Source #
graftExprWithM :: forall m a. (MonadFail m, Data a) => SrcSpan -> (LHsExpr GhcPs -> TransformT m (Maybe (LHsExpr GhcPs))) -> Graft m a Source #
genericGraftWithSmallestM Source #
:: forall m a ast. (Monad m, Data a, Typeable ast) | |
=> Proxy (Located ast) | The type of nodes we'd like to consider when finding the smallest. |
-> SrcSpan | |
-> (DynFlags -> ast -> GenericM (TransformT m)) | |
-> Graft m a |
Run the given transformation only on the smallest node in the tree that
contains the SrcSpan
.
genericGraftWithLargestM Source #
:: forall m a ast. (Monad m, Data a, Typeable ast) | |
=> Proxy (Located ast) | The type of nodes we'd like to consider when finding the largest. |
-> SrcSpan | |
-> (DynFlags -> ast -> GenericM (TransformT m)) | |
-> Graft m a |
Run the given transformation only on the largest node in the tree that
contains the SrcSpan
.
graftSmallestDeclsWithM :: forall a. HasDecls a => SrcSpan -> (LHsDecl GhcPs -> TransformT (Either String) (Maybe [LHsDecl GhcPs])) -> Graft (Either String) a Source #
transform :: DynFlags -> ClientCapabilities -> Uri -> Graft (Either String) ParsedSource -> Annotated ParsedSource -> Either String WorkspaceEdit Source #
Convert a Graft
into a WorkspaceEdit
.
transformM :: Monad m => DynFlags -> ClientCapabilities -> Uri -> Graft (ExceptStringT m) ParsedSource -> Annotated ParsedSource -> m (Either String WorkspaceEdit) Source #
Convert a Graft
into a WorkspaceEdit
.
class ExactPrint ast where Source #
Nothing
makeDeltaAst :: ast -> ast Source #
Instances
ExactPrint ast Source # | |
Defined in Development.IDE.GHC.Compat.ExactPrint makeDeltaAst :: ast -> ast Source # |
type Anns = Map AnnKey Annotation #
This structure holds a complete set of annotations for an AST
class Data ast => Annotate ast #
Instances
setPrecedingLinesT :: forall a (m :: Type -> Type). (Data a, Monad m) => Located a -> Int -> Int -> TransformT m () #
Transform
monad version of setPrecedingLines
getAnnotatedParsedSourceRule :: Recorder (WithPriority Log) -> Rules () Source #
Get the latest version of the annotated parse source with comments.
data GetAnnotatedParsedSource Source #
Instances
Eq GetAnnotatedParsedSource Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
Show GetAnnotatedParsedSource Source # | |
Defined in Development.IDE.GHC.ExactPrint showsPrec :: Int -> GetAnnotatedParsedSource -> ShowS # show :: GetAnnotatedParsedSource -> String # showList :: [GetAnnotatedParsedSource] -> ShowS # | |
Generic GetAnnotatedParsedSource Source # | |
Defined in Development.IDE.GHC.ExactPrint type Rep GetAnnotatedParsedSource :: Type -> Type # | |
Hashable GetAnnotatedParsedSource Source # | |
Defined in Development.IDE.GHC.ExactPrint hashWithSalt :: Int -> GetAnnotatedParsedSource -> Int # hash :: GetAnnotatedParsedSource -> Int # | |
NFData GetAnnotatedParsedSource Source # | |
Defined in Development.IDE.GHC.ExactPrint rnf :: GetAnnotatedParsedSource -> () # | |
type Rep GetAnnotatedParsedSource Source # | |
type RuleResult GetAnnotatedParsedSource Source # | |
Defined in Development.IDE.GHC.ExactPrint |
class (Data ast, Typeable l, Outputable l, Outputable ast) => ASTElement l ast | ast -> l where Source #
parseAST :: Parser (LocatedAn l ast) Source #
maybeParensAST :: LocatedAn l ast -> LocatedAn l ast Source #
graft :: forall a. Data a => SrcSpan -> LocatedAn l ast -> Graft (Either String) a Source #
Instances
ASTElement NameAnn RdrName Source # | |
p ~ GhcPs => ASTElement AnnListItem (HsDecl p) Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
p ~ GhcPs => ASTElement AnnListItem (HsType p) Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
p ~ GhcPs => ASTElement AnnListItem (HsExpr p) Source # | |
Defined in Development.IDE.GHC.ExactPrint | |
p ~ GhcPs => ASTElement AnnListItem (ImportDecl p) Source # | |
Defined in Development.IDE.GHC.ExactPrint parseAST :: Parser (LocatedAn AnnListItem (ImportDecl p)) Source # maybeParensAST :: LocatedAn AnnListItem (ImportDecl p) -> LocatedAn AnnListItem (ImportDecl p) Source # graft :: Data a => SrcSpan -> LocatedAn AnnListItem (ImportDecl p) -> Graft (Either String) a Source # | |
p ~ GhcPs => ASTElement AnnListItem (Pat p) Source # | |
Defined in Development.IDE.GHC.ExactPrint |
newtype ExceptStringT m a Source #
Instances
data TransformT (m :: Type -> Type) a #
Monad transformer version of Transform
monad