haskell-tools-refactor-1.0.0.4: Refactoring Tool for Haskell

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Tools.Refactor.Monad

Contents

Description

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

Documentation

class Monad m => RefactorMonad m where Source #

A monad that can be used to refactor

Minimal complete definition

refactError, liftGhc

Methods

refactError :: String -> m a Source #

liftGhc :: Ghc a -> m a 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

type Refactor = ExceptT String Ghc Source #

The refactoring monad for the whole project

newtype LocalRefactorT m a Source #

Input and output information for the refactoring TODO: use multiple states instead of Either

Instances

MonadTrans LocalRefactorT Source # 

Methods

lift :: Monad m => m a -> LocalRefactorT m a #

RefactorMonad LocalRefactor Source # 
Monad m => MonadReader RefactorCtx (LocalRefactorT m) Source # 
Monad m => Monad (LocalRefactorT m) Source # 
Functor m => Functor (LocalRefactorT m) Source # 

Methods

fmap :: (a -> b) -> LocalRefactorT m a -> LocalRefactorT m b #

(<$) :: a -> LocalRefactorT m b -> LocalRefactorT m a #

Applicative m => Applicative (LocalRefactorT m) Source # 

Methods

pure :: a -> LocalRefactorT m a #

(<*>) :: LocalRefactorT m (a -> b) -> LocalRefactorT m a -> LocalRefactorT m b #

liftA2 :: (a -> b -> c) -> LocalRefactorT m a -> LocalRefactorT m b -> LocalRefactorT m c #

(*>) :: LocalRefactorT m a -> LocalRefactorT m b -> LocalRefactorT m b #

(<*) :: LocalRefactorT m a -> LocalRefactorT m b -> LocalRefactorT m a #

MonadIO m => MonadIO (LocalRefactorT m) Source # 

Methods

liftIO :: IO a -> LocalRefactorT m a #

GhcMonad m => GhcMonad (LocalRefactorT m) Source # 
(HasDynFlags m, Monad m) => HasDynFlags (LocalRefactorT m) Source # 
ExceptionMonad m => ExceptionMonad (LocalRefactorT m) Source # 
Monad m => MonadWriter [Either Name (SrcSpan, String, String)] (LocalRefactorT m) Source # 

data RefactorCtx Source #

The information a refactoring can use

Constructors

RefactorCtx 

Fields

Some instances missing from GHC

Orphan instances

GhcMonad m => GhcMonad (ExceptT s m) Source # 

Methods

getSession :: ExceptT s m HscEnv #

setSession :: HscEnv -> ExceptT s m () #

GhcMonad m => GhcMonad (StateT s m) Source # 

Methods

getSession :: StateT s m HscEnv #

setSession :: HscEnv -> StateT s m () #

GhcMonad m => GhcMonad (StateT s m) Source # 

Methods

getSession :: StateT s m HscEnv #

setSession :: HscEnv -> StateT s m () #

(GhcMonad m, Monoid s) => GhcMonad (WriterT s m) Source # 

Methods

getSession :: WriterT s m HscEnv #

setSession :: HscEnv -> WriterT s m () #

(Monad m, HasDynFlags m) => HasDynFlags (StateT s m) Source # 
(Monad m, HasDynFlags m) => HasDynFlags (StateT s m) Source # 
ExceptionMonad m => ExceptionMonad (ExceptT s m) Source # 

Methods

gcatch :: Exception e => ExceptT s m a -> (e -> ExceptT s m a) -> ExceptT s m a #

gmask :: ((ExceptT s m a -> ExceptT s m a) -> ExceptT s m b) -> ExceptT s m b #

gbracket :: ExceptT s m a -> (a -> ExceptT s m b) -> (a -> ExceptT s m c) -> ExceptT s m c #

gfinally :: ExceptT s m a -> ExceptT s m b -> ExceptT s m a #

ExceptionMonad m => ExceptionMonad (StateT s m) Source # 

Methods

gcatch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

gmask :: ((StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

gbracket :: StateT s m a -> (a -> StateT s m b) -> (a -> StateT s m c) -> StateT s m c #

gfinally :: StateT s m a -> StateT s m b -> StateT s m a #

ExceptionMonad m => ExceptionMonad (StateT s m) Source # 

Methods

gcatch :: Exception e => StateT s m a -> (e -> StateT s m a) -> StateT s m a #

gmask :: ((StateT s m a -> StateT s m a) -> StateT s m b) -> StateT s m b #

gbracket :: StateT s m a -> (a -> StateT s m b) -> (a -> StateT s m c) -> StateT s m c #

gfinally :: StateT s m a -> StateT s m b -> StateT s m a #

(ExceptionMonad m, Monoid s) => ExceptionMonad (WriterT s m) Source # 

Methods

gcatch :: Exception e => WriterT s m a -> (e -> WriterT s m a) -> WriterT s m a #

gmask :: ((WriterT s m a -> WriterT s m a) -> WriterT s m b) -> WriterT s m b #

gbracket :: WriterT s m a -> (a -> WriterT s m b) -> (a -> WriterT s m c) -> WriterT s m c #

gfinally :: WriterT s m a -> WriterT s m b -> WriterT s m a #

GhcMonad m => GhcMonad (ReaderT * s m) Source # 

Methods

getSession :: ReaderT * s m HscEnv #

setSession :: HscEnv -> ReaderT * s m () #

ExceptionMonad m => ExceptionMonad (ReaderT * s m) Source # 

Methods

gcatch :: Exception e => ReaderT * s m a -> (e -> ReaderT * s m a) -> ReaderT * s m a #

gmask :: ((ReaderT * s m a -> ReaderT * s m a) -> ReaderT * s m b) -> ReaderT * s m b #

gbracket :: ReaderT * s m a -> (a -> ReaderT * s m b) -> (a -> ReaderT * s m c) -> ReaderT * s m c #

gfinally :: ReaderT * s m a -> ReaderT * s m b -> ReaderT * s m a #