Skip to content

Commit

Permalink
Use packageId from the Package class in more places
Browse files Browse the repository at this point in the history
Using 'packageId' seems a bit clearer that it's just the PackageIdentifier 
rather than 'package' which might indicate something containing more info.
contain
  • Loading branch information
dcoutts committed Feb 22, 2008
1 parent a675703 commit db061bf
Show file tree
Hide file tree
Showing 12 changed files with 45 additions and 43 deletions.
2 changes: 1 addition & 1 deletion Distribution/Simple.hs
Expand Up @@ -505,5 +505,5 @@ defaultRegHook pkg_descr localbuildinfo _ flags =
if hasLibs pkg_descr
then register pkg_descr localbuildinfo flags
else setupMessage verbosity
"Package contains no library to register:" (package pkg_descr)
"Package contains no library to register:" (packageId pkg_descr)
where verbosity = fromFlag (regVerbose flags)
10 changes: 5 additions & 5 deletions Distribution/Simple/Build.hs
Expand Up @@ -49,7 +49,7 @@ import Distribution.Simple.Compiler ( Compiler(..), CompilerFlavor(..) )
import Distribution.PackageDescription
( PackageDescription(..), BuildInfo(..),
Executable(..), Library(..) )
import Distribution.Package ( PackageIdentifier(..), showPackageId )
import Distribution.Package ( PackageIdentifier(..), showPackageId, Package(..) )
import Distribution.Simple.Setup ( CopyDest(..), BuildFlags(..),
MakefileFlags(..), fromFlag )
import Distribution.Simple.PreProcess ( preprocessSources, PPSuffixHandler )
Expand Down Expand Up @@ -88,7 +88,7 @@ build :: PackageDescription -- ^mostly information from the .cabal file
build pkg_descr lbi flags suffixes = do
let verbosity = fromFlag (buildVerbose flags)
initialBuildSteps pkg_descr lbi verbosity suffixes
setupMessage verbosity "Building" (package pkg_descr)
setupMessage verbosity "Building" (packageId pkg_descr)
case compilerFlavor (compiler lbi) of
GHC -> GHC.build pkg_descr lbi verbosity
JHC -> JHC.build pkg_descr lbi verbosity
Expand All @@ -106,7 +106,7 @@ makefile pkg_descr lbi flags suffixes = do
initialBuildSteps pkg_descr lbi verbosity suffixes
when (not (hasLibs pkg_descr)) $
die ("Makefile is only supported for libraries, currently.")
setupMessage verbosity "Generating Makefile" (package pkg_descr)
setupMessage verbosity "Generating Makefile" (packageId pkg_descr)
case compilerFlavor (compiler lbi) of
GHC -> GHC.makefile pkg_descr lbi flags
_ -> die ("Generating a Makefile is not supported for this compiler.")
Expand All @@ -123,7 +123,7 @@ initialBuildSteps pkg_descr lbi verbosity suffixes = do
map libBuildInfo (maybeToList (library pkg_descr)) ++
map buildInfo (executables pkg_descr)
unless (any buildable buildInfos) $ do
let name = showPackageId (package pkg_descr)
let name = showPackageId (packageId pkg_descr)
die ("Package " ++ name ++ " can't be built on this system.")

createDirectoryIfMissingVerbose verbosity True (buildDir lbi)
Expand Down Expand Up @@ -171,7 +171,7 @@ buildPathsModule pkg_descr lbi =
"import Data.Version"++
"\n"++
"\nversion :: Version"++
"\nversion = " ++ show (pkgVersion (package pkg_descr))++
"\nversion = " ++ show (pkgVersion (packageId pkg_descr))++
"\n"

body
Expand Down
12 changes: 6 additions & 6 deletions Distribution/Simple/BuildPaths.hs
Expand Up @@ -62,9 +62,9 @@ module Distribution.Simple.BuildPaths (

import System.FilePath (FilePath, (</>), (<.>))

import Distribution.Package (PackageIdentifier(..))
import Distribution.PackageDescription (PackageDescription(..))
import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(..))
import Distribution.Package (PackageIdentifier(..), Package(..))
import Distribution.PackageDescription (PackageDescription)
import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(buildDir))
import Distribution.Version (showVersion)
import Distribution.System (OS(..), os)

Expand All @@ -82,7 +82,7 @@ hscolourPref = haddockPref

