module Distribution.Simple.Hugs (
configure,
getInstalledPackages,
buildLib,
buildExe,
install,
registerPackage,
) where
import Distribution.Package
( PackageName, PackageIdentifier(..), InstalledPackageId(..)
, packageName )
import Distribution.InstalledPackageInfo
( InstalledPackageInfo, emptyInstalledPackageInfo
, InstalledPackageInfo_( InstalledPackageInfo, installedPackageId
, sourcePackageId )
, parseInstalledPackageInfo, showInstalledPackageInfo )
import Distribution.PackageDescription
( PackageDescription(..), BuildInfo(..), hcOptions, allExtensions
, Executable(..), withExe, Library(..), withLib, libModules )
import Distribution.ModuleName (ModuleName)
import qualified Distribution.ModuleName as ModuleName
import Distribution.Simple.Compiler
( CompilerFlavor(..), CompilerId(..)
, Compiler(..), Flag, languageToFlags, extensionsToFlags
, PackageDB(..), PackageDBStack )
import qualified Distribution.Simple.PackageIndex as PackageIndex
import Distribution.Simple.PackageIndex (PackageIndex)
import Distribution.Simple.Program
( Program(programFindVersion)
, ProgramConfiguration, userMaybeSpecifyPath
, requireProgram, requireProgramVersion
, rawSystemProgramConf, programPath
, ffihugsProgram, hugsProgram )
import Distribution.Version
( Version(..), orLaterVersion )
import Distribution.Simple.PreProcess ( ppCpp, runSimplePreProcessor )
import Distribution.Simple.PreProcess.Unlit
( unlit )
import Distribution.Simple.LocalBuildInfo
( LocalBuildInfo(..), ComponentLocalBuildInfo(..)
, InstallDirs(..), absoluteInstallDirs )
import Distribution.Simple.BuildPaths
( autogenModuleName, autogenModulesDir,
dllExtension )
import Distribution.Simple.Setup
( CopyDest(..) )
import Distribution.Simple.Utils
( createDirectoryIfMissingVerbose
, installOrdinaryFiles, setFileExecutable
, withUTF8FileContents, writeFileAtomic, writeUTF8File
, copyFileVerbose, findFile, findFileWithExtension, findModuleFiles
, rawSystemStdInOut
, die, info, notice )
import Language.Haskell.Extension
( Language(Haskell98), Extension(..), KnownExtension(..) )
import System.FilePath ( (</>), takeExtension, (<.>),
searchPathSeparator, normalise, takeDirectory )
import Distribution.System
( OS(..), buildOS )
import Distribution.Text
( display, simpleParse )
import Distribution.ParseUtils
( ParseResult(..) )
import Distribution.Verbosity
import Data.Char ( isSpace )
import Data.Maybe ( mapMaybe, catMaybes )
import Data.Monoid ( Monoid(..) )
import Control.Monad ( unless, when, filterM )
import Data.List ( nub, sort, isSuffixOf )
import System.Directory
( doesFileExist, doesDirectoryExist, getDirectoryContents
, removeDirectoryRecursive, getHomeDirectory )
import System.Exit
( ExitCode(ExitSuccess) )
import Distribution.Compat.Exception
configure :: Verbosity -> Maybe FilePath -> Maybe FilePath
-> ProgramConfiguration -> IO (Compiler, ProgramConfiguration)
configure verbosity hcPath _hcPkgPath conf = do
(_ffihugsProg, conf') <- requireProgram ::
Verbosity
-> Program
-> ProgramDb
-> IO (ConfiguredProgram, ProgramDb)requireProgram verbosity :: Verbosityverbosity ffihugsProgram :: ProgramffihugsProgram
(userMaybeSpecifyPath ::
String -> Maybe FilePath -> ProgramDb -> ProgramDbuserMaybeSpecifyPath "ffihugs" hcPath :: Maybe FilePathhcPath conf :: ProgramConfigurationconf)
(_hugsProg, version, conf'')
<- requireProgramVersion ::
Verbosity
-> Program
-> VersionRange
-> ProgramDb
-> IO (ConfiguredProgram, Version, ProgramDb)requireProgramVersion verbosity :: Verbosityverbosity hugsProgram' :: ProgramhugsProgram'
(orLaterVersion :: Version -> VersionRangeorLaterVersion (Version :: [Int] -> [String] -> VersionVersion [2006] [] :: [a][])) conf' :: ProgramDbconf'
let comp = Compiler {
compilerId = CompilerId :: CompilerFlavor -> Version -> CompilerIdCompilerId Hugs :: CompilerFlavorHugs version :: Versionversion,
compilerLanguages = hugsLanguages :: [(Language, Flag)]hugsLanguages,
compilerExtensions = hugsLanguageExtensions :: [(Extension, Flag)]hugsLanguageExtensions
}
return :: Monad m => forall a. a -> m areturn (comp :: Compilercomp, conf'' :: ProgramDbconf'')
where
hugsProgram' = hugsProgram :: ProgramhugsProgram { programFindVersion = getVersion :: Verbosity -> FilePath -> IO (Maybe Version)getVersion }
getVersion :: Verbosity -> FilePath -> IO (Maybe Version)
getVersion verbosity hugsPath = do
(output, _err, exit) <- rawSystemStdInOut ::
Verbosity
-> FilePath
-> [String]
-> Maybe (String, Bool)
-> Bool
-> IO (String, String, ExitCode)rawSystemStdInOut verbosity :: Verbosityverbosity hugsPath :: FilePathhugsPath [] :: [a][]
(Just :: a -> Maybe aJust (":quit", False :: BoolFalse)) False :: BoolFalse
if exit :: ExitCodeexit (==) :: Eq a => a -> a -> Bool== ExitSuccess :: ExitCodeExitSuccess
then return :: Monad m => forall a. a -> m areturn ($!) :: (a -> b) -> a -> b$! findVersion :: String -> Maybe VersionfindVersion output :: Stringoutput
else return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing
where
findVersion output = do
(monthStr, yearStr) <- selectWords :: String -> Maybe (String, String)selectWords output :: Stringoutput
year <- convertYear :: (Read a, Ord a, Num a) => String -> Maybe aconvertYear yearStr :: StringyearStr
month <- convertMonth :: (Num b, Enum b) => [Char] -> Maybe bconvertMonth monthStr :: StringmonthStr
return :: Monad m => forall a. a -> m areturn (Version :: [Int] -> [String] -> VersionVersion [year :: Intyear, month :: Intmonth] [] :: [a][])
selectWords output =
case [ (month :: Intmonth, year :: Intyear)
| [_,_,"Version:", month, year,_] <- map :: (a -> b) -> [a] -> [b]map words :: String -> [String]words (lines :: String -> [String]lines output :: Stringoutput) ] of
[(month, year)] -> Just :: a -> Maybe aJust (month :: Intmonth, year :: Intyear)
_ -> Nothing :: Maybe aNothing
convertYear year = case reads :: Read a => ReadS areads year :: Intyear of
[(y, [])] | y :: ay (>=) :: Ord a => a -> a -> Bool>= 1999 (&&) :: Bool -> Bool -> Bool&& y :: ay (<) :: Ord a => a -> a -> Bool< 2020 -> Just :: a -> Maybe aJust y :: ay
_ -> Nothing :: Maybe aNothing
convertMonth month = lookup :: Eq a => a -> [(a, b)] -> Maybe blookup month :: Intmonth (zip :: [a] -> [b] -> [(a, b)]zip months :: [[Char]]months [1..])
months = [ "January", "February", "March", "April", "May", "June", "July"
, "August", "September", "October", "November", "December" ]
hugsLanguages :: [(Language, Flag)]
hugsLanguages = [(Haskell98 :: LanguageHaskell98, "")]
hugsLanguageExtensions :: [(Extension, Flag)]
hugsLanguageExtensions =
let doFlag (f, (enable, disable)) = [(EnableExtension :: KnownExtension -> ExtensionEnableExtension f :: KnownExtensionf, enable :: tenable),
(DisableExtension :: KnownExtension -> ExtensionDisableExtension f :: KnownExtensionf, disable :: tdisable)]
alwaysOn = ("", "")
ext98 = ("-98", "")
in concatMap :: (a -> [b]) -> [a] -> [b]concatMap doFlag :: (KnownExtension, (t, t)) -> [(Extension, t)]doFlag
[(OverlappingInstances :: KnownExtensionOverlappingInstances , ("+o", "-o"))
,(IncoherentInstances :: KnownExtensionIncoherentInstances , ("+oO", "-O"))
,(HereDocuments :: KnownExtensionHereDocuments , ("+H", "-H"))
,(TypeSynonymInstances :: KnownExtensionTypeSynonymInstances , ext98 :: ([Char], [Char])ext98)
,(RecursiveDo :: KnownExtensionRecursiveDo , ext98 :: ([Char], [Char])ext98)
,(ParallelListComp :: KnownExtensionParallelListComp , ext98 :: ([Char], [Char])ext98)
,(MultiParamTypeClasses :: KnownExtensionMultiParamTypeClasses , ext98 :: ([Char], [Char])ext98)
,(FunctionalDependencies :: KnownExtensionFunctionalDependencies , ext98 :: ([Char], [Char])ext98)
,(Rank2Types :: KnownExtensionRank2Types , ext98 :: ([Char], [Char])ext98)
,(PolymorphicComponents :: KnownExtensionPolymorphicComponents , ext98 :: ([Char], [Char])ext98)
,(ExistentialQuantification :: KnownExtensionExistentialQuantification , ext98 :: ([Char], [Char])ext98)
,(ScopedTypeVariables :: KnownExtensionScopedTypeVariables , ext98 :: ([Char], [Char])ext98)
,(ImplicitParams :: KnownExtensionImplicitParams , ext98 :: ([Char], [Char])ext98)
,(ExtensibleRecords :: KnownExtensionExtensibleRecords , ext98 :: ([Char], [Char])ext98)
,(RestrictedTypeSynonyms :: KnownExtensionRestrictedTypeSynonyms , ext98 :: ([Char], [Char])ext98)
,(FlexibleContexts :: KnownExtensionFlexibleContexts , ext98 :: ([Char], [Char])ext98)
,(FlexibleInstances :: KnownExtensionFlexibleInstances , ext98 :: ([Char], [Char])ext98)
,(ForeignFunctionInterface :: KnownExtensionForeignFunctionInterface , alwaysOn :: ([Char], [Char])alwaysOn)
,(EmptyDataDecls :: KnownExtensionEmptyDataDecls , alwaysOn :: ([Char], [Char])alwaysOn)
,(CPP :: KnownExtensionCPP , alwaysOn :: ([Char], [Char])alwaysOn)
]
getInstalledPackages :: Verbosity -> PackageDBStack -> ProgramConfiguration
-> IO PackageIndex
getInstalledPackages verbosity packagedbs conf = do
homedir <- getHomeDirectory :: IO FilePathgetHomeDirectory
(hugsProg, _) <- requireProgram ::
Verbosity
-> Program
-> ProgramDb
-> IO (ConfiguredProgram, ProgramDb)requireProgram verbosity :: Verbosityverbosity hugsProgram :: ProgramhugsProgram conf :: ProgramConfigurationconf
let hugsbindir = takeDirectory :: FilePath -> FilePathtakeDirectory (programPath :: ConfiguredProgram -> FilePathprogramPath hugsProg :: ConfiguredProgramhugsProg)
hugslibdir = takeDirectory :: FilePath -> FilePathtakeDirectory hugsbindir :: FilePathhugsbindir (</>) :: FilePath -> FilePath -> FilePath</> "lib" (</>) :: FilePath -> FilePath -> FilePath</> "hugs"
dbdirs = nub :: Eq a => [a] -> [a]nub (concatMap :: (a -> [b]) -> [a] -> [b]concatMap (packageDbPaths :: FilePath -> FilePath -> PackageDB -> [FilePath]packageDbPaths homedir :: FilePathhomedir hugslibdir :: FilePathhugslibdir) packagedbs :: PackageDBStackpackagedbs)
indexes <- mapM :: Monad m => (a -> m b) -> [a] -> m [b]mapM getIndividualDBPackages :: FilePath -> IO PackageIndexgetIndividualDBPackages dbdirs :: [FilePath]dbdirs
return :: Monad m => forall a. a -> m areturn ($!) :: (a -> b) -> a -> b$! mconcat :: Monoid a => [a] -> amconcat indexes :: [PackageIndex]indexes
where
getIndividualDBPackages :: FilePath -> IO PackageIndex
getIndividualDBPackages dbdir = do
pkgdirs <- getPackageDbDirs :: FilePath -> IO [(PackageName, FilePath)]getPackageDbDirs dbdir :: FilePathdbdir
pkgs <- sequence :: Monad m => [m a] -> m [a]sequence [ getInstalledPackage ::
PackageName -> FilePath -> IO (Maybe InstalledPackageInfo)getInstalledPackage pkgname :: PackageNamepkgname pkgdir :: FilePathpkgdir
| (pkgname, pkgdir) <- pkgdirs :: [(PackageName, FilePath)]pkgdirs ]
let pkgs' = map :: (a -> b) -> [a] -> [b]map setInstalledPackageId ::
InstalledPackageInfo -> InstalledPackageInfosetInstalledPackageId (catMaybes :: [Maybe a] -> [a]catMaybes pkgs :: [Maybe InstalledPackageInfo]pkgs)
return :: Monad m => forall a. a -> m areturn (fromList :: [InstalledPackageInfo] -> PackageIndexPackageIndex.fromList pkgs' :: [InstalledPackageInfo]pkgs')
packageDbPaths :: FilePath -> FilePath -> PackageDB -> [FilePath]
packageDbPaths home hugslibdir db = case db :: PackageDBdb of
GlobalPackageDB -> [ hugslibdir :: FilePathhugslibdir (</>) :: FilePath -> FilePath -> FilePath</> "packages"
, "/usr/local/lib/hugs/packages" ]
UserPackageDB -> [ home :: FilePathhome (</>) :: FilePath -> FilePath -> FilePath</> "lib/hugs/packages" ]
SpecificPackageDB path -> [ path :: FilePathpath ]
getPackageDbDirs :: FilePath -> IO [(PackageName, FilePath)]
getPackageDbDirs dbdir = do
dbexists <- doesDirectoryExist :: FilePath -> IO BooldoesDirectoryExist dbdir :: FilePathdbdir
if not :: Bool -> Boolnot dbexists :: Booldbexists
then return :: Monad m => forall a. a -> m areturn [] :: [a][]
else do
entries <- getDirectoryContents :: FilePath -> IO [FilePath]getDirectoryContents dbdir :: FilePathdbdir
pkgdirs <- sequence :: Monad m => [m a] -> m [a]sequence
[ do pkgdirExists <- doesDirectoryExist :: FilePath -> IO BooldoesDirectoryExist pkgdir :: FilePathpkgdir
return :: Monad m => forall a. a -> m areturn (pkgname :: PackageNamepkgname, pkgdir :: FilePathpkgdir, pkgdirExists :: BoolpkgdirExists)
| (entry, Just pkgname) <- [ (entry :: FilePathentry, simpleParse :: Text a => String -> Maybe asimpleParse entry :: FilePathentry)
| entry <- entries :: [FilePath]entries ]
, let pkgdir = dbdir :: FilePathdbdir (</>) :: FilePath -> FilePath -> FilePath</> entry :: FilePathentry ]
return :: Monad m => forall a. a -> m areturn [ (pkgname :: PackageNamepkgname, pkgdir :: FilePathpkgdir) | (pkgname, pkgdir, True) <- pkgdirs :: [(PackageName, FilePath)]pkgdirs ]
getInstalledPackage :: PackageName -> FilePath -> IO (Maybe InstalledPackageInfo)
getInstalledPackage pkgname pkgdir = do
let pkgconfFile = pkgdir :: FilePathpkgdir (</>) :: FilePath -> FilePath -> FilePath</> "package.conf"
pkgconfExists <- doesFileExist :: FilePath -> IO BooldoesFileExist pkgconfFile :: FilePathpkgconfFile
let pathsModule = pkgdir :: FilePathpkgdir (</>) :: FilePath -> FilePath -> FilePath</> ("Paths_" (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay pkgname :: PackageNamepkgname) (<.>) :: FilePath -> String -> FilePath<.> "hs"
pathsModuleExists <- doesFileExist :: FilePath -> IO BooldoesFileExist pathsModule :: FilePathpathsModule
case () of
_ | pkgconfExists :: BoolpkgconfExists -> getFullInstalledPackageInfo ::
PackageName -> FilePath -> IO (Maybe InstalledPackageInfo)getFullInstalledPackageInfo pkgname :: PackageNamepkgname pkgconfFile :: FilePathpkgconfFile
| pathsModuleExists :: BoolpathsModuleExists -> getPhonyInstalledPackageInfo ::
PackageName -> FilePath -> IO (Maybe InstalledPackageInfo)getPhonyInstalledPackageInfo pkgname :: PackageNamepkgname pathsModule :: FilePathpathsModule
| otherwise :: Boolotherwise -> return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing
getFullInstalledPackageInfo :: PackageName -> FilePath
-> IO (Maybe InstalledPackageInfo)
getFullInstalledPackageInfo pkgname pkgconfFile =
withUTF8FileContents :: FilePath -> (String -> IO a) -> IO awithUTF8FileContents pkgconfFile :: FilePathpkgconfFile ($) :: (a -> b) -> a -> b$ \contents ->
case parseInstalledPackageInfo ::
String -> ParseResult InstalledPackageInfoparseInstalledPackageInfo contents :: Stringcontents of
ParseOk _ pkginfo | packageName :: Package pkg => pkg -> PackageNamepackageName pkginfo :: InstalledPackageInfopkginfo (==) :: Eq a => a -> a -> Bool== pkgname :: PackageNamepkgname
-> return :: Monad m => forall a. a -> m areturn (Just :: a -> Maybe aJust pkginfo :: InstalledPackageInfopkginfo)
_ -> return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing
getPhonyInstalledPackageInfo :: PackageName -> FilePath
-> IO (Maybe InstalledPackageInfo)
getPhonyInstalledPackageInfo pkgname pathsModule = do
content <- readFile :: FilePath -> IO StringreadFile pathsModule :: FilePathpathsModule
case extractVersion :: String -> Maybe aextractVersion content :: Stringcontent of
Nothing -> return :: Monad m => forall a. a -> m areturn Nothing :: Maybe aNothing
Just version -> return :: Monad m => forall a. a -> m areturn (Just :: a -> Maybe aJust pkginfo :: InstalledPackageInfopkginfo)
where
pkgid = PackageIdentifier :: PackageName -> Version -> PackageIdentifierPackageIdentifier pkgname :: PackageNamepkgname version :: Versionversion
pkginfo = emptyInstalledPackageInfo :: InstalledPackageInfo_ memptyInstalledPackageInfo { sourcePackageId = pkgid :: PackageIdentifierpkgid }
where
extractVersion content =
case [ version :: Versionversion
| ("version":"=":rest) <- map :: (a -> b) -> [a] -> [b]map words :: String -> [String]words (lines :: String -> [String]lines content :: Stringcontent)
, (version, []) <- reads :: Read a => ReadS areads (concat :: [[a]] -> [a]concat rest :: [String]rest) ] of
[version] -> Just :: a -> Maybe aJust version :: Versionversion
_ -> Nothing :: Maybe aNothing
setInstalledPackageId :: InstalledPackageInfo -> InstalledPackageInfo
setInstalledPackageId pkginfo@InstalledPackageInfo {
installedPackageId = InstalledPackageId "",
sourcePackageId = pkgid
}
= pkginfo :: InstalledPackageInfopkginfo {
installedPackageId = InstalledPackageId :: String -> InstalledPackageIdInstalledPackageId (display :: Text a => a -> Stringdisplay pkgid :: PackageIdentifierpkgid)
}
setInstalledPackageId pkginfo = pkginfo :: InstalledPackageInfopkginfo
buildLib :: Verbosity -> PackageDescription -> LocalBuildInfo
-> Library -> ComponentLocalBuildInfo -> IO ()
buildLib verbosity pkg_descr lbi lib _clbi = do
let pref = scratchDir :: LocalBuildInfo -> FilePathscratchDir lbi :: LocalBuildInfolbi
createDirectoryIfMissingVerbose ::
Verbosity -> Bool -> FilePath -> IO ()createDirectoryIfMissingVerbose verbosity :: Verbosityverbosity True :: BoolTrue pref :: FilePathpref
copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()copyFileVerbose verbosity :: Verbosityverbosity (autogenModulesDir :: LocalBuildInfo -> StringautogenModulesDir lbi :: LocalBuildInfolbi (</>) :: FilePath -> FilePath -> FilePath</> paths_modulename :: FilePathpaths_modulename)
(pref :: FilePathpref (</>) :: FilePath -> FilePath -> FilePath</> paths_modulename :: FilePathpaths_modulename)
compileBuildInfo ::
Verbosity
-> FilePath
-> [FilePath]
-> [ModuleName]
-> BuildInfo
-> LocalBuildInfo
-> IO ()compileBuildInfo verbosity :: Verbosityverbosity pref :: FilePathpref [] :: [a][] (libModules :: Library -> [ModuleName]libModules lib :: Librarylib) (libBuildInfo :: Library -> BuildInfolibBuildInfo lib :: Librarylib) lbi :: LocalBuildInfolbi
where
paths_modulename = toFilePath :: ModuleName -> FilePathModuleName.toFilePath (autogenModuleName :: PackageDescription -> ModuleNameautogenModuleName pkg_descr :: PackageDescriptionpkg_descr)
(<.>) :: FilePath -> String -> FilePath<.> ".hs"
buildExe :: Verbosity -> PackageDescription -> LocalBuildInfo
-> Executable -> ComponentLocalBuildInfo -> IO ()
buildExe verbosity pkg_descr lbi
exe@Executable {modulePath=mainPath, buildInfo=bi} _clbi = do
let pref = scratchDir :: LocalBuildInfo -> FilePathscratchDir lbi :: LocalBuildInfolbi
createDirectoryIfMissingVerbose ::
Verbosity -> Bool -> FilePath -> IO ()createDirectoryIfMissingVerbose verbosity :: Verbosityverbosity True :: BoolTrue pref :: FilePathpref
let destDir = pref :: FilePathpref (</>) :: FilePath -> FilePath -> FilePath</> "programs"
let exeMods = otherModules :: BuildInfo -> [ModuleName]otherModules bi :: BuildInfobi
srcMainFile <- findFile :: [FilePath] -> FilePath -> IO FilePathfindFile (hsSourceDirs :: BuildInfo -> [FilePath]hsSourceDirs bi :: BuildInfobi) mainPath :: FilePathmainPath
let exeDir = destDir :: FilePathdestDir (</>) :: FilePath -> FilePath -> FilePath</> exeName :: Executable -> StringexeName exe :: Executableexe
let destMainFile = exeDir :: FilePathexeDir (</>) :: FilePath -> FilePath -> FilePath</> hugsMainFilename :: Executable -> FilePathhugsMainFilename exe :: Executableexe
copyModule ::
Verbosity
-> Bool
-> BuildInfo
-> LocalBuildInfo
-> FilePath
-> FilePath
-> IO ()copyModule verbosity :: Verbosityverbosity (EnableExtension :: KnownExtension -> ExtensionEnableExtension CPP :: KnownExtensionCPP elem :: Eq a => a -> [a] -> Bool`elem` allExtensions :: BuildInfo -> [Extension]allExtensions bi :: BuildInfobi) bi :: BuildInfobi lbi :: LocalBuildInfolbi srcMainFile :: FilePathsrcMainFile destMainFile :: FilePathdestMainFile
let destPathsFile = exeDir :: FilePathexeDir (</>) :: FilePath -> FilePath -> FilePath</> paths_modulename :: FilePathpaths_modulename
copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()copyFileVerbose verbosity :: Verbosityverbosity (autogenModulesDir :: LocalBuildInfo -> StringautogenModulesDir lbi :: LocalBuildInfolbi (</>) :: FilePath -> FilePath -> FilePath</> paths_modulename :: FilePathpaths_modulename)
destPathsFile :: FilePathdestPathsFile
compileBuildInfo ::
Verbosity
-> FilePath
-> [FilePath]
-> [ModuleName]
-> BuildInfo
-> LocalBuildInfo
-> IO ()compileBuildInfo verbosity :: Verbosityverbosity exeDir :: FilePathexeDir
(maybe :: b -> (a -> b) -> Maybe a -> bmaybe [] :: [a][] (hsSourceDirs :: BuildInfo -> [FilePath]hsSourceDirs (.) :: (b -> c) -> (a -> b) -> a -> c. libBuildInfo :: Library -> BuildInfolibBuildInfo) (library :: PackageDescription -> Maybe Librarylibrary pkg_descr :: PackageDescriptionpkg_descr)) exeMods :: [ModuleName]exeMods bi :: BuildInfobi lbi :: LocalBuildInfolbi
compileFiles ::
Verbosity
-> BuildInfo
-> LocalBuildInfo
-> FilePath
-> [FilePath]
-> IO ()compileFiles verbosity :: Verbosityverbosity bi :: BuildInfobi lbi :: LocalBuildInfolbi exeDir :: FilePathexeDir [destMainFile :: FilePathdestMainFile, destPathsFile :: FilePathdestPathsFile]
where
paths_modulename = toFilePath :: ModuleName -> FilePathModuleName.toFilePath (autogenModuleName :: PackageDescription -> ModuleNameautogenModuleName pkg_descr :: PackageDescriptionpkg_descr)
(<.>) :: FilePath -> String -> FilePath<.> ".hs"
compileBuildInfo :: Verbosity
-> FilePath
-> [FilePath]
-> [ModuleName]
-> BuildInfo
-> LocalBuildInfo
-> IO ()
compileBuildInfo verbosity destDir mLibSrcDirs mods bi lbi = do
let useCpp = EnableExtension :: KnownExtension -> ExtensionEnableExtension CPP :: KnownExtensionCPP elem :: Eq a => a -> [a] -> Bool`elem` allExtensions :: BuildInfo -> [Extension]allExtensions bi :: BuildInfobi
let srcDir = buildDir :: LocalBuildInfo -> FilePathbuildDir lbi :: LocalBuildInfolbi
srcDirs = nub :: Eq a => [a] -> [a]nub ($) :: (a -> b) -> a -> b$ srcDir :: FilePathsrcDir (:) :: a -> [a] -> [a]: hsSourceDirs :: BuildInfo -> [FilePath]hsSourceDirs bi :: BuildInfobi (++) :: [a] -> [a] -> [a]++ mLibSrcDirs :: [FilePath]mLibSrcDirs
info :: Verbosity -> String -> IO ()info verbosity :: Verbosityverbosity ($) :: (a -> b) -> a -> b$ "Source directories: " (++) :: [a] -> [a] -> [a]++ show :: Show a => a -> Stringshow srcDirs :: [FilePath]srcDirs
flip :: (a -> b -> c) -> b -> a -> cflip mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ mods :: [ModuleName]mods ($) :: (a -> b) -> a -> b$ \ m -> do
fs <- findFileWithExtension ::
[String] -> [FilePath] -> FilePath -> IO (Maybe FilePath)findFileWithExtension suffixes :: [String]suffixes srcDirs :: [FilePath]srcDirs (toFilePath :: ModuleName -> FilePathModuleName.toFilePath m :: ModuleNamem)
case fs :: Maybe FilePathfs of
Nothing ->
die :: String -> IO adie ("can't find source for module " (++) :: [a] -> [a] -> [a]++ display :: Text a => a -> Stringdisplay m :: ModuleNamem)
Just srcFile -> do
let ext = takeExtension :: FilePath -> StringtakeExtension srcFile :: FilePathsrcFile
copyModule ::
Verbosity
-> Bool
-> BuildInfo
-> LocalBuildInfo
-> FilePath
-> FilePath
-> IO ()copyModule verbosity :: Verbosityverbosity useCpp :: BooluseCpp bi :: BuildInfobi lbi :: LocalBuildInfolbi srcFile :: FilePathsrcFile
(destDir :: FilePathdestDir (</>) :: FilePath -> FilePath -> FilePath</> toFilePath :: ModuleName -> FilePathModuleName.toFilePath m :: ModuleNamem (<.>) :: FilePath -> String -> FilePath<.> ext :: Stringext)
stubsFileLists <- fmap :: Functor f => forall a b. (a -> b) -> f a -> f bfmap catMaybes :: [Maybe a] -> [a]catMaybes ($) :: (a -> b) -> a -> b$ sequence :: Monad m => [m a] -> m [a]sequence
[ findFileWithExtension ::
[String] -> [FilePath] -> FilePath -> IO (Maybe FilePath)findFileWithExtension suffixes :: [String]suffixes [destDir :: FilePathdestDir] (toFilePath :: ModuleName -> FilePathModuleName.toFilePath modu :: ModuleNamemodu)
| modu <- mods :: [ModuleName]mods]
compileFiles ::
Verbosity
-> BuildInfo
-> LocalBuildInfo
-> FilePath
-> [FilePath]
-> IO ()compileFiles verbosity :: Verbosityverbosity bi :: BuildInfobi lbi :: LocalBuildInfolbi destDir :: FilePathdestDir stubsFileLists :: [FilePath]stubsFileLists
suffixes :: [String]
suffixes = ["hs", "lhs"]
copyModule :: Verbosity -> Bool -> BuildInfo -> LocalBuildInfo -> FilePath -> FilePath -> IO ()
copyModule verbosity cppAll bi lbi srcFile destFile = do
createDirectoryIfMissingVerbose ::
Verbosity -> Bool -> FilePath -> IO ()createDirectoryIfMissingVerbose verbosity :: Verbosityverbosity True :: BoolTrue (takeDirectory :: FilePath -> FilePathtakeDirectory destFile :: FilePathdestFile)
(exts, opts, _) <- getOptionsFromSource ::
FilePath
-> IO ([Extension], [(CompilerFlavor, [String])], [String])getOptionsFromSource srcFile :: FilePathsrcFile
let ghcOpts = [ op :: Stringop | (GHC, ops) <- opts :: [(CompilerFlavor, [String])]opts, op <- ops :: [String]ops ]
if cppAll :: BoolcppAll (||) :: Bool -> Bool -> Bool|| EnableExtension :: KnownExtension -> ExtensionEnableExtension CPP :: KnownExtensionCPP elem :: Eq a => a -> [a] -> Bool`elem` exts :: [Extension]exts (||) :: Bool -> Bool -> Bool|| "-cpp" elem :: Eq a => a -> [a] -> Bool`elem` ghcOpts :: [String]ghcOpts then do
runSimplePreProcessor ::
PreProcessor -> FilePath -> FilePath -> Verbosity -> IO ()runSimplePreProcessor (ppCpp :: BuildInfo -> LocalBuildInfo -> PreProcessorppCpp bi :: BuildInfobi lbi :: LocalBuildInfolbi) srcFile :: FilePathsrcFile destFile :: FilePathdestFile verbosity :: Verbosityverbosity
return :: Monad m => forall a. a -> m areturn ()
else
copyFileVerbose :: Verbosity -> FilePath -> FilePath -> IO ()copyFileVerbose verbosity :: Verbosityverbosity srcFile :: FilePathsrcFile destFile :: FilePathdestFile
compileFiles :: Verbosity -> BuildInfo -> LocalBuildInfo -> FilePath -> [FilePath] -> IO ()
compileFiles verbosity bi lbi modDir fileList = do
ffiFileList <- filterM :: Monad m => (a -> m Bool) -> [a] -> m [a]filterM testFFI :: FilePath -> IO BooltestFFI fileList :: [FilePath]fileList
unless :: Monad m => Bool -> m () -> m ()unless (null :: [a] -> Boolnull ffiFileList :: [FilePath]ffiFileList) ($) :: (a -> b) -> a -> b$ do
notice :: Verbosity -> String -> IO ()notice verbosity :: Verbosityverbosity "Compiling FFI stubs"
mapM_ :: Monad m => (a -> m b) -> [a] -> m ()mapM_ (compileFFI ::
Verbosity
-> BuildInfo
-> LocalBuildInfo
-> FilePath
-> FilePath
-> IO ()compileFFI verbosity :: Verbosityverbosity bi :: BuildInfobi lbi :: LocalBuildInfolbi modDir :: FilePathmodDir) ffiFileList :: [FilePath]ffiFileList
testFFI :: FilePath -> IO Bool
testFFI file =
withHaskellFile :: FilePath -> (String -> IO a) -> IO awithHaskellFile file :: FilePathfile ($) :: (a -> b) -> a -> b$ \inp ->
return :: Monad m => forall a. a -> m areturn ($!) :: (a -> b) -> a -> b$! "foreign" elem :: Eq a => a -> [a] -> Bool`elem` symbols :: String -> [String]symbols (stripComments :: Bool -> String -> StringstripComments False :: BoolFalse inp :: Stringinp)
compileFFI :: Verbosity -> BuildInfo -> LocalBuildInfo -> FilePath -> FilePath -> IO ()
compileFFI verbosity bi lbi modDir file = do
(_, opts, file_incs) <- getOptionsFromSource ::
FilePath
-> IO ([Extension], [(CompilerFlavor, [String])], [String])getOptionsFromSource file :: FilePathfile
let ghcOpts = [ op :: Stringop | (GHC, ops) <- opts :: [(CompilerFlavor, [String])]opts, op <- ops :: [String]ops ]
let pkg_incs = ["\"" (++) :: [a] -> [a] -> [a]++ inc :: FilePathinc (++) :: [a] -> [a] -> [a]++ "\"" | inc <- includes :: BuildInfo -> [FilePath]includes bi :: BuildInfobi]
let incs = nub :: Eq a => [a] -> [a]nub (sort :: Ord a => [a] -> [a]sort (file_incs :: [String]file_incs (++) :: [a] -> [a] -> [a]++ includeOpts :: [String] -> [String]includeOpts ghcOpts :: [String]ghcOpts (++) :: [a] -> [a] -> [a]++ pkg_incs :: [[Char]]pkg_incs))
let pathFlag = "-P" (++) :: [a] -> [a] -> [a]++ modDir :: FilePathmodDir (++) :: [a] -> [a] -> [a]++ [searchPathSeparator :: CharsearchPathSeparator]
let hugsArgs = "-98" (:) :: a -> [a] -> [a]: pathFlag :: [Char]pathFlag (:) :: a -> [a] -> [a]: map :: (a -> b) -> [a] -> [b]map ("-i" (++) :: [a] -> [a] -> [a]++) incs :: [String]incs
cfiles <- getCFiles :: FilePath -> IO [String]getCFiles file :: FilePathfile
let cArgs =
["-I" (++) :: [a] -> [a] -> [a]++ dir :: Stringdir | dir <- includeDirs :: BuildInfo -> [FilePath]includeDirs bi :: BuildInfobi] (++) :: [a] -> [a] -> [a]++
ccOptions :: BuildInfo -> [String]ccOptions bi :: BuildInfobi (++) :: [a] -> [a] -> [a]++
cfiles :: [String]cfiles (++) :: [a] -> [a] -> [a]++
["-L" (++) :: [a] -> [a] -> [a]++ dir :: Stringdir | dir <- extraLibDirs :: BuildInfo -> [String]extraLibDirs bi :: BuildInfobi] (++) :: [a] -> [a] -> [a]++
ldOptions :: BuildInfo -> [String]ldOptions bi :: BuildInfobi (++) :: [a] -> [a] -> [a]++
["-l" (++) :: [a] -> [a] -> [a]++ lib :: Librarylib | lib <- extraLibs :: BuildInfo -> [String]extraLibs bi :: BuildInfobi] (++) :: [a] -> [a] -> [a]++
concat :: [[a]] -> [a]concat [["-framework", f :: KnownExtensionf] | f <- frameworks :: BuildInfo -> [String]frameworks bi :: BuildInfobi]
rawSystemProgramConf ::
Verbosity -> Program -> ProgramConfiguration -> [ProgArg] -> IO ()rawSystemProgramConf verbosity :: Verbosityverbosity ffihugsProgram :: ProgramffihugsProgram (withPrograms :: LocalBuildInfo -> ProgramConfigurationwithPrograms lbi :: LocalBuildInfolbi)
(hugsArgs :: [[Char]]hugsArgs (++) :: [a] -> [a] -> [a]++ file :: FilePathfile (:) :: a -> [a] -> [a]: cArgs :: [[Char]]cArgs)
includeOpts :: [String] -> [String]
includeOpts [] = [] :: [a][]
includeOpts ("-#include" : arg : opts) = arg :: Stringarg (:) :: a -> [a] -> [a]: includeOpts :: [String] -> [String]includeOpts opts :: [(CompilerFlavor, [String])]opts
includeOpts (_ : opts) = includeOpts :: [String] -> [String]includeOpts opts :: [(CompilerFlavor, [String])]opts
getCFiles :: FilePath -> IO [String]
getCFiles file =
withHaskellFile :: FilePath -> (String -> IO a) -> IO awithHaskellFile file :: FilePathfile ($) :: (a -> b) -> a -> b$ \inp ->
let cfiles =
[ normalise :: FilePath -> FilePathnormalise cfile :: Stringcfile
| "{-#" : "CFILES" : rest <- map :: (a -> b) -> [a] -> [b]map words :: String -> [String]words
($) :: (a -> b) -> a -> b$ lines :: String -> [String]lines
($) :: (a -> b) -> a -> b$ stripComments :: Bool -> String -> StringstripComments True :: BoolTrue inp :: Stringinp
, last :: [a] -> alast rest :: [String]rest (==) :: Eq a => a -> a -> Bool== "#-}"
, cfile <- init :: [a] -> [a]init rest :: [String]rest]
in seq :: a -> b -> bseq (length :: [a] -> Intlength cfiles :: [String]cfiles) (return :: Monad m => forall a. a -> m areturn cfiles :: [String]cfiles)
symbols :: String -> [String]
symbols cs = case lex :: ReadS Stringlex cs :: Stringcs of
(sym, cs'):_ | not :: Bool -> Boolnot (null :: [a] -> Boolnull sym :: Stringsym) -> sym :: Stringsym (:) :: a -> [a] -> [a]: symbols :: String -> [String]symbols cs' :: Stringcs'
_ -> [] :: [a][]
withHaskellFile :: FilePath -> (String -> IO a) -> IO a
withHaskellFile file action =
withUTF8FileContents :: FilePath -> (String -> IO a) -> IO awithUTF8FileContents file :: FilePathfile ($) :: (a -> b) -> a -> b$ \text ->
if ".lhs" isSuffixOf :: Eq a => [a] -> [a] -> Bool`isSuffixOf` file :: FilePathfile
then either :: (a -> c) -> (b -> c) -> Either a b -> ceither action :: String -> IO aaction die :: String -> IO adie (unlit :: FilePath -> String -> Either String Stringunlit file :: FilePathfile text :: Stringtext)
else action :: String -> IO aaction text :: Stringtext
getOptionsFromSource
:: FilePath
-> IO ([Extension],
[(CompilerFlavor,[String])],
[String]
)
getOptionsFromSource file =
withHaskellFile :: FilePath -> (String -> IO a) -> IO awithHaskellFile file :: FilePathfile ($) :: (a -> b) -> a -> b$
(return :: Monad m => forall a. a -> m areturn ($!) :: (a -> b) -> a -> b$!)
(.) :: (b -> c) -> (a -> b) -> a -> c. foldr :: (a -> b -> b) -> b -> [a] -> bfoldr appendOptions ::
([a], [a], [a]) -> ([a], [a], [a]) -> ([a], [a], [a])appendOptions ([] :: [a][],[] :: [a][],[] :: [a][]) (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map getOptions ::
[[Char]] -> ([Extension], [(CompilerFlavor, [[Char]])], [[Char]])getOptions
(.) :: (b -> c) -> (a -> b) -> a -> c. takeWhileJust :: [Maybe a] -> [a]takeWhileJust (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map getPragma :: String -> Maybe [String]getPragma
(.) :: (b -> c) -> (a -> b) -> a -> c. filter :: (a -> Bool) -> [a] -> [a]filter textLine :: [Char] -> BooltextLine (.) :: (b -> c) -> (a -> b) -> a -> c. map :: (a -> b) -> [a] -> [b]map (dropWhile :: (a -> Bool) -> [a] -> [a]dropWhile isSpace :: Char -> BoolisSpace) (.) :: (b -> c) -> (a -> b) -> a -> c. lines :: String -> [String]lines
(.) :: (b -> c) -> (a -> b) -> a -> c. stripComments :: Bool -> String -> StringstripComments True :: BoolTrue
where textLine [] = False :: BoolFalse
textLine ('#':_) = False :: BoolFalse
textLine _ = True :: BoolTrue
getPragma :: String -> Maybe [String]
getPragma line = case words :: String -> [String]words line :: Stringline of
("{-#" : rest) | last :: [a] -> alast rest :: [String]rest (==) :: Eq a => a -> a -> Bool== "#-}" -> Just :: a -> Maybe aJust (init :: [a] -> [a]init rest :: [String]rest)
_ -> Nothing :: Maybe aNothing
getOptions ("OPTIONS":opts) = ([] :: [a][], [(GHC :: CompilerFlavorGHC, opts :: [(CompilerFlavor, [String])]opts)], [] :: [a][])
getOptions ("OPTIONS_GHC":opts) = ([] :: [a][], [(GHC :: CompilerFlavorGHC, opts :: [(CompilerFlavor, [String])]opts)], [] :: [a][])
getOptions ("OPTIONS_NHC98":opts) = ([] :: [a][], [(NHC :: CompilerFlavorNHC, opts :: [(CompilerFlavor, [String])]opts)], [] :: [a][])
getOptions ("OPTIONS_HUGS":opts) = ([] :: [a][], [(Hugs :: CompilerFlavorHugs, opts :: [(CompilerFlavor, [String])]opts)], [] :: [a][])
getOptions ("LANGUAGE":ws) = (mapMaybe :: (a -> Maybe b) -> [a] -> [b]mapMaybe readExtension :: String -> Maybe ExtensionreadExtension ws :: [[Char]]ws, [] :: [a][], [] :: [a][])
where readExtension :: String -> Maybe Extension
readExtension w = case reads :: Read a => ReadS areads w :: Stringw of
[(ext, "")] -> Just :: a -> Maybe aJust ext :: Stringext
[(ext, ",")] -> Just :: a -> Maybe aJust ext :: Stringext
_ -> Nothing :: Maybe aNothing
getOptions ("INCLUDE":ws) = ([] :: [a][], [] :: [a][], ws :: [[Char]]ws)
getOptions _ = ([] :: [a][], [] :: [a][], [] :: [a][])
appendOptions (exts, opts, incs) (exts', opts', incs')
= (exts :: [Extension]exts(++) :: [a] -> [a] -> [a]++exts' :: [a]exts', opts :: [(CompilerFlavor, [String])]opts(++) :: [a] -> [a] -> [a]++opts' :: [a]opts', incs :: [String]incs(++) :: [a] -> [a] -> [a]++incs' :: [a]incs')
takeWhileJust :: [Maybe a] -> [a]
takeWhileJust (Just x:xs) = x :: ax (:) :: a -> [a] -> [a]: takeWhileJust :: [Maybe a] -> [a]takeWhileJust xs :: [Maybe a]xs
takeWhileJust _ = [] :: [a][]
stripComments
:: Bool
-> String
-> String
stripComments keepPragmas = stripCommentsLevel :: Int -> String -> StringstripCommentsLevel 0
where stripCommentsLevel :: Int -> String -> String
stripCommentsLevel 0 ('"':cs) = '"'(:) :: a -> [a] -> [a]:copyString :: [Char] -> [Char]copyString cs :: Stringcs
stripCommentsLevel 0 ('-':'-':cs) =
stripCommentsLevel :: Int -> String -> StringstripCommentsLevel 0 (dropWhile :: (a -> Bool) -> [a] -> [a]dropWhile ((/=) :: Eq a => a -> a -> Bool/= '\n') cs :: Stringcs)
stripCommentsLevel 0 ('{':'-':'#':cs)
| keepPragmas :: BoolkeepPragmas = '{' (:) :: a -> [a] -> [a]: '-' (:) :: a -> [a] -> [a]: '#' (:) :: a -> [a] -> [a]: copyPragma :: [Char] -> [Char]copyPragma cs :: Stringcs
stripCommentsLevel n ('{':'-':cs) = stripCommentsLevel :: Int -> String -> StringstripCommentsLevel (n :: Intn(+) :: Num a => a -> a -> a+1) cs :: Stringcs
stripCommentsLevel 0 (c:cs) = c :: Charc (:) :: a -> [a] -> [a]: stripCommentsLevel :: Int -> String -> StringstripCommentsLevel 0 cs :: Stringcs
stripCommentsLevel n ('-':'}':cs) = stripCommentsLevel :: Int -> String -> StringstripCommentsLevel (n :: Intn(-) :: Num a => a -> a -> a1) cs :: Stringcs
stripCommentsLevel n (_:cs) = stripCommentsLevel :: Int -> String -> StringstripCommentsLevel n :: Intn cs :: Stringcs
stripCommentsLevel _ [] = [] :: [a][]
copyString ('\\':c:cs) = '\\' (:) :: a -> [a] -> [a]: c :: Charc (:) :: a -> [a] -> [a]: copyString :: [Char] -> [Char]copyString cs :: Stringcs
copyString ('"':cs) = '"' (:) :: a -> [a] -> [a]: stripCommentsLevel :: Int -> String -> StringstripCommentsLevel 0 cs :: Stringcs
copyString (c:cs) = c :: Charc (:) :: a -> [a] -> [a]: copyString :: [Char] -> [Char]copyString cs :: Stringcs
copyString [] = [] :: [a][]
copyPragma ('#':'-':'}':cs) = '#' (:) :: a -> [a] -> [a]: '-' (:) :: a -> [a] -> [a]: '}' (:) :: a -> [a] -> [a]: stripCommentsLevel :: Int -> String -> StringstripCommentsLevel 0 cs :: Stringcs
copyPragma (c:cs) = c :: Charc (:) :: a -> [a] -> [a]: copyPragma :: [Char] -> [Char]copyPragma cs :: Stringcs
copyPragma [] = [] :: [a][]
install
:: Verbosity
-> LocalBuildInfo
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> FilePath
-> (FilePath,FilePath)
-> PackageDescription
-> IO ()
install verbosity lbi libDir installProgDir binDir targetProgDir buildPref (progprefix,progsuffix) pkg_descr = do
removeDirectoryRecursive :: FilePath -> IO ()removeDirectoryRecursive libDir :: FilePathlibDir catchIO :: IO a -> (IOException -> IO a) -> IO a`catchIO` \_ -> return :: Monad m => forall a. a -> m areturn ()
withLib :: PackageDescription -> (Library -> IO ()) -> IO ()withLib pkg_descr :: PackageDescriptionpkg_descr ($) :: (a -> b) -> a -> b$ \ lib ->
findModuleFiles ::
[FilePath] -> [String] -> [ModuleName] -> IO [(FilePath, FilePath)]findModuleFiles [buildPref :: FilePathbuildPref] hugsInstallSuffixes :: [String]hugsInstallSuffixes (libModules :: Library -> [ModuleName]libModules lib :: Librarylib)
(>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= installOrdinaryFiles ::
Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()installOrdinaryFiles verbosity :: Verbosityverbosity libDir :: FilePathlibDir
let buildProgDir = buildPref :: FilePathbuildPref (</>) :: FilePath -> FilePath -> FilePath</> "programs"
when :: Monad m => Bool -> m () -> m ()when (any :: (a -> Bool) -> [a] -> Boolany (buildable :: BuildInfo -> Boolbuildable (.) :: (b -> c) -> (a -> b) -> a -> c. buildInfo :: Executable -> BuildInfobuildInfo) (executables :: PackageDescription -> [Executable]executables pkg_descr :: PackageDescriptionpkg_descr)) ($) :: (a -> b) -> a -> b$
createDirectoryIfMissingVerbose ::
Verbosity -> Bool -> FilePath -> IO ()createDirectoryIfMissingVerbose verbosity :: Verbosityverbosity True :: BoolTrue binDir :: FilePathbinDir
withExe :: PackageDescription -> (Executable -> IO ()) -> IO ()withExe pkg_descr :: PackageDescriptionpkg_descr ($) :: (a -> b) -> a -> b$ \ exe -> do
let bi = buildInfo :: Executable -> BuildInfobuildInfo exe :: Executableexe
let theBuildDir = buildProgDir :: FilePathbuildProgDir (</>) :: FilePath -> FilePath -> FilePath</> exeName :: Executable -> StringexeName exe :: Executableexe
let installDir = installProgDir :: FilePathinstallProgDir (</>) :: FilePath -> FilePath -> FilePath</> exeName :: Executable -> StringexeName exe :: Executableexe
let targetDir = targetProgDir :: FilePathtargetProgDir (</>) :: FilePath -> FilePath -> FilePath</> exeName :: Executable -> StringexeName exe :: Executableexe
removeDirectoryRecursive :: FilePath -> IO ()removeDirectoryRecursive installDir :: FilePathinstallDir catchIO :: IO a -> (IOException -> IO a) -> IO a`catchIO` \_ -> return :: Monad m => forall a. a -> m areturn ()
findModuleFiles ::
[FilePath] -> [String] -> [ModuleName] -> IO [(FilePath, FilePath)]findModuleFiles [theBuildDir :: FilePaththeBuildDir] hugsInstallSuffixes :: [String]hugsInstallSuffixes
(main :: ModuleNameModuleName.main (:) :: a -> [a] -> [a]: autogenModuleName :: PackageDescription -> ModuleNameautogenModuleName pkg_descr :: PackageDescriptionpkg_descr
(:) :: a -> [a] -> [a]: otherModules :: BuildInfo -> [ModuleName]otherModules (buildInfo :: Executable -> BuildInfobuildInfo exe :: Executableexe))
(>>=) :: Monad m => forall a b. m a -> (a -> m b) -> m b>>= installOrdinaryFiles ::
Verbosity -> FilePath -> [(FilePath, FilePath)] -> IO ()installOrdinaryFiles verbosity :: Verbosityverbosity installDir :: FilePathinstallDir
let targetName = "\"" (++) :: [a] -> [a] -> [a]++ (targetDir :: FilePathtargetDir (</>) :: FilePath -> FilePath -> FilePath</> hugsMainFilename :: Executable -> FilePathhugsMainFilename exe :: Executableexe) (++) :: [a] -> [a] -> [a]++ "\""
let hugsOptions = hcOptions :: CompilerFlavor -> BuildInfo -> [String]hcOptions Hugs :: CompilerFlavorHugs (buildInfo :: Executable -> BuildInfobuildInfo exe :: Executableexe)
(++) :: [a] -> [a] -> [a]++ languageToFlags :: Compiler -> Maybe Language -> [Flag]languageToFlags (compiler :: LocalBuildInfo -> Compilercompiler lbi :: LocalBuildInfolbi) (defaultLanguage :: BuildInfo -> Maybe LanguagedefaultLanguage bi :: BuildInfobi)
(++) :: [a] -> [a] -> [a]++ extensionsToFlags :: Compiler -> [Extension] -> [Flag]extensionsToFlags (compiler :: LocalBuildInfo -> Compilercompiler lbi :: LocalBuildInfolbi) (allExtensions :: BuildInfo -> [Extension]allExtensions bi :: BuildInfobi)
let baseExeFile = progprefix :: FilePathprogprefix (++) :: [a] -> [a] -> [a]++ (exeName :: Executable -> StringexeName exe :: Executableexe) (++) :: [a] -> [a] -> [a]++ progsuffix :: FilePathprogsuffix
let exeFile = case buildOS :: OSbuildOS of
Windows -> binDir :: FilePathbinDir (</>) :: FilePath -> FilePath -> FilePath</> baseExeFile :: [Char]baseExeFile (<.>) :: FilePath -> String -> FilePath<.> ".bat"
_ -> binDir :: FilePathbinDir (</>) :: FilePath -> FilePath -> FilePath</> baseExeFile :: [Char]baseExeFile
let script = case buildOS :: OSbuildOS of
Windows ->
let args = hugsOptions :: [String]hugsOptions (++) :: [a] -> [a] -> [a]++ [targetName :: [Char]targetName, "%*"]
in unlines :: [String] -> Stringunlines ["@echo off",
unwords :: [String] -> Stringunwords ("runhugs" (:) :: a -> [a] -> [a]: args :: [String]args)]
_ ->
let args = hugsOptions :: [String]hugsOptions (++) :: [a] -> [a] -> [a]++ [targetName :: [Char]targetName, "\"$@\""]
in unlines :: [String] -> Stringunlines ["#! /bin/sh",
unwords :: [String] -> Stringunwords ("runhugs" (:) :: a -> [a] -> [a]: args :: [String]args)]
writeFileAtomic :: FilePath -> String -> IO ()writeFileAtomic exeFile :: FilePathexeFile script :: Stringscript
setFileExecutable :: FilePath -> IO ()setFileExecutable exeFile :: FilePathexeFile
hugsInstallSuffixes :: [String]
hugsInstallSuffixes = [".hs", ".lhs", dllExtension :: StringdllExtension]
hugsMainFilename :: Executable -> FilePath
hugsMainFilename exe = "Main" (<.>) :: FilePath -> String -> FilePath<.> ext :: Stringext
where ext = takeExtension :: FilePath -> StringtakeExtension (modulePath :: Executable -> FilePathmodulePath exe :: Executableexe)
registerPackage
:: Verbosity
-> InstalledPackageInfo
-> PackageDescription
-> LocalBuildInfo
-> Bool
-> PackageDBStack
-> IO ()
registerPackage verbosity installedPkgInfo pkg lbi inplace _packageDbs = do
let installDirs = absoluteInstallDirs ::
PackageDescription
-> LocalBuildInfo
-> CopyDest
-> InstallDirs FilePathabsoluteInstallDirs pkg :: PackageDescriptionpkg lbi :: LocalBuildInfolbi NoCopyDest :: CopyDestNoCopyDest
pkgdir | inplace :: Boolinplace = buildDir :: LocalBuildInfo -> FilePathbuildDir lbi :: LocalBuildInfolbi
| otherwise :: Boolotherwise = libdir :: InstallDirs dir -> dirlibdir installDirs :: InstallDirs FilePathinstallDirs
createDirectoryIfMissingVerbose ::
Verbosity -> Bool -> FilePath -> IO ()createDirectoryIfMissingVerbose verbosity :: Verbosityverbosity True :: BoolTrue pkgdir :: FilePathpkgdir
writeUTF8File :: FilePath -> String -> IO ()writeUTF8File (pkgdir :: FilePathpkgdir (</>) :: FilePath -> FilePath -> FilePath</> "package.conf")
(showInstalledPackageInfo :: InstalledPackageInfo -> StringshowInstalledPackageInfo installedPkgInfo :: InstalledPackageInfoinstalledPkgInfo)