Safe Haskell | None |
---|
Functions to control the state variables of MonadClean
.
- data Params = Params {
- scratchDir :: FilePath
- dryRun :: Bool
- verbosity :: Int
- hsFlags :: [String]
- moduVerse :: ModuVerseState
- junk :: Set FilePath
- removeEmptyImports :: Bool
- extraImports :: Map ModuleName (Set ImportDecl)
- testMode :: Bool
- type CleanT m = StateT Params m
- class (MonadIO m, MonadBaseControl IO m, Functor m) => MonadClean m where
- modifyParams :: MonadClean m => (Params -> Params) -> m ()
- runCleanT :: (MonadIO m, MonadBaseControl IO m) => CleanT m a -> m a
- markForDelete :: MonadClean m => FilePath -> m ()
- modifyRemoveEmptyImports :: MonadClean m => (Bool -> Bool) -> m ()
- modifyHsFlags :: MonadClean m => ([String] -> [String]) -> m ()
- modifyDryRun :: MonadClean m => (Bool -> Bool) -> m ()
- modifyTestMode :: MonadClean m => (Bool -> Bool) -> m ()
- extraImport :: MonadClean m => ModuleName -> ModuleName -> m ()
Documentation
This contains the information required to run the state monad for import cleaning and module spliting/mergeing.
Params | |
|
class (MonadIO m, MonadBaseControl IO m, Functor m) => MonadClean m whereSource
(MonadIO m, MonadBaseControl IO m, Functor m) => MonadClean (CleanT m) |
modifyParams :: MonadClean m => (Params -> Params) -> m ()Source
runCleanT :: (MonadIO m, MonadBaseControl IO m) => CleanT m a -> m aSource
Create the environment required to do import cleaning and module
splitting/merging. This environment, StateT Params m a
, is an
instance of MonadClean
.
markForDelete :: MonadClean m => FilePath -> m ()Source
modifyRemoveEmptyImports :: MonadClean m => (Bool -> Bool) -> m ()Source
If this flag is set, imports that become empty are removed.
Sometimes this will lead to errors, specifically when an instance
in the removed import that was required is no longer be available.
(Note that this reflects a limitation of the
-ddump-minimal-imports
option of GHC.) If this happens this flag
should be set. Note that an import that is already empty when
cleanImports
runs will never be removed, on the assumption that
it was placed there only to import instances. Default is True.
modifyHsFlags :: MonadClean m => ([String] -> [String]) -> m ()Source
Modify the list of extra flags passed to GHC. Default is []
.
modifyDryRun :: MonadClean m => (Bool -> Bool) -> m ()Source
Controls whether file updates will actually be performed. Default is False. (I recommend running in a directory controlled by a version control system so you don't have to worry about this.)
modifyTestMode :: MonadClean m => (Bool -> Bool) -> m ()Source
If TestMode is turned on no import cleaning will occur after a split or cat. Default is False. Note that the modules produced with this option will often fail to compile to to circular imports. (Does this seem counterintuitive to anyone else?)
extraImport :: MonadClean m => ModuleName -> ModuleName -> m ()Source
When we write module m
, insert an extra line that imports the
instances (only) from module i
.