haddockPref :: PackageDescription -> FilePath
haddockPref pkg_descr
= foldl1 (</>) [distPref, "doc", "html", pkgName (package pkg_descr)]
= foldl1 (</>) [distPref, "doc", "html", pkgName (packageId pkg_descr)]

-- |The directory in which we put auto-generated modules
autogenModulesDir :: LocalBuildInfo -> String
Expand All @@ -92,12 +92,12 @@ autogenModulesDir lbi = buildDir lbi </> "autogen"
-- |The name of the auto-generated module associated with a package
autogenModuleName :: PackageDescription -> String
autogenModuleName pkg_descr =
"Paths_" ++ map fixchar (pkgName (package pkg_descr))
"Paths_" ++ map fixchar (pkgName (packageId pkg_descr))
where fixchar '-' = '_'
fixchar c = c

haddockName :: PackageDescription -> FilePath
haddockName pkg_descr = pkgName (package pkg_descr) <.> "haddock"
haddockName pkg_descr = pkgName (packageId pkg_descr) <.> "haddock"

-- ---------------------------------------------------------------------------
-- Library file names
Expand Down
3 changes: 2 additions & 1 deletion Distribution/Simple/GHC.hs
Expand Up @@ -65,7 +65,8 @@ import Distribution.Simple.LocalBuildInfo
( LocalBuildInfo(..) )
import Distribution.Simple.BuildPaths
import Distribution.Simple.Utils
import Distribution.Package ( PackageIdentifier(..), showPackageId )
import Distribution.Package
( PackageIdentifier(..), showPackageId, Package(..) )
import Distribution.Simple.Program ( rawSystemProgram, rawSystemProgramConf,
rawSystemProgramStdoutConf,
rawSystemProgramStdout,
Expand Down
8 changes: 4 additions & 4 deletions Distribution/Simple/Haddock.hs
Expand Up @@ -46,7 +46,7 @@ module Distribution.Simple.Haddock (
) where

-- local
import Distribution.Package (PackageIdentifier, showPackageId)
import Distribution.Package (PackageIdentifier, showPackageId, Package(..))
import Distribution.PackageDescription as PD
(PackageDescription(..), BuildInfo(..), hcOptions,
Library(..), hasLibs, withLib,
Expand Down Expand Up @@ -122,10 +122,10 @@ haddock pkg_descr lbi suffixes flags = do
createDirectoryIfMissingVerbose verbosity True $ haddockPref pkg_descr
preprocessSources pkg_descr lbi False verbosity suffixes

setupMessage verbosity "Running Haddock for" (PD.package pkg_descr)
setupMessage verbosity "Running Haddock for" (packageId pkg_descr)

let replaceLitExts = map ( (tmpDir </>) . (`replaceExtension` "hs") )
let showPkg = showPackageId (PD.package pkg_descr)
let showPkg = showPackageId (packageId pkg_descr)
let outputFlag = if fromFlag (haddockHoogle flags)
then "--hoogle"
else "--html"
Expand Down Expand Up @@ -336,7 +336,7 @@ hscolour pkg_descr lbi suffixes flags = do
createDirectoryIfMissingVerbose verbosity True $ hscolourPref pkg_descr
preprocessSources pkg_descr lbi False verbosity suffixes

setupMessage verbosity "Running hscolour for" (PD.package pkg_descr)
setupMessage verbosity "Running hscolour for" (packageId pkg_descr)
let replaceDot = map (\c -> if c == '.' then '-' else c)

withLib pkg_descr () $ \lib -> when (isJust $ library pkg_descr) $ do
Expand Down
3 changes: 2 additions & 1 deletion Distribution/Simple/Install.hs
Expand Up @@ -48,6 +48,7 @@ module Distribution.Simple.Install (
import Distribution.PackageDescription (
PackageDescription(..), BuildInfo(..), Library(..),
hasLibs, withLib, hasExes, withExe )
import Distribution.Package (Package(..))
import Distribution.Simple.LocalBuildInfo (
LocalBuildInfo(..), InstallDirs(..), absoluteInstallDirs,
substPathTemplate)
Expand Down Expand Up @@ -141,7 +142,7 @@ install pkg_descr lbi flags = do
let targetProgPref = progdir (absoluteInstallDirs pkg_descr lbi NoCopyDest)
let scratchPref = scratchDir lbi
Hugs.install verbosity libPref progPref binPref targetProgPref scratchPref (progPrefixPref, progSuffixPref) pkg_descr
NHC -> do withLib pkg_descr () $ NHC.installLib verbosity libPref buildPref (package pkg_descr)
NHC -> do withLib pkg_descr () $ NHC.installLib verbosity libPref buildPref (packageId pkg_descr)
withExe pkg_descr $ NHC.installExe verbosity binPref buildPref (progPrefixPref, progSuffixPref)
_ -> die ("only installing with GHC, JHC, Hugs or nhc98 is implemented")
return ()
Expand Down
8 changes: 4 additions & 4 deletions Distribution/Simple/JHC.hs
Expand Up @@ -68,7 +68,7 @@ import Distribution.Simple.Program ( ConfiguredProgram(..), jhcProgram,
rawSystemProgram, rawSystemProgramStdoutConf )
import Distribution.Version ( VersionRange(AnyVersion) )
import Distribution.Package ( PackageIdentifier(..), showPackageId,
parsePackageId )
parsePackageId, Package(..) )
import Distribution.Simple.Utils( createDirectoryIfMissingVerbose,
copyFileVerbose, die, info, intercalate )
import System.FilePath ( (</>) )
Expand Down Expand Up @@ -136,7 +136,7 @@ build pkg_descr lbi verbosity = do
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)
let pkgid = showPackageId (packageId pkg_descr)
pfile = buildDir lbi </> "jhc-pkg.conf"
hlfile= buildDir lbi </> (pkgid ++ ".hl")
writeFile pfile $ jhcPkgConf pkg_descr
Expand Down Expand Up @@ -164,14 +164,14 @@ jhcPkgConf pd =
let sline name sel = name ++ ": "++sel pd
Just lib = library pd
comma = intercalate ","
in unlines [sline "name" (showPackageId . package)
in unlines [sline "name" (showPackageId . packageId)
,"exposed-modules: " ++ (comma (PD.exposedModules lib))
,"hidden-modules: " ++ (comma (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"
let p = showPackageId (packageId pkg_descr)++".hl"
createDirectoryIfMissingVerbose verb True dest
copyFileVerbose verb (build_dir </> p) (dest </> p)

Expand Down
8 changes: 4 additions & 4 deletions Distribution/Simple/LocalBuildInfo.hs
Expand Up @@ -59,7 +59,7 @@ import qualified Distribution.Simple.InstallDirs as InstallDirs
import Distribution.Simple.Setup (CopyDest(..))
import Distribution.Simple.Program (ProgramConfiguration)
import Distribution.PackageDescription (PackageDescription(..))
import Distribution.Package (PackageIdentifier(..))
import Distribution.Package (PackageIdentifier(..), Package(..))
import Distribution.Simple.Compiler (Compiler(..), PackageDB)
import Distribution.Simple.PackageIndex (PackageIndex)
import Distribution.InstalledPackageInfo (InstalledPackageInfo)
Expand Down Expand Up @@ -112,7 +112,7 @@ absoluteInstallDirs :: PackageDescription -> LocalBuildInfo -> CopyDest
-> InstallDirs FilePath
absoluteInstallDirs pkg_descr lbi copydest =
InstallDirs.absoluteInstallDirs
(package pkg_descr)
(packageId pkg_descr)
(compilerId (compiler lbi))
copydest
(installDirTemplates lbi)
Expand All @@ -122,7 +122,7 @@ prefixRelativeInstallDirs :: PackageDescription -> LocalBuildInfo
-> InstallDirs (Maybe FilePath)
prefixRelativeInstallDirs pkg_descr lbi =
InstallDirs.prefixRelativeInstallDirs
(package pkg_descr)
(packageId pkg_descr)
(compilerId (compiler lbi))
(installDirTemplates lbi)

Expand All @@ -131,6 +131,6 @@ substPathTemplate :: PackageDescription -> LocalBuildInfo
substPathTemplate pkg_descr lbi = fromPathTemplate
. ( InstallDirs.substPathTemplate env )
where env = initialPathTemplateEnv
(package pkg_descr)
(packageId pkg_descr)
(compilerId (compiler lbi))

4 changes: 2 additions & 2 deletions Distribution/Simple/NHC.hs
Expand Up @@ -46,7 +46,7 @@ module Distribution.Simple.NHC
) where

import Distribution.Package
( PackageIdentifier(..) )
( PackageIdentifier(..), Package(..) )
import Distribution.PackageDescription
( PackageDescription(..), BuildInfo(..), Library(..), Executable(..),
withLib, withExe, hcOptions )
Expand Down Expand Up @@ -167,7 +167,7 @@ build pkg_descr lbi verbosity = do
info verbosity "Linking..."
let --cObjs = [ targetDir </> cFile `replaceExtension` objExtension
-- | cFile <- cSources bi ]
libName = mkLibName targetDir (pkgName (package pkg_descr))
libName = mkLibName targetDir (pkgName (packageId pkg_descr))
hObjs = [ targetDir </> dotToSep m <.> objExtension
| m <- modules ]

Expand Down
6 changes: 3 additions & 3 deletions Distribution/Simple/PreProcess.hs
Expand Up @@ -59,7 +59,7 @@ import Distribution.Simple.PreProcess.Unlit (unlit)
import Distribution.PackageDescription (PackageDescription(..),
BuildInfo(..), Executable(..), withExe,
Library(..), withLib, libModules)
import Distribution.Package (showPackageId)
import Distribution.Package (showPackageId, Package(..))
import Distribution.Simple.Compiler (CompilerFlavor(..), Compiler(..), compilerVersion)
import Distribution.Simple.LocalBuildInfo (LocalBuildInfo(..))
import Distribution.Simple.Utils
Expand Down Expand Up @@ -166,14 +166,14 @@ preprocessSources :: PackageDescription

preprocessSources pkg_descr lbi forSDist verbosity handlers = do
withLib pkg_descr () $ \ lib -> do
setupMessage verbosity "Preprocessing library" (package pkg_descr)
setupMessage verbosity "Preprocessing library" (packageId pkg_descr)
let bi = libBuildInfo lib
let biHandlers = localHandlers bi
sequence_ [ preprocessModule (hsSourceDirs bi) (buildDir lbi) forSDist
modu verbosity builtinSuffixes biHandlers
| modu <- libModules pkg_descr]
unless (null (executables pkg_descr)) $
setupMessage verbosity "Preprocessing executables for" (package pkg_descr)
setupMessage verbosity "Preprocessing executables for" (packageId pkg_descr)
withExe pkg_descr $ \ theExe -> do
let bi = buildInfo theExe
let biHandlers = localHandlers bi
Expand Down
18 changes: 9 additions & 9 deletions Distribution/Simple/Register.hs
Expand Up @@ -62,7 +62,7 @@ import Distribution.Simple.Setup (RegisterFlags(..), CopyDest(..),
fromFlag, fromFlagOrDefault)
import Distribution.PackageDescription (PackageDescription(..),
BuildInfo(..), Library(..))
import Distribution.Package (PackageIdentifier(..), showPackageId)
import Distribution.Package (PackageIdentifier(..), showPackageId, Package(..))
import Distribution.Verbosity
import Distribution.InstalledPackageInfo
(InstalledPackageInfo, showInstalledPackageInfo,
Expand Down Expand Up @@ -101,13 +101,13 @@ register :: PackageDescription -> LocalBuildInfo
-> IO ()
register pkg_descr lbi regFlags
| isNothing (library pkg_descr) = do
setupMessage (fromFlag $ regVerbose regFlags) "No package to register" (package pkg_descr)
setupMessage (fromFlag $ regVerbose regFlags) "No package to register" (packageId pkg_descr)
return ()
| otherwise = do
let isWindows = case os of Windows _ -> True; _ -> False
genScript = fromFlag (regGenScript regFlags)
genPkgConf = isJust (fromFlag (regGenPkgConf regFlags))
genPkgConfigDefault = showPackageId (package pkg_descr) <.> "conf"
genPkgConfigDefault = showPackageId (packageId pkg_descr) <.> "conf"
genPkgConfigFile = fromMaybe genPkgConfigDefault
(fromFlag (regGenPkgConf regFlags))
verbosity = fromFlag (regVerbose regFlags)
Expand All @@ -118,7 +118,7 @@ register pkg_descr lbi regFlags
| genScript = "Writing registration script: "
++ regScriptLocation ++ " for"
| otherwise = "Registering"
setupMessage verbosity message (package pkg_descr)
setupMessage verbosity message (packageId pkg_descr)

case compilerFlavor (compiler lbi) of
GHC -> do
Expand Down Expand Up @@ -223,7 +223,7 @@ mkInstalledPackageInfo pkg_descr lbi inplace = do
}
where inplaceDocdir = pwd </> distPref </> "doc"
inplaceHtmldir = inplaceDocdir </> "html"
</> pkgName (package pkg_descr)
</> pkgName (packageId pkg_descr)
(absinc,relinc) = partition isAbsolute (includeDirs bi)
installIncludeDir | null (installIncludes bi) = []
| otherwise = [includedir installDirs]
Expand All @@ -238,7 +238,7 @@ mkInstalledPackageInfo pkg_descr lbi inplace = do
| otherwise = libdir installDirs
in
return emptyInstalledPackageInfo{
IPI.package = package pkg_descr,
IPI.package = packageId pkg_descr,
IPI.license = license pkg_descr,
IPI.copyright = copyright pkg_descr,
IPI.maintainer = maintainer pkg_descr,
Expand All @@ -253,7 +253,7 @@ mkInstalledPackageInfo pkg_descr lbi inplace = do
IPI.hiddenModules = otherModules bi,
IPI.importDirs = [libraryDir],
IPI.libraryDirs = libraryDir : extraLibDirs bi,
IPI.hsLibraries = ["HS" ++ showPackageId (package pkg_descr)],
IPI.hsLibraries = ["HS" ++ showPackageId (packageId pkg_descr)],
IPI.extraLibraries = extraLibs bi,
IPI.includeDirs = absinc ++ if inplace
then map (pwd </>) relinc
Expand All @@ -278,15 +278,15 @@ unregister pkg_descr lbi regFlags = do
verbosity = fromFlag (regVerbose regFlags)
packageDB = fromFlagOrDefault (withPackageDB lbi) (regPackageDB regFlags)
installDirs = absoluteInstallDirs pkg_descr lbi NoCopyDest
setupMessage verbosity "Unregistering" (package pkg_descr)
setupMessage verbosity "Unregistering" (packageId pkg_descr)
case compilerFlavor (compiler lbi) of
GHC -> do
config_flags <- case packageDB of
GlobalPackageDB -> return []
UserPackageDB -> return ["--user"]
SpecificPackageDB db -> return ["--package-conf=" ++ db]

let removeCmd = ["unregister",showPackageId (package pkg_descr)]
let removeCmd = ["unregister",showPackageId (packageId pkg_descr)]
let Just pkgTool = lookupProgram ghcPkgProgram (withPrograms lbi)
allArgs = removeCmd ++ config_flags
if genScript
Expand Down
6 changes: 3 additions & 3 deletions Distribution/Simple/SrcDist.hs
Expand Up @@ -57,7 +57,7 @@ import Distribution.PackageDescription
(PackageDescription(..), BuildInfo(..), Executable(..), Library(..),
withLib, withExe)
import Distribution.PackageDescription.Check
import Distribution.Package (showPackageId, PackageIdentifier(pkgVersion))
import Distribution.Package (showPackageId, PackageIdentifier(pkgVersion), Package(..))
import Distribution.Version (Version(versionBranch), VersionRange(AnyVersion))
import Distribution.Simple.Utils (createDirectoryIfMissingVerbose,
die, warn, notice, setupMessage, defaultPackageDesc,
Expand Down Expand Up @@ -120,7 +120,7 @@ prepareTree :: PackageDescription -- ^info from the cabal file
-> IO FilePath

prepareTree pkg_descr verbosity mb_lbi snapshot tmpDir pps date = do
setupMessage verbosity "Building source dist for" (package pkg_descr)
setupMessage verbosity "Building source dist for" (packageId pkg_descr)
ex <- doesDirectoryExist tmpDir
when ex (die $ "Source distribution already in place. please move: " ++ tmpDir)
let targetDir = tmpDir </> (nameVersion pkg_descr)
Expand Down Expand Up @@ -274,4 +274,4 @@ tarBallName :: PackageDescription -> FilePath
tarBallName p = (nameVersion p) ++ ".tar.gz"

nameVersion :: PackageDescription -> String
nameVersion = showPackageId . package
nameVersion = showPackageId . packageId

0 comments on commit db061bf

Please sign in to comment.