[Haskell-cafe] Re: cabal haddock hpc, exposed modules?
Greg Fitzgerald
garious at gmail.com
Tue Oct 27 20:35:30 EDT 2009
The workaround is for a script to traverse the filesystem and generate a
list of modules that can then be copied into the .cabal for haddock and
Setup.hs for hpc. If anyone else is trying to do the same, here's the code:
http://hpaste.org/fastcgi/hpaste.fcgi/view?id=11224#a11224
script copied below:
import System.Directory(doesDirectoryExist, getDirectoryContents)
import Data.Tree(unfoldTreeM, flatten)
import Control.Monad(filterM)
import System.FilePath(splitDirectories, dropExtension, takeExtension)
import Data.List(sort, intercalate)
main :: IO ()
main = do
paths <- modules
putStrLn (cabal paths)
putStrLn (hpc paths)
cabal :: [String] -> String
cabal xs = header ++ intercalate sep xs
where
header = " exposed-modules: "
sep = ",\n "
hpc :: [String] -> String
hpc = concatMap include
where
include x = pre ++ x ++ "\""
pre = "\n , \"--include="
modules :: IO [String]
modules = do
paths <- filePaths "."
return [modName p | p <- paths, takeExtension p == ".hs"]
where
modName = intercalate "." . splitDirectories . dropExtension
filePaths :: FilePath -> IO [FilePath]
filePaths path = do
tree <- unfoldTreeM childPaths path
filterM (fmap not . doesDirectoryExist) (flatten tree)
childPaths :: FilePath -> IO (FilePath, [String])
childPaths dir = do
b <- doesDirectoryExist dir
fs <- if b then getDirectoryContents dir else return []
return (dir, [dir ++ "/" ++ p | p <- fs, head p /= '.'])
-Greg
On Tue, Oct 27, 2009 at 2:33 PM, Greg Fitzgerald <garious at gmail.com> wrote:
> I have a cabal package that defines a few dozen modules, and I'm
> hoping to generate documentation and code coverage for all modules
> without listing each module explicitly.
>
> currently my .cabal includes:
>
> library
> exposed-modules:
> Language.Idl.Data,
> Language.Idl.Merge,
> Language.Idl.Parser,
> ...lots more...
>
>
> my Setup.hs includes an explicit system call to hpc:
>
> exec "hpc" ["markup"
> , "--include=Language.Idl.Data"
> , "--include=Language.Idl.Merge"
> , "--include=Language.Idl.Parser"
> ...all the same files as above...
> ]
>
> Questions:
> 1) Is there a way to create haddock docs for /all/ modules, instead of
> just the ones listed by 'exposed-modules'?
> 2) Is there a way to query cabal for the list of modules? Or by
> chance has hpc recently been integrated with cabal?
>
> Thanks,
> Greg
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20091027/2897bd40/attachment.html
More information about the Haskell-Cafe
mailing list