Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Graft m a = Graft {
- runGraft :: DynFlags -> a -> TransformT m a
- graft :: forall ast a. (Data a, ASTElement ast) => SrcSpan -> Located ast -> Graft (Either String) a
- graftWithoutParentheses :: forall ast a. (Data a, ASTElement ast) => SrcSpan -> Located ast -> Graft (Either String) 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 ast => DynFlags -> Located ast -> TransformT (Either String) (Anns, Located ast)
- hoistGraft :: (forall x. m x -> n x) -> Graft m a -> Graft n a
- graftWithM :: forall ast m a. (MonadFail m, Data a, ASTElement ast) => SrcSpan -> (Located ast -> TransformT m (Maybe (Located ast))) -> Graft m a
- graftWithSmallestM :: forall ast m a. (MonadFail m, Data a, ASTElement ast) => SrcSpan -> (Located ast -> TransformT m (Maybe (Located ast))) -> Graft m a
- graftSmallestDecls :: forall a. HasDecls a => SrcSpan -> [LHsDecl GhcPs] -> Graft (Either String) 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)
- useAnnotatedSource :: String -> IdeState -> NormalizedFilePath -> IO (Maybe (Annotated ParsedSource))
- annotateParsedSource :: ParsedModule -> Annotated ParsedSource
- getAnnotatedParsedSourceRule :: Rules ()
- data GetAnnotatedParsedSource = GetAnnotatedParsedSource
- class (Data ast, Outputable ast) => ASTElement ast where
- newtype ExceptStringT m a = ExceptStringT {
- runExceptString :: ExceptT String m a
- data Annotated ast
- data TransformT (m :: Type -> Type) a
- type Anns = Map AnnKey Annotation
- class Data ast => Annotate ast
Documentation
A transformation for grafting source trees together. Use the semigroup
instance to combine Graft
s, and run them via transform
.
Graft | |
|
graft :: forall ast a. (Data a, ASTElement ast) => SrcSpan -> Located ast -> Graft (Either String) a Source #
graftWithoutParentheses :: forall ast a. (Data a, ASTElement ast) => SrcSpan -> Located ast -> Graft (Either String) a Source #
Like graft
, but trusts that you have correctly inserted the parentheses
yourself. If you haven't, the resulting AST will not be valid!
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 ast => DynFlags -> Located ast -> TransformT (Either String) (Anns, Located ast) Source #
Given an LHSExpr
, compute its exactprint annotations.
Note that this function will throw away any existing annotations (and format)
hoistGraft :: (forall x. m x -> n x) -> Graft m a -> Graft n a Source #
graftWithM :: forall ast m a. (MonadFail m, Data a, ASTElement ast) => SrcSpan -> (Located ast -> TransformT m (Maybe (Located ast))) -> Graft m a Source #
graftWithSmallestM :: forall ast m a. (MonadFail m, Data a, ASTElement ast) => SrcSpan -> (Located ast -> TransformT m (Maybe (Located ast))) -> Graft m a Source #
graftSmallestDecls :: forall a. HasDecls a => SrcSpan -> [LHsDecl GhcPs] -> Graft (Either String) a Source #
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
.
useAnnotatedSource :: String -> IdeState -> NormalizedFilePath -> IO (Maybe (Annotated ParsedSource)) Source #
getAnnotatedParsedSourceRule :: Rules () Source #
Get the latest version of the annotated parse source with comments.
data GetAnnotatedParsedSource Source #
Instances
class (Data ast, Outputable ast) => ASTElement ast where Source #
Instances
ASTElement RdrName Source # | |
p ~ GhcPs => ASTElement (HsDecl p) Source # | |
p ~ GhcPs => ASTElement (HsType p) Source # | |
p ~ GhcPs => ASTElement (HsExpr p) Source # | |
p ~ GhcPs => ASTElement (ImportDecl p) Source # | |
Defined in Development.IDE.GHC.ExactPrint parseAST :: Parser (Located (ImportDecl p)) Source # maybeParensAST :: Located (ImportDecl p) -> Located (ImportDecl p) Source # | |
p ~ GhcPs => ASTElement (Pat p) Source # | |
newtype ExceptStringT m a Source #
Instances
Annotated
packages an AST fragment with the annotations necessary to
exactPrint
or transform
that AST.
Instances
data TransformT (m :: Type -> Type) a #
Monad transformer version of Transform
monad
Instances
type Anns = Map AnnKey Annotation #
This structure holds a complete set of annotations for an AST
class Data ast => Annotate ast #