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

Safe HaskellNone

Language.Haskell.Modules

Description

This package provides three functions. The cleanImports function uses ghc's -ddump-minimal-imports flag to generate minimized and explicit imports and re-insert them into the module.

The splitModule moves each declaration of a module into a separate new module, and may also create three additional modules: ReExported (for identifiers that were re-exported from other imports), Instances (for declarations that don't result in an identifier to export), and OtherSymbols (for declarations that can't be turned into a module name.)

In addition to creating new modules, splitModule also scans the a set of modules (known as the moduVerse) and updates their imports to account for the new locations of the symbols. The moduVerse is stored in MonadClean's state, and is updated as modules are created and destroyed by splitModule and catModules.

The catModules function is the inverse operation of splitModule, it merges two or more modules into a new or existing module, updating imports of the moduVerse elements as necessary.

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:

Examples:

  • Use cleanImports to clean up the import lists of all the modules under ./Language:
findPaths "Language" >>= runMonadClean . mapM cleanImports . toList
  • Use splitModule to split up module Language.Haskell.Modules.Common, and then merge two of the pieces back in.
findModules "Language" >>= \ modules -> runMonadClean $
      let mn = Language.Haskell.Exts.Syntax.ModuleName in
      modifyModuVerse (const modules) >>
      splitModule (mn "Language.Haskell.Modules.Common") >>
      mergeModules (map mn ["Language.Haskell.Modules.Common.WithCurrentDirectory",
                            "Language.Haskell.Modules.Common.ModulePathBase"])
                   (mn "Language.Haskell.Modules.Common"))

Synopsis

Documentation

cleanImports :: MonadClean m => FilePath -> m ModuleResultSource

Clean up the imports of a source file.

splitModule :: MonadClean m => ModuleName -> m ()Source

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 splitModule 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.

mergeModules :: MonadClean m => [ModuleName] -> ModuleName -> m (Set 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.

findModules :: FilePath -> IO (Set 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.

findPaths :: FilePath -> IO (Set FilePath)Source

Find the paths of all the files below the directory top.