module Distribution.Simple.JHC (
configure, getInstalledPackages, build, installLib, installExe
) where
import Distribution.PackageDescription
( PackageDescription(..), BuildInfo(..),
withLib,
Executable(..), withExe, Library(..),
libModules, hcOptions )
import Distribution.Simple.LocalBuildInfo
( LocalBuildInfo(..),
autogenModulesDir )
import Distribution.Simple.Compiler ( Compiler(..), CompilerFlavor(..), Flag,
PackageDB, extensionsToFlags )
import Language.Haskell.Extension (Extension(..))
import Distribution.Simple.Program ( ConfiguredProgram(..), jhcProgram,
ProgramConfiguration, userMaybeSpecifyPath,
requireProgram, lookupProgram,
rawSystemProgram, rawSystemProgramStdoutConf )
import Distribution.Version ( VersionRange(AnyVersion) )
import Distribution.Package ( PackageIdentifier(..), showPackageId,
parsePackageId )
import Distribution.Simple.Utils( createDirectoryIfMissingVerbose,
copyFileVerbose, exeExtension, die, info )
import System.FilePath ( (</>) )
import Distribution.Verbosity
import Distribution.Compat.ReadP
( readP_to_S, many, skipSpaces )
import Data.List ( nub, intersperse )
import Data.Char ( isSpace )
configure :: Verbosity -> Maybe FilePath -> Maybe FilePath
-> ProgramConfiguration -> IO (Compiler, ProgramConfiguration)
configure verbosity hcPath _hcPkgPath conf = do
(jhcProg, conf') <- requireProgram verbosity jhcProgram AnyVersion
(userMaybeSpecifyPath "jhc" hcPath conf)
let Just version = programVersion jhcProg
comp = Compiler {
compilerFlavor = JHC,
compilerId = PackageIdentifier "jhc" version,
compilerExtensions = jhcLanguageExtensions
}
return (comp, conf')
jhcLanguageExtensions :: [(Extension, Flag)]
jhcLanguageExtensions =
[(TypeSynonymInstances , "")
,(ForeignFunctionInterface , "")
,(NoImplicitPrelude , "--noprelude")
,(CPP , "-fcpp")
]
getInstalledPackages :: Verbosity -> PackageDB -> ProgramConfiguration
-> IO [PackageIdentifier]
getInstalledPackages verbosity _packagedb conf = do
str <- rawSystemProgramStdoutConf verbosity jhcProgram conf ["--list-libraries"]
case pCheck (readP_to_S (many (skipSpaces >> parsePackageId)) str) of
[ps] -> return ps
_ -> die "cannot parse package list"
where
pCheck :: [(a, [Char])] -> [a]
pCheck rs = [ r | (r,s) <- rs, all isSpace s ]
build :: PackageDescription -> LocalBuildInfo -> Verbosity -> IO ()
build pkg_descr lbi verbosity = do
let Just jhcProg = lookupProgram jhcProgram (withPrograms lbi)
withLib pkg_descr () $ \lib -> do
info verbosity "Building library..."
let libBi = libBuildInfo lib
let args = constructJHCCmdLine lbi libBi (buildDir lbi) verbosity
rawSystemProgram verbosity jhcProg (["-c"] ++ args ++ libModules pkg_descr)
let pkgid = showPackageId (package pkg_descr)
pfile = buildDir lbi </> "jhc-pkg.conf"
hlfile= buildDir lbi </> (pkgid ++ ".hl")
writeFile pfile $ jhcPkgConf pkg_descr
rawSystemProgram verbosity jhcProg ["--build-hl="++pfile, "-o", hlfile]
withExe pkg_descr $ \exe -> do
info verbosity ("Building executable "++exeName exe)
let exeBi = buildInfo exe
let out = buildDir lbi </> exeName exe
let args = constructJHCCmdLine lbi exeBi (buildDir lbi) verbosity
rawSystemProgram verbosity jhcProg (["-o",out] ++ args ++ [modulePath exe])
constructJHCCmdLine :: LocalBuildInfo -> BuildInfo -> FilePath -> Verbosity -> [String]
constructJHCCmdLine lbi bi _odir verbosity =
(if verbosity >= deafening then ["-v"] else [])
++ extensionsToFlags (compiler lbi) (extensions bi)
++ hcOptions JHC (options bi)
++ ["--noauto","-i-"]
++ ["-i", autogenModulesDir lbi]
++ concat [["-i", l] | l <- nub (hsSourceDirs bi)]
++ ["-optc" ++ opt | opt <- ccOptions bi]
++ (concat [ ["-p", showPackageId pkg] | pkg <- packageDeps lbi ])
jhcPkgConf :: PackageDescription -> String
jhcPkgConf pd =
let sline name sel = name ++ ": "++sel pd
Just lib = library pd
comma f l = concat $ intersperse "," $ map f l
in unlines [sline "name" (showPackageId . package)
,"exposed-modules: " ++ (comma id (exposedModules lib))
,"hidden-modules: " ++ (comma id (otherModules $ libBuildInfo lib))
]
installLib :: Verbosity -> FilePath -> FilePath -> PackageDescription -> Library -> IO ()
installLib verb dest build_dir pkg_descr _ = do
let p = showPackageId (package pkg_descr)++".hl"
createDirectoryIfMissingVerbose verb True dest
copyFileVerbose verb (build_dir </> p) (dest </> p)
installExe :: Verbosity -> FilePath -> FilePath -> PackageDescription -> Executable -> IO ()
installExe verb dest build_dir _ exe = do
let out = exeName exe </> exeExtension
createDirectoryIfMissingVerbose verb True dest
copyFileVerbose verb (build_dir </> out) (dest </> out)