| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Development.IDE.Plugin.CodeAction.ExactPrint
Contents
Synopsis
- data Rewrite where
- rewriteToEdit :: HasCallStack => DynFlags -> Anns -> Rewrite -> Either String [TextEdit]
- rewriteToWEdit :: DynFlags -> Uri -> Anns -> Rewrite -> Either String WorkspaceEdit
- transferAnn :: (Data a, Data b) => Located a -> Located b -> (Annotation -> Annotation) -> TransformT (Either String) ()
- appendConstraint :: String -> LHsType GhcPs -> Rewrite
- removeConstraint :: (LHsType GhcPs -> Bool) -> LHsType GhcPs -> Rewrite
- extendImport :: Maybe String -> String -> LImportDecl GhcPs -> Rewrite
- hideSymbol :: String -> LImportDecl GhcPs -> Rewrite
- liftParseAST :: forall ast l. (ASTElement l ast, ExactPrint (LocatedAn l ast)) => DynFlags -> String -> TransformT (Either String) (LocatedAn l ast)
- wildCardSymbol :: String
Documentation
rewriteToEdit :: HasCallStack => DynFlags -> Anns -> Rewrite -> Either String [TextEdit] Source #
Convert a Rewrite into a list of '[TextEdit]'.
rewriteToWEdit :: DynFlags -> Uri -> Anns -> Rewrite -> Either String WorkspaceEdit Source #
Convert a Rewrite into a WorkspaceEdit
transferAnn :: (Data a, Data b) => Located a -> Located b -> (Annotation -> Annotation) -> TransformT (Either String) () Source #
Copy anns attached to a into b with modification, then delete anns of a
Utilities
Arguments
| :: String | The new constraint to append | 
| -> LHsType GhcPs | The type signature where the constraint is to be inserted, also assuming annotated | 
| -> Rewrite | 
Append a constraint at the end of a type context. If no context is present, a new one will be created.
extendImport :: Maybe String -> String -> LImportDecl GhcPs -> Rewrite Source #
hideSymbol :: String -> LImportDecl GhcPs -> Rewrite Source #
Hide a symbol from import declaration
liftParseAST :: forall ast l. (ASTElement l ast, ExactPrint (LocatedAn l ast)) => DynFlags -> String -> TransformT (Either String) (LocatedAn l ast) Source #