imports-0.2.0.0: Generate code for importing directories automatically

Copyright(C) 2015 Cindy Wang (CindyLinz)
LicenseMIT
MaintainerCindy Wang (CindyLinz) <cindylinz@gmail.com>
Stabilitybeta
PortabilityPOSIX / Windows
Safe HaskellSafe
LanguageHaskell2010

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 from Simple to Custom.
  • Then modify the main function in Setup.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
    

Synopsis

Documentation

type Predictor Source

Arguments

 = FilePath

relative path from search root: "Bar/Ex/Ex2/Foo.hs" or "Bar/Ex/Ex2" (you should determine the path is whether a file or a directory)

-> IO Bool 

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"

searchImportsWith Source

Arguments

:: Predictor 
-> FilePath

path to the search root

-> IO [String]

something like ["Foo", "Foo.Bar", "Foo.Bar2"], relative to the search root

searchImports Source

Arguments

:: FilePath

path to the search root

-> IO [String]

something like ["Foo", "Foo.Bar", "Foo.Bar2"], relative to the search root

importsContentWith Source

Arguments

:: Predictor 
-> String

import alias

-> [(String, FilePath)]

[(prefix, search root)]

-> IO String

"import A as Alias\n.."

importsContent Source

Arguments

:: String

import alias

-> [(String, FilePath)]

[(prefix, search root)]

-> IO String

"import A as Alias\n.."

writeMultiImportsHeaderWith Source

Arguments

:: Predictor 
-> FilePath

import header file to write

-> String

import alias

-> [(String, FilePath)]

[(module name prefix, path to the search root)]

-> IO () 

writeMultiImportsHeader Source

Arguments

:: FilePath

import header file to write

-> String

import alias

-> [(String, FilePath)]

[(module name prefix, path to the search root)]

-> IO () 

writeImportsHeaderWith Source

Arguments

:: Predictor 
-> FilePath

import header file to write

-> String

import alias

-> String

module name prefix

-> FilePath

path to the search root

-> IO () 

writeImportsHeader Source

Arguments

:: FilePath

import header file to write

-> String

import alias

-> String

module name prefix

-> FilePath

path to the search root

-> IO () 

writeMultiImportsModuleWith Source

Arguments

:: Predictor 
-> FilePath

module file to write

-> String

module name

-> [(String, FilePath)]

[(module name prefix, path to the search root)]

-> IO () 

writeMultiImportsModule Source

Arguments

:: FilePath

module file to write

-> String

module name

-> [(String, FilePath)]

[(module name prefix, path to the search root)]

-> IO () 

writeImportsModuleWith Source

Arguments

:: Predictor 
-> FilePath

module file to write

-> String

module name

-> String

module name prefix

-> FilePath

path to the search root

-> IO () 

writeImportsModule Source

Arguments

:: FilePath

module file to write

-> String

module name

-> String

module name prefix

-> FilePath

path to the search root

-> IO ()