Safe Haskell | None |
---|
This package provides functions to clean import lists, to split up modules, and to merge modules. The important entry points are:
There are several features worth noting. The Params
type in the
state of MonadClean
has a removeEmptyImports
field, which is
True by default. This determines whether imports that turn into
empty lists are preserved or not - if your program needs instances
from a such an import, you will either want to set this flag to
False or (better) add an empty import list to the import.
These are the important entry points:
-
runCleanT
- Sets up the environment for splitting and merging. These operations require updates to be made to all the modules that import the modules being split or merged, so this environment tracks the creation and removal of modules. This allows a sequence of splits and merges to be performed without forgetting to update newly created modules. -
cleanImports
- uses ghc's -ddump-minimal-imports flag to generate minimized and explicit imports and re-insert them into the module. -
splitModule
- Splits a module into two or more parts according to the argument function. -
splitModuleDecls
- CallssplitModule
with a default first argument. Each declaration goes into a different module, and separate modules are created for instances and re-exports. Decls that were local to the original module go into a subdirectory namedInternal
. Symbols which can't be turned into valid module names go intoOtherSymbols
. -
mergeModules
- the inverse operation ofsplitModule
, it merges two or more modules into a new or existing module, updating imports of the moduVerse elements as necessary.
Examples:
- Use
findHsFiles
andcleanImports
to clean up the import lists of all the modules under./Language
:
findHsFiles ["Language", "Tests.hs", "Tests"] >>= runCleanT . cleanImports
- Split the module
Language.Haskell.Modules.Common
, and then merge two of the declarations back in:
:m +Language.Haskell.Exts.Syntax findHsModules ["Language", "Tests.hs", "Tests"] >>= \ modules -> runCleanT $ mapM putModule modules >> splitModuleDecls "Language/Haskell/Modules/Common.hs" >> mergeModules [ModuleName "Language.Haskell.Modules.Common.WithCurrentDirectory", ModuleName "Language.Haskell.Modules.Common.Internal.ToEq"] (ModuleName "Language.Haskell.Modules.Common")
- Move two declarations from Internal to Common. The intermediate module
Tmp
is used because using existing modules for a split is not allowed. The exception to this is that you can leave declarations in the original module.
findHsModules ["Language", "Tests.hs", "Tests"] >>= \ modules -> runCleanT $ mapM putModule modules >> splitModule (\ n -> if elem n [Just (Ident "ModuleResult"), Just (Ident "doResult")] then ModuleName "Tmp" else ModuleName "Language.Haskell.Modules.Internal") (ModuleName "Language/Haskell/Modules/Internal.hs") >> mergeModules [ModuleName "Language.Haskell.Modules.Common", ModuleName "Tmp"] (ModuleName "Language.Haskell.Modules.Common")
- Split a module where one of the result modules needs to import the instances:
runCleanT $ putModule (ModuleName "Main") >> extraImport (ModuleName "Main.GetPasteById") (ModuleName "Main.Instances") >> splitModuleDecls "Main.hs"
- cleanImports :: MonadClean m => [FilePath] -> m [ModuleResult]
- splitModule :: MonadClean m => (Maybe Name -> ModuleName) -> FilePath -> m [ModuleResult]
- splitModuleDecls :: MonadClean m => FilePath -> m [ModuleResult]
- defaultSymbolToModule :: ModuleInfo -> Maybe Name -> ModuleName
- mergeModules :: MonadClean m => [ModuleName] -> ModuleName -> m [ModuleResult]
- class (MonadIO m, MonadBaseControl IO m, Functor m) => MonadClean m
- type CleanT m = StateT Params m
- runCleanT :: (MonadIO m, MonadBaseControl IO m) => CleanT m a -> m a
- putModule :: (ModuVerse m, MonadVerbosity m) => ModuleName -> m ()
- findModule :: (ModuVerse m, MonadVerbosity m) => ModuleName -> m (Maybe ModuleInfo)
- modifyDryRun :: MonadClean m => (Bool -> Bool) -> m ()
- modifyHsFlags :: MonadClean m => ([String] -> [String]) -> m ()
- modifyRemoveEmptyImports :: MonadClean m => (Bool -> Bool) -> m ()
- modifyExtensions :: ModuVerse m => ([Extension] -> [Extension]) -> m ()
- modifyTestMode :: MonadClean m => (Bool -> Bool) -> m ()
- modifyDirs :: SourceDirs m => ([FilePath] -> [FilePath]) -> m ()
- putDirs :: SourceDirs m => [FilePath] -> m ()
- extraImport :: MonadClean m => ModuleName -> ModuleName -> m ()
- noisily :: MonadVerbosity m => m a -> m a
- quietly :: MonadVerbosity m => m a -> m a
- newtype ModuleName = ModuleName String
- data Name
- modulePathBase :: String -> ModuleName -> RelPath
- findHsModules :: [FilePath] -> IO [ModuleName]
- findHsFiles :: [FilePath] -> IO [FilePath]
- withCurrentDirectory :: (MonadIO m, MonadBaseControl IO m) => FilePath -> m a -> m a
Entry points
cleanImports :: MonadClean m => [FilePath] -> m [ModuleResult]Source
Clean up the imports of a source file. This means:
- All import lines get an explict list of symbols
- Imports of unused symbols are removed
- Imports of modules whose symbol list becomse empty are
removed, unless the
removeEmptyImports
flag is set toFalse
. However, imports that started out with an empty import list()
are retained - Repeated imports are merged
- Imports are alphabetized by module name
- Imported symbols are alphabetized by symbol name
- Imported constructors and field accessors are alphabetized
:: MonadClean m | |
=> (Maybe Name -> ModuleName) | Map each symbol name to the module it will be moved
to. The name |
-> FilePath | The file containing the input module. |
-> m [ModuleResult] |
Split the declarations of the module in the input file into new
modules as specified by the symToModule
function, which maps
symbol name's to module names. It is permissable for the output
function to map one or more symbols to the original module. The
modules will be written into files whose names are constructed from
the module name in the usual way, but with a prefix taken from the
first element of the list of directories in the SourceDirs
list.
This list is just [.]
by default.
:: MonadClean m | |
=> FilePath | The file containing the input module. |
-> m [ModuleResult] |
Split each of a module's declarations into a new module. Update the imports of all the modules in the moduVerse to reflect the split. For example, if you have a module like
module Start (a, b, (.+.)) where import a = 1 + a b = 2 c = 3 c' = 4 (.+.) = b + c
After running splitModuleDecls Start.hs
the Start
module will
be gone. The a
and b
symbols will be in new modules named
Start.A
and Start.B
. Because they were not exported by
Start
, the c
and c'
symbols will both be in a new module
named Start.Internal.C
. And the .+.
symbol will be in a module
named Start.OtherSymbols
. Note that this module needs to import
new Start.A
and Start.Internal.C
modules.
If we had imported and then re-exported a symbol in Start it would
go into a module named Start.ReExported
. Any instance declarations
would go into Start.Instances
.
:: ModuleInfo | Parent module name |
-> Maybe Name | |
-> ModuleName |
This can be used to build the function parameter of splitModule
,
it determines which module should a symbol be moved to.
mergeModules :: MonadClean m => [ModuleName] -> ModuleName -> m [ModuleResult]Source
Merge the declarations from several modules into a single new one, updating the imports of the modules in the moduVerse to reflect the change. It *is* permissable to use one of the input modules as the output module. Note that circular imports can be created by this operation.
Runtime environment
class (MonadIO m, MonadBaseControl IO m, Functor m) => MonadClean m Source
(MonadIO m, MonadBaseControl IO m, Functor m) => MonadClean (CleanT m) |
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
.
putModule :: (ModuVerse m, MonadVerbosity m) => ModuleName -> m ()Source
findModule :: (ModuVerse m, MonadVerbosity m) => ModuleName -> m (Maybe ModuleInfo)Source
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.)
modifyHsFlags :: MonadClean m => ([String] -> [String]) -> m ()Source
Modify the list of extra flags passed to GHC. Default is []
.
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.
modifyExtensions :: ModuVerse m => ([Extension] -> [Extension]) -> m ()Source
Modify the list of extensions passed to GHC when dumping the minimal imports. Note that GHC will also use the extensions in the module's LANGUAGE pragma, so this can usually be left alone.
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?)
modifyDirs :: SourceDirs m => ([FilePath] -> [FilePath]) -> m ()Source
Modify the list of directories that will be searched for imported modules.
putDirs :: SourceDirs m => [FilePath] -> m ()Source
Set the list of directories that will be searched for imported modules. Similar to the Hs-Source-Dirs field in the cabal file.
extraImport :: MonadClean m => ModuleName -> ModuleName -> m ()Source
When we write module m
, insert an extra line that imports the
instances (only) from module i
.
Progress reporting
noisily :: MonadVerbosity m => m a -> m aSource
Increase the amount of progress reporting during an action.
quietly :: MonadVerbosity m => m a -> m aSource
Decrease the amount of progress reporting during an action.
Re-Exports from haskell-src-exts
newtype ModuleName
The name of a Haskell module.
data Name
This type is used to represent variables, and also constructors.
Helper functions
modulePathBase :: String -> ModuleName -> RelPathSource
findHsModules :: [FilePath] -> IO [ModuleName]Source
Convenience function for building the moduVerse, searches for modules in a directory hierarchy. FIXME: This should be in MonadClean and use the value of sourceDirs to remove prefixes from the module paths. And then it should look at the module text to see what the module name really is.
findHsFiles :: [FilePath] -> IO [FilePath]Source
Find the paths of all the files below the directory top
.
withCurrentDirectory :: (MonadIO m, MonadBaseControl IO m) => FilePath -> m a -> m aSource
Perform an action with the working directory set to path
.