module-management-0.16.1: Clean up module imports, split and merge modules

Safe HaskellNone

Language.Haskell.Modules.Params

Description

Functions to control the state variables of MonadClean.

Synopsis

Documentation

data Params Source

This contains the information required to run the state monad for import cleaning and module spliting/mergeing.

Constructors

Params 

Fields

scratchDir :: FilePath

Location of the temporary directory for ghc output.

dryRun :: Bool

None of the operations that modify the modules will actually be performed if this is ture.

verbosity :: Int

Increase or decrease the amount of progress reporting.

hsFlags :: [String]

Extra flags to pass to GHC.

moduVerse :: ModuVerseState

The set of modules that splitModules and catModules will check for imports of symbols that moved.

junk :: Set FilePath

Paths added to this list are removed as the state monad finishes.

removeEmptyImports :: Bool

If true, remove any import that became empty due to the clean. THe import might still be required because of the instances it contains, but usually it is not. Note that this option does not affect imports that started empty and end empty.

extraImports :: Map ModuleName (Set ImportDecl)

Deciding whether a module needs to be imported can be difficult when instances are involved, this is a cheat to force keys of the map to import the corresponding elements.

testMode :: Bool

For testing, do not run cleanImports on the results of the splitModule and catModules operations.

type CleanT m = StateT Params mSource

An instance of MonadClean.

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.

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.