Skip to content
Snippets Groups Projects
Commit f8887306 authored by Isaac Potoczny-Jones's avatar Isaac Potoczny-Jones
Browse files

mostly fiddle with target file locations (prefixes) and tests

** Added tests to look for .o and .hi files, as well as libHStest in destdir
** Added a handful of tests for sdist, and checked to see if sdist directory exists
** moved temporary sdist location from dist/build to dist/src
** added a prefix to several of the commands, so they know where to put files
*** build  -- dist/build
*** install -- both dist/build and install-prefix
*** sdist -- dist/src and target directory, dist
** chaged ar command to output libHS file in correct place
parent 0bb0cf2a
No related branches found
No related tags found
No related merge requests found
......@@ -67,7 +67,7 @@ import Directory(setCurrentDirectory, doesFileExist,
import System.Cmd(system)
import System.Exit(ExitCode(..))
import HUnit(runTestTT, Test(..), Counts, assertBool)
import HUnit(runTestTT, Test(..), Counts, assertBool, assertEqual)
label :: String -> String
label t = "-= " ++ t ++ " =-"
......@@ -83,23 +83,33 @@ tests = [TestCase $
do setCurrentDirectory "test"
dirE1 <- doesDirectoryExist ",tmp"
when dirE1 (system "rm -r ,tmp">>return())
dirE2 <- doesDirectoryExist "dist"
when dirE2 (system "rm -r dist">>return())
-- system "ls"
system "./setup configure --prefix=,tmp"
let targetDir = ",tmp/lib/test-1.0/"
system "./setup build"
instRetCode <- system "./setup install --user"
dirE <- doesDirectoryExist targetDir
assertBool "target dir exists" dirE
let files = ["A.hs", "B/A.hs", "libHStest-1.0.a"]
doesDirectoryExist targetDir >>=
assertBool "target dir exists"
let files = "libHStest-1.0.a":[x++y |
x <- ["A", "B/A"],
y <- [".o", ".hi", ".hs"]]
allFilesE <- sequence [doesFileExist (targetDir ++ t)
| t <- files]
sequence [assertBool ("target file missing: " ++ targetDir ++ f) e
| (e, f) <- zip allFilesE files]
assertBool "install returned error code" (instRetCode == ExitSuccess)
assertEqual "install returned error code" ExitSuccess instRetCode
system "./setup sdist"
doesFileExist "dist/test-1.0.tgz" >>=
assertBool "sdist did not put the expected file in place"
doesFileExist "dist/src" >>=
assertEqual "dist/src exists" False
doesFileExist "dist/build" >>=
assertBool "dist/build doesn't exists"
]
main :: IO ()
main = do putStrLn "compile successful"
putStrLn "-= Setup Tests =-"
......
......@@ -62,7 +62,7 @@ import Distribution.Simple.Register ( register, unregister )
import Distribution.Simple.Configure(LocalBuildInfo(..), getPersistBuildConfig,
configure, writePersistBuildConfig)
import Distribution.Simple.Install(install)
import Distribution.Simple.Utils (die)
import Distribution.Simple.Utils (die, pathSeperatorStr)
import Distribution.Misc (License(..))
import Distribution.Version (Version(..))
......@@ -89,6 +89,9 @@ doBuildInstall f pkgConf
defaultMain :: PackageDescription -> IO ()
defaultMain pkg_descr
= do args <- getArgs
let distPref = "dist"
let buildPref = distPref ++ pathSeperatorStr ++ "build"
let srcPref = distPref ++ pathSeperatorStr ++ "src"
case parseArgs args of
Right (HelpCmd, _) -> hPutStr stderr (optionHelpString helpprefix)
......@@ -100,18 +103,18 @@ defaultMain pkg_descr
Right (BuildCmd, extra_flags) -> do
no_extra_flags extra_flags
localbuildinfo <- getPersistBuildConfig
build pkg_descr localbuildinfo
build buildPref pkg_descr localbuildinfo
Right (InstallCmd install_prefixM userInst, extra_flags) -> do
no_extra_flags extra_flags
localbuildinfo <- getPersistBuildConfig
install pkg_descr localbuildinfo install_prefixM
install buildPref pkg_descr localbuildinfo install_prefixM
when (isNothing install_prefixM) (register pkg_descr localbuildinfo userInst)
Right (SDistCmd, extra_flags) -> do
no_extra_flags extra_flags
localbuildinfo <- getPersistBuildConfig
sdist pkg_descr localbuildinfo
sdist srcPref distPref pkg_descr localbuildinfo
Right (RegisterCmd userFlag, extra_flags) -> do
no_extra_flags extra_flags
......
......@@ -53,7 +53,9 @@ import Distribution.Package (PackageDescription(..), showPackageId)
import Distribution.Simple.Configure (LocalBuildInfo, compiler)
import Distribution.Simple.Utils (rawSystemExit, setupMessage,
die, rawSystemPathExit,
pathSeperatorStr, split, createIfNotExists)
pathSeperatorStr, split, createIfNotExists,
mkLibName
)
import Control.Monad (when)
......@@ -66,10 +68,10 @@ import HUnit (Test)
-- -----------------------------------------------------------------------------
-- Build the library
build :: PackageDescription -> LocalBuildInfo -> IO ()
build pkg_descr lbi = do
build :: FilePath -- ^Build location
-> PackageDescription -> LocalBuildInfo -> IO ()
build pref pkg_descr lbi = do
setupMessage "Building" pkg_descr
let pref = ("dist" ++ pathSeperatorStr ++ "build")
createIfNotExists True pref
case compilerFlavor (compiler lbi) of
GHC -> buildGHC pref pkg_descr lbi
......@@ -99,8 +101,8 @@ buildGHC pref pkg_descr lbi = do
-- now, build the library
let objs = map (++objsuffix) (map dotToSep (allModules pkg_descr))
lib = mkLibName (showPackageId (package pkg_descr))
rawSystemPathExit "ar" (["q", lib] ++ (map (pref ++) objs))
lib = mkLibName pref (showPackageId (package pkg_descr))
rawSystemPathExit "ar" (["q", lib] ++ (map ((pref ++ pathSeperatorStr) ++) objs))
constructGHCCmdLine :: FilePath -> PackageDescription -> LocalBuildInfo -> [String]
constructGHCCmdLine pref pkg_descr _ =
......@@ -125,9 +127,6 @@ objsuffix = ".obj"
objsuffix = ".o"
#endif
mkLibName :: String -> String
mkLibName lib = "libHS" ++ lib ++ ".a"
dotToSep :: String -> String
dotToSep s = concat $ intersperse pathSeperatorStr (split '.' s)
......
......@@ -52,7 +52,10 @@ module Distribution.Simple.Install (
import Distribution.Package (PackageDescription(..), showPackageId)
import Distribution.Simple.Configure(LocalBuildInfo(..))
import Distribution.Simple.Utils(setupMessage, moveSources, pathSeperatorStr)
import Distribution.Simple.Utils(setupMessage, moveSources,
pathSeperatorStr, mkLibName)
import System.Cmd(system)
#ifdef DEBUG
import HUnit (Test)
......@@ -61,15 +64,19 @@ import HUnit (Test)
-- |FIX: for now, only works with hugs or sdist-style
-- installation... must implement for .hi files and such... how do we
-- know which files to expect?
install :: PackageDescription -> LocalBuildInfo
install :: FilePath -- ^build location
-> PackageDescription -> LocalBuildInfo
-> Maybe FilePath -- ^install-prefix
-> IO ()
install pkg_descr lbi install_prefixM = do
install buildPref pkg_descr lbi install_prefixM = do
let pref = (maybe (prefix lbi) id install_prefixM) ++
pathSeperatorStr ++ "lib" ++ pathSeperatorStr ++ (showPackageId $ package pkg_descr)
setupMessage "Installing" pkg_descr
moveSources pref (allModules pkg_descr) (mainModules pkg_descr)
-- installation step should be performed by caller.
moveSources buildPref pref (allModules pkg_descr) (mainModules pkg_descr)
system $ "cp " ++ mkLibName buildPref (showPackageId (package pkg_descr))
++ " " ++ mkLibName pref (showPackageId (package pkg_descr))
return ()
-- register step should be performed by caller.
-- -----------------------------------------------------------------------------
-- Installation policies
......
......@@ -49,9 +49,11 @@ module Distribution.Simple.SrcDist (
import Distribution.Package(PackageDescription(..), showPackageId)
import Distribution.Simple.Configure(LocalBuildInfo)
import Distribution.Simple.Utils(setupMessage, moveSources, pathSeperatorStr)
import Distribution.Simple.Utils(setupMessage, moveSources, pathSeperatorStr, die)
import Control.Monad(when)
import System.Cmd (system)
import System.Directory (doesDirectoryExist)
#ifdef DEBUG
import HUnit (Test)
......@@ -59,22 +61,23 @@ import HUnit (Test)
-- |Create a source distribution. FIX: Calls tar directly (won't work
-- on windows).
sdist :: PackageDescription -> LocalBuildInfo -> IO ()
sdist pkg_descr _ = do
sdist :: FilePath -- ^build prefix
-> FilePath -- ^TargetPrefix
-> PackageDescription -> LocalBuildInfo -> IO ()
sdist srcPref targetPref pkg_descr _ = do
setupMessage "Building source dist for" pkg_descr
moveSources (distSrc++pathSeperatorStr++nameVersion pkg_descr)
ex <- doesDirectoryExist srcPref
when ex (die $ "Source distribution already in place. please move: " ++ srcPref)
moveSources srcPref (srcPref++pathSeperatorStr++nameVersion pkg_descr)
(allModules pkg_descr) (mainModules pkg_descr)
system $ "tar --directory=" ++ distSrc ++ " -zcf"
++ " dist/" ++ (tarBallName pkg_descr)
system $ "tar --directory=" ++ srcPref ++ " -zcf "
++ targetPref ++ pathSeperatorStr ++ (tarBallName pkg_descr)
++ " " ++ (nameVersion pkg_descr)
system $ "rm -rf " ++ distSrc
system $ "rm -rf " ++ srcPref
putStrLn "Source tarball created."
------------------------------------------------------------
distSrc :: FilePath
distSrc = "dist/src"
-- |The file name of the tarball
tarBallName :: PackageDescription -> FilePath
tarBallName p = (nameVersion p) ++ ".tgz"
......
......@@ -55,7 +55,8 @@ module Distribution.Simple.Utils (
rawSystemPathExit,
moveSources,
hunitTests,
createIfNotExists
createIfNotExists,
mkLibName,
) where
import Distribution.Package (PackageDescription(..), showPackageId)
......@@ -135,7 +136,7 @@ setupMessage msg pkg_descr =
putStrLn (msg ++ ' ':showPackageId (package pkg_descr) ++ "...")
die :: String -> IO a
die msg = do hPutStr stderr msg; exitWith (ExitFailure 1)
die msg = do hPutStr stderr (msg++"\n"); exitWith (ExitFailure 1)
-- -----------------------------------------------------------------------------
-- rawSystem variants
......@@ -257,11 +258,12 @@ moduleToPossiblePaths s
-- |Put the source files into the right directory in preperation for
-- something like sdist or installHugs.
moveSources :: FilePath -- ^Target directory
moveSources :: FilePath -- ^build prefix (location of objects)
-> FilePath -- ^Target directory
-> [String] -- ^Modules
-> [String] -- ^Main modules
-> IO ()
moveSources _targetDir sources mains
moveSources buildPref _targetDir sources mains
= do let targetDir = maybeAddSep _targetDir
createIfNotExists True targetDir
-- Create parent directories for everything:
......@@ -280,6 +282,12 @@ moveSources _targetDir sources mains
>> exitWith (ExitFailure 1))
return $ fromJust p
mkLibName :: FilePath -- ^file Prefix
-> String -- ^library name.
-> String
mkLibName pref lib = pref ++ pathSeperatorStr ++ "libHS" ++ lib ++ ".a"
-- ------------------------------------------------------------
-- * Testing
-- ------------------------------------------------------------
......
module Main where
module A where
a = 42 :: Int
main = print a
all:
ghc -Wall --make -i../:/usr/local/src/HUnit-1.0 Setup.hs -o setup
clean:
rm *.o setup *.hi
rm -f setup a.out
rm -rf ,tmp dist
find . -name "*.o" |xargs rm -f
find . -name "*.hi" |xargs rm -f
check: all
./setup configure --user --prefix=/tmp/foo
./setup install --install-prefix=/tmp/bar
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment