Copyright | (C) 2015 Cindy Wang (CindyLinz) |
---|---|
License | MIT |
Maintainer | Cindy Wang (CindyLinz) <cindylinz@gmail.com> |
Stability | beta |
Portability | POSIX / Windows |
Safe Haskell | Safe |
Language | Haskell2010 |
System.Imports
Description
This module helps to automatically generate code for importing all the haskell files from directories.
Synopsis
For cabal inited project, we customize Setup.hs
file to generate the importing code.
- Be sure to modify the
build-type
field in the.cabal
file fromSimple
toCustom
. Then modify the
main
function inSetup.hs
to generate importing code by either header file or a module file.Setup.hs:
import Distribution.Simple import System.Imports (writeImportsHeader, writeImportsModule) main = do writeImportsHeader "imports.header" "Export" "Some.Where" "Some/Where" -- or writeImportsModule "ImportAll.hs" "ImportAll" "Some.Where" "Some/Where" defaultMain
Target.hs: (by header)
{-# LANGUAGE CPP #-} module Target where #include "imports.header" func = Export.funcFromSomeWhere
Target.hs: (by module)
module Target where import qualified ImportAll func = ImportAll.funcFromSomeWhere
- type Predictor = FilePath -> IO Bool
- defaultPred :: Predictor
- searchImportsWith :: Predictor -> FilePath -> IO [String]
- searchImports :: FilePath -> IO [String]
- importsContentWith :: Predictor -> String -> [(String, FilePath)] -> IO String
- importsContent :: String -> [(String, FilePath)] -> IO String
- writeMultiImportsHeaderWith :: Predictor -> FilePath -> String -> [(String, FilePath)] -> IO ()
- writeMultiImportsHeader :: FilePath -> String -> [(String, FilePath)] -> IO ()
- writeImportsHeaderWith :: Predictor -> FilePath -> String -> String -> FilePath -> IO ()
- writeImportsHeader :: FilePath -> String -> String -> FilePath -> IO ()
- writeMultiImportsModuleWith :: Predictor -> FilePath -> String -> [(String, FilePath)] -> IO ()
- writeMultiImportsModule :: FilePath -> String -> [(String, FilePath)] -> IO ()
- writeImportsModuleWith :: Predictor -> FilePath -> String -> String -> FilePath -> IO ()
- writeImportsModule :: FilePath -> String -> String -> FilePath -> IO ()
Documentation
defaultPred :: Predictor Source
The default predictor will skip files or directories whose names are beginned with '.' or '_'. And it will take only files whose extension are ".hs" or ".lhs"