| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Development.IDE.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 ast => DynFlags -> Bool -> Located ast -> TransformT (Either String) (Anns, Located 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. (MonadFail m, Data a, ASTElement ast) => SrcSpan -> (Located ast -> TransformT m (Maybe (Located ast))) -> Graft m a
- genericGraftWithSmallestM :: forall m a ast. (Monad m, Data a, Typeable ast) => Proxy (Located ast) -> SrcSpan -> (DynFlags -> GenericM (TransformT m)) -> Graft m a
- genericGraftWithLargestM :: forall m a ast. (Monad m, Data a, Typeable ast) => Proxy (Located ast) -> SrcSpan -> (DynFlags -> 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)
- 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
- mkBindListT :: forall b m. (Data b, Monad m) => (Int -> b -> m [b]) -> GenericM m
- setPrecedingLinesT :: forall a (m :: Type -> Type). (Data a, Monad m) => Located a -> Int -> Int -> TransformT m ()
- everywhereM' :: forall m. Monad m => GenericM m -> GenericM m
Documentation
A transformation for grafting source trees together. Use the semigroup
instance to combine Grafts, and run them via transform.
Constructors
| Graft | |
Fields
| |
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 -> Bool -> 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)
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. (MonadFail m, Data a, ASTElement ast) => SrcSpan -> (Located ast -> TransformT m (Maybe (Located ast))) -> Graft m a Source #
genericGraftWithSmallestM Source #
Arguments
| :: 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 -> GenericM (TransformT m)) | |
| -> Graft m a |
Run the given transformation only on the smallest node in the tree that
contains the SrcSpan.
genericGraftWithLargestM Source #
Arguments
| :: 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 -> 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.
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 #
Constructors
| GetAnnotatedParsedSource |
Instances
class (Data ast, Outputable ast) => ASTElement ast where Source #
Minimal complete definition
Methods
parseAST :: Parser (Located ast) Source #
maybeParensAST :: Located ast -> Located ast Source #
graft :: forall a. Data a => SrcSpan -> Located ast -> Graft (Either String) a 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 Methods parseAST :: Parser (Located (ImportDecl p)) Source # maybeParensAST :: Located (ImportDecl p) -> Located (ImportDecl p) Source # graft :: Data a => SrcSpan -> Located (ImportDecl p) -> Graft (Either String) a Source # | |
| p ~ GhcPs => ASTElement (Pat p) Source # | |
newtype ExceptStringT m a Source #
Constructors
| ExceptStringT | |
Fields
| |
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 #
Minimal complete definition
Instances
mkBindListT :: forall b m. (Data b, Monad m) => (Int -> b -> m [b]) -> GenericM m Source #
Lift a function that replaces a value with several values into a generic
function. The result doesn't perform any searching, so should be driven via
everywhereM or friends.
The Int argument is the index in the list being bound.
setPrecedingLinesT :: forall a (m :: Type -> Type). (Data a, Monad m) => Located a -> Int -> Int -> TransformT m () #
Transform monad version of setPrecedingLines