module Distribution.Simple.Hugs (
configure,
buildLib,
buildExe,
install
) where
import Distribution.PackageDescription
( PackageDescription(..), BuildInfo(..), hcOptions,
Executable(..), withExe, Library(..), withLib, libModules )
import Distribution.ModuleName (ModuleName)
import qualified Distribution.ModuleName as ModuleName
import Distribution.Simple.Compiler
( CompilerFlavor(..), CompilerId(..), Compiler(..), Flag )
import Distribution.Simple.Program ( ProgramConfiguration, userMaybeSpecifyPath,
requireProgram, rawSystemProgramConf,
ffihugsProgram, hugsProgram )
import Distribution.Version
( Version(..) )
import Distribution.Simple.PreProcess ( ppCpp, runSimplePreProcessor )
import Distribution.Simple.PreProcess.Unlit
( unlit )
import Distribution.Simple.LocalBuildInfo
( LocalBuildInfo(..), ComponentLocalBuildInfo(..) )
import Distribution.Simple.BuildPaths
( autogenModuleName, autogenModulesDir,
dllExtension )
import Distribution.Simple.Utils
( createDirectoryIfMissingVerbose, installOrdinaryFiles
, withUTF8FileContents, writeFileAtomic, copyFileVerbose
, findFile, findFileWithExtension, findModuleFiles
, die, info, notice )
import Language.Haskell.Extension
( Extension(..) )
import System.FilePath ( (</>), takeExtension, (<.>),
searchPathSeparator, normalise, takeDirectory )
import Distribution.System
( OS(..), buildOS )
import Distribution.Text
( display )
import Distribution.Verbosity
import Data.Char ( isSpace )
import Data.Maybe ( mapMaybe, catMaybes )
import Control.Monad ( unless, when, filterM )
import Data.List ( nub, sort, isSuffixOf )
import System.Directory ( removeDirectoryRecursive )
import Distribution.Compat.CopyFile
( setFileExecutable )
import Distribution.Compat.Exception
configure :: Verbosity -> Maybe FilePath -> Maybe FilePath
-> ProgramConfiguration -> IO (Compiler, ProgramConfiguration)
configure verbosity hcPath _hcPkgPath conf = do
(_ffihugsProg, conf') <- requireProgram verbosity ffihugsProgram
(userMaybeSpecifyPath "ffihugs" hcPath conf)
(_hugsProg, conf'') <- requireProgram verbosity hugsProgram conf'
let comp = Compiler {
compilerId = CompilerId Hugs (Version [] []),
compilerExtensions = hugsLanguageExtensions
}
return (comp, conf'')
hugsLanguageExtensions :: [(Extension, Flag)]
hugsLanguageExtensions =
[(OverlappingInstances , "+o")
,(IncoherentInstances , "+oO")
,(HereDocuments , "+H")
,(TypeSynonymInstances , "-98")
,(RecursiveDo , "-98")
,(ParallelListComp , "-98")
,(MultiParamTypeClasses , "-98")
,(FunctionalDependencies , "-98")
,(Rank2Types , "-98")
,(PolymorphicComponents , "-98")
,(ExistentialQuantification , "-98")
,(ScopedTypeVariables , "-98")
,(ImplicitParams , "-98")
,(ExtensibleRecords , "-98")
,(RestrictedTypeSynonyms , "-98")
,(FlexibleContexts , "-98")
,(FlexibleInstances , "-98")
,(ForeignFunctionInterface , "")
,(EmptyDataDecls , "")
,(CPP , "")
]
buildLib :: Verbosity -> PackageDescription -> LocalBuildInfo
-> Library -> ComponentLocalBuildInfo -> IO ()
buildLib verbosity pkg_descr lbi lib _clbi = do
let pref = scratchDir lbi
createDirectoryIfMissingVerbose verbosity True pref
copyFileVerbose verbosity (autogenModulesDir lbi </> paths_modulename)
(pref </> paths_modulename)
compileBuildInfo verbosity pref [] (libModules lib) (libBuildInfo lib) lbi
where
paths_modulename = ModuleName.toFilePath (autogenModuleName pkg_descr)
<.> ".hs"
buildExe :: Verbosity -> PackageDescription -> LocalBuildInfo
-> Executable -> ComponentLocalBuildInfo -> IO ()
buildExe verbosity pkg_descr lbi
exe@Executable {modulePath=mainPath, buildInfo=bi} _clbi = do
let pref = scratchDir lbi
createDirectoryIfMissingVerbose verbosity True pref
let destDir = pref </> "programs"
let exeMods = otherModules bi
srcMainFile <- findFile (hsSourceDirs bi) mainPath
let exeDir = destDir </> exeName exe
let destMainFile = exeDir </> hugsMainFilename exe
copyModule verbosity (CPP `elem` extensions bi) bi lbi srcMainFile destMainFile
let destPathsFile = exeDir </> paths_modulename
copyFileVerbose verbosity (autogenModulesDir lbi </> paths_modulename)
destPathsFile
compileBuildInfo verbosity exeDir
(maybe [] (hsSourceDirs . libBuildInfo) (library pkg_descr)) exeMods bi lbi
compileFiles verbosity bi lbi exeDir [destMainFile, destPathsFile]
where
paths_modulename = ModuleName.toFilePath (autogenModuleName pkg_descr)
<.> ".hs"
compileBuildInfo :: Verbosity
-> FilePath
-> [FilePath]
-> [ModuleName]
-> BuildInfo
-> LocalBuildInfo
-> IO ()
compileBuildInfo verbosity destDir mLibSrcDirs mods bi lbi = do
let useCpp = CPP `elem` extensions bi
let srcDir = buildDir lbi
srcDirs = nub $ srcDir : hsSourceDirs bi ++ mLibSrcDirs
info verbosity $ "Source directories: " ++ show srcDirs
flip mapM_ mods $ \ m -> do
fs <- findFileWithExtension suffixes srcDirs (ModuleName.toFilePath m)
case fs of
Nothing ->
die ("can't find source for module " ++ display m)
Just srcFile -> do
let ext = takeExtension srcFile
copyModule verbosity useCpp bi lbi srcFile
(destDir </> ModuleName.toFilePath m <.> ext)
stubsFileLists <- fmap catMaybes $ sequence
[ findFileWithExtension suffixes [destDir] (ModuleName.toFilePath modu)
| modu <- mods]
compileFiles verbosity bi lbi destDir stubsFileLists
suffixes :: [String]
suffixes = ["hs", "lhs"]
copyModule :: Verbosity -> Bool -> BuildInfo -> LocalBuildInfo -> FilePath -> FilePath -> IO ()
copyModule verbosity cppAll bi lbi srcFile destFile = do
createDirectoryIfMissingVerbose verbosity True (takeDirectory destFile)
(exts, opts, _) <- getOptionsFromSource srcFile
let ghcOpts = [ op | (GHC, ops) <- opts, op <- ops ]
if cppAll || CPP `elem` exts || "-cpp" `elem` ghcOpts then do
runSimplePreProcessor (ppCpp bi lbi) srcFile destFile verbosity
return ()
else
copyFileVerbose verbosity srcFile destFile
compileFiles :: Verbosity -> BuildInfo -> LocalBuildInfo -> FilePath -> [FilePath] -> IO ()
compileFiles verbosity bi lbi modDir fileList = do
ffiFileList <- filterM testFFI fileList
unless (null ffiFileList) $ do
notice verbosity "Compiling FFI stubs"
mapM_ (compileFFI verbosity bi lbi modDir) ffiFileList
testFFI :: FilePath -> IO Bool
testFFI file =
withHaskellFile file $ \inp ->
return $! "foreign" `elem` symbols (stripComments False inp)
compileFFI :: Verbosity -> BuildInfo -> LocalBuildInfo -> FilePath -> FilePath -> IO ()
compileFFI verbosity bi lbi modDir file = do
(_, opts, file_incs) <- getOptionsFromSource file
let ghcOpts = [ op | (GHC, ops) <- opts, op <- ops ]
let pkg_incs = ["\"" ++ inc ++ "\"" | inc <- includes bi]
let incs = nub (sort (file_incs ++ includeOpts ghcOpts ++ pkg_incs))
let pathFlag = "-P" ++ modDir ++ [searchPathSeparator]
let hugsArgs = "-98" : pathFlag : map ("-i" ++) incs
cfiles <- getCFiles file
let cArgs =
["-I" ++ dir | dir <- includeDirs bi] ++
ccOptions bi ++
cfiles ++
["-L" ++ dir | dir <- extraLibDirs bi] ++
ldOptions bi ++
["-l" ++ lib | lib <- extraLibs bi] ++
concat [["-framework", f] | f <- frameworks bi]
rawSystemProgramConf verbosity ffihugsProgram (withPrograms lbi)
(hugsArgs ++ file : cArgs)
includeOpts :: [String] -> [String]
includeOpts [] = []
includeOpts ("-#include" : arg : opts) = arg : includeOpts opts
includeOpts (_ : opts) = includeOpts opts
getCFiles :: FilePath -> IO [String]
getCFiles file =
withHaskellFile file $ \inp ->
let cfiles =
[ normalise cfile
| "{-#" : "CFILES" : rest <- map words
$ lines
$ stripComments True inp
, last rest == "#-}"
, cfile <- init rest]
in seq (length cfiles) (return cfiles)
symbols :: String -> [String]
symbols cs = case lex cs of
(sym, cs'):_ | not (null sym) -> sym : symbols cs'
_ -> []
withHaskellFile :: FilePath -> (String -> IO a) -> IO a
withHaskellFile file action =
withUTF8FileContents file $ \text ->
if ".lhs" `isSuffixOf` file
then either action die (unlit file text)
else action text
getOptionsFromSource
:: FilePath
-> IO ([Extension],
[(CompilerFlavor,[String])],
[String]
)
getOptionsFromSource file =
withHaskellFile file $
(return $!)
. foldr appendOptions ([],[],[]) . map getOptions
. takeWhileJust . map getPragma
. filter textLine . map (dropWhile isSpace) . lines
. stripComments True
where textLine [] = False
textLine ('#':_) = False
textLine _ = True
getPragma :: String -> Maybe [String]
getPragma line = case words line of
("{-#" : rest) | last rest == "#-}" -> Just (init rest)
_ -> Nothing
getOptions ("OPTIONS":opts) = ([], [(GHC, opts)], [])
getOptions ("OPTIONS_GHC":opts) = ([], [(GHC, opts)], [])
getOptions ("OPTIONS_NHC98":opts) = ([], [(NHC, opts)], [])
getOptions ("OPTIONS_HUGS":opts) = ([], [(Hugs, opts)], [])
getOptions ("LANGUAGE":ws) = (mapMaybe readExtension ws, [], [])
where readExtension :: String -> Maybe Extension
readExtension w = case reads w of
[(ext, "")] -> Just ext
[(ext, ",")] -> Just ext
_ -> Nothing
getOptions ("INCLUDE":ws) = ([], [], ws)
getOptions _ = ([], [], [])
appendOptions (exts, opts, incs) (exts', opts', incs')
= (exts++exts', opts++opts', incs++incs')
takeWhileJust :: [Maybe a] -> [a]
takeWhileJust (Just x:xs) = x : takeWhileJust xs
takeWhileJust _ = []
stripComments
:: Bool
-> String
-> String
stripComments keepPragmas = stripCommentsLevel 0
where stripCommentsLevel :: Int -> String -> String
stripCommentsLevel 0 ('"':cs) = '"':copyString cs
stripCommentsLevel 0 ('-':'-':cs) =
stripCommentsLevel 0 (dropWhile (/= '\n') cs)
stripCommentsLevel 0 ('{':'-':'#':cs)
| keepPragmas = '{' : '-' : '#' : copyPragma cs
stripCommentsLevel n ('{':'-':cs) = stripCommentsLevel (n+1) cs
stripCommentsLevel 0 (c:cs) = c : stripCommentsLevel 0 cs
stripCommentsLevel n ('-':'}':cs) = stripCommentsLevel (n1) cs
stripCommentsLevel n (_:cs) = stripCommentsLevel n cs
stripCommentsLevel _ [] = []
copyString ('\\':c:cs) = '\\' : c : copyString cs
copyString ('"':cs) = '"' : stripCommentsLevel 0 cs
copyString (c:cs) = c : copyString cs
copyString [] = []
copyPragma ('#':'-':'}':cs) = '#' : '-' : '}' : stripCommentsLevel 0 cs
copyPragma (c:cs) = c : copyPragma cs
copyPragma [] = []
install
:: Verbosity
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> (FilePath,FilePath)
-> PackageDescription
-> IO ()
install verbosity libDir installProgDir binDir targetProgDir buildPref (progprefix,progsuffix) pkg_descr = do
removeDirectoryRecursive libDir `catchIO` \_ -> return ()
withLib pkg_descr $ \ lib ->
findModuleFiles [buildPref] hugsInstallSuffixes (libModules lib)
>>= installOrdinaryFiles verbosity libDir
let buildProgDir = buildPref </> "programs"
when (any (buildable . buildInfo) (executables pkg_descr)) $
createDirectoryIfMissingVerbose verbosity True binDir
withExe pkg_descr $ \ exe -> do
let theBuildDir = buildProgDir </> exeName exe
let installDir = installProgDir </> exeName exe
let targetDir = targetProgDir </> exeName exe
removeDirectoryRecursive installDir `catchIO` \_ -> return ()
findModuleFiles [theBuildDir] hugsInstallSuffixes
(ModuleName.main : autogenModuleName pkg_descr
: otherModules (buildInfo exe))
>>= installOrdinaryFiles verbosity installDir
let targetName = "\"" ++ (targetDir </> hugsMainFilename exe) ++ "\""
let hugsOptions = hcOptions Hugs (buildInfo exe)
let baseExeFile = progprefix ++ (exeName exe) ++ progsuffix
let exeFile = case buildOS of
Windows -> binDir </> baseExeFile <.> ".bat"
_ -> binDir </> baseExeFile
let script = case buildOS of
Windows ->
let args = hugsOptions ++ [targetName, "%*"]
in unlines ["@echo off",
unwords ("runhugs" : args)]
_ ->
let args = hugsOptions ++ [targetName, "\"$@\""]
in unlines ["#! /bin/sh",
unwords ("runhugs" : args)]
writeFileAtomic exeFile script
setFileExecutable exeFile
hugsInstallSuffixes :: [String]
hugsInstallSuffixes = [".hs", ".lhs", dllExtension]
hugsMainFilename :: Executable -> FilePath
hugsMainFilename exe = "Main" <.> ext
where ext = takeExtension (modulePath exe)