Safe Haskell | None |
---|---|
Language | Haskell2010 |
Types and instances for monadic refactorings. The refactoring monad provides automatic importing, keeping important source fragments (such as preprocessor pragmas), and providing contextual information for refactorings.
Synopsis
- class Monad m => RefactorMonad m where
- type LocalRefactoring = UnnamedModule -> LocalRefactor UnnamedModule
- type Refactoring = ModuleDom -> [ModuleDom] -> Refactor [RefactorChange]
- type ProjectRefactoring = [ModuleDom] -> Refactor [RefactorChange]
- type LocalRefactor = LocalRefactorT Refactor
- type Refactor = ExceptT String Ghc
- newtype LocalRefactorT m a = LocalRefactorT {
- fromRefactorT :: WriterT [Either Name (SrcSpan, String, String)] (ReaderT RefactorCtx m) a
- data RefactorCtx = RefactorCtx {}
Documentation
class Monad m => RefactorMonad m where Source #
A monad that can be used to refactor
Instances
RefactorMonad Refactor Source # | |
RefactorMonad LocalRefactor Source # | |
Defined in Language.Haskell.Tools.Refactor.Monad refactError :: String -> LocalRefactor a Source # liftGhc :: Ghc a -> LocalRefactor a Source # | |
RefactorMonad m => RefactorMonad (StateT s m) Source # | |
RefactorMonad m => RefactorMonad (StateT s m) Source # | |
type LocalRefactoring = UnnamedModule -> LocalRefactor UnnamedModule Source #
A refactoring that only affects one module
type Refactoring = ModuleDom -> [ModuleDom] -> Refactor [RefactorChange] Source #
The type of a refactoring
type ProjectRefactoring = [ModuleDom] -> Refactor [RefactorChange] Source #
The type of a refactoring that affects the whole project.
type LocalRefactor = LocalRefactorT Refactor Source #
The refactoring monad for a given module
newtype LocalRefactorT m a Source #
Input and output information for the refactoring TODO: use multiple states instead of Either
LocalRefactorT | |
|
Instances
data RefactorCtx Source #
The information a refactoring can use
RefactorCtx | |
|
Instances
Monad m => MonadReader RefactorCtx (LocalRefactorT m) Source # | |
Defined in Language.Haskell.Tools.Refactor.Monad ask :: LocalRefactorT m RefactorCtx # local :: (RefactorCtx -> RefactorCtx) -> LocalRefactorT m a -> LocalRefactorT m a # reader :: (RefactorCtx -> a) -> LocalRefactorT m a # |