Skip to content
GitLab
Menu
Projects
Groups
Snippets
Help
Help
Support
Community forum
Keyboard shortcuts
?
Submit feedback
Sign in / Register
Toggle navigation
Menu
Open sidebar
Glasgow Haskell Compiler
Packages
Cabal
Commits
3c689f00
Commit
3c689f00
authored
Apr 28, 2008
by
Duncan Coutts
Browse files
Make the old test code compile
Still a lot of bit rot, many of the full tests fail due to changed paths
parent
fa8a6b1e
Changes
4
Hide whitespace changes
Inline
Side-by-side
tests/UnitTest.hs
View file @
3c689f00
...
...
@@ -46,9 +46,6 @@ module Main where
import
qualified
UnitTest.Distribution.Version
as
D.V
(
hunitTests
)
import
qualified
UnitTest.Distribution.PackageDescription
as
D.PD
(
hunitTests
)
import
qualified
Distribution.Simple.Configure
as
D.S.C
(
localBuildInfoFile
)
import
qualified
Distribution.Simple.Register
as
D.S.R
(
installedPkgConfigFile
)
import
Distribution.Simple.Compiler
(
CompilerFlavor
(
..
),
compilerVersion
)
import
Distribution.Simple.Program
(
defaultProgramConfiguration
)
import
Distribution.Version
(
Version
(
..
))
...
...
@@ -220,10 +217,10 @@ tests currDir comp compConf compVersion = [
assertCmd'
compCmd
"configure -v0"
"configure failed"
assertCmd'
compCmd
"unregister -v0 --user"
"unregister failed"
system
$
"touch
"
++
D
.
S
.
C
.
localBuildInfoFile
system
$
"touch
"
++
D
.
S
.
R
.
installed
PkgC
onfig
File
doesFileExist
D
.
S
.
C
.
localBuildInfoFile
>>=
assertBool
(
"touch
"
++
D
.
S
.
C
.
localBuildInfoFile
++
"
failed"
)
system
$
"touch
dist/setup-config"
system
$
"touch
dist/
installed
-pkg-c
onfig
"
doesFileExist
"dist/setup-config"
>>=
assertBool
(
"touch
dist/setup-config
failed"
)
-- Test clean:
assertBuild
...
...
@@ -233,10 +230,10 @@ tests currDir comp compConf compVersion = [
doesDirectoryExist
"dist/build"
>>=
assertEqual
"HUnit clean did not get rid of build directory"
False
doesFileExist
D
.
S
.
C
.
localBuildInfoFile
>>=
assertEqual
(
"clean
"
++
D
.
S
.
C
.
localBuildInfoFile
++
"
failed"
)
False
doesFileExist
D
.
S
.
R
.
installed
PkgC
onfig
File
>>=
assertEqual
(
"clean
"
++
D
.
S
.
R
.
installedPkgConfigFile
++
"
failed"
)
False
doesFileExist
"dist/setup-config"
>>=
assertEqual
(
"clean
dist/setup-config
failed"
)
False
doesFileExist
"dist/
installed
-pkg-c
onfig
"
>>=
assertEqual
(
"clean
dist/installed-pkg-config
failed"
)
False
assertConfigure
",tmp"
assertHaddock
...
...
@@ -397,7 +394,7 @@ tests currDir comp compConf compVersion = [
(doesFileExist "/tmp/lib/HSQL/GHC/libHSsql.a" >>=
assertBool "libHSsql.a doesn't exist. copy failed.")-}
]
where
testdir
=
currDir
</>
"
t
ests"
where
testdir
=
currDir
</>
"
systemT
ests"
compStr
=
show
comp
compVerStr
=
concat
.
intersperse
"."
.
map
show
.
versionBranch
$
compVersion
compCmd
=
command
comp
...
...
tests/UnitTest/Distribution/PackageDescription.hs
View file @
3c689f00
...
...
@@ -39,7 +39,7 @@ THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
(INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE
OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}
module
PackageDescription
Tests
(
module
UnitTest.Distribution.
PackageDescription
(
-- * Debugging
hunitTests
,
...
...
@@ -47,14 +47,16 @@ module PackageDescriptionTests (
import
Distribution.ParseUtils
import
Distribution.Package
(
PackageIdentifier
(
..
))
import
Distribution.Version
(
Version
(
..
),
VersionRange
(
..
),
Dependency
(
..
))
import
Distribution.Compiler
(
CompilerFlavor
(
..
))
import
Distribution.Package
(
PackageIdentifier
(
..
),
Dependency
(
..
))
import
Distribution.Version
(
Version
(
..
),
VersionRange
(
..
))
import
Distribution.Compiler
(
CompilerFlavor
(
..
),
CompilerId
(
..
))
import
Distribution.System
(
OS
(
..
),
buildOS
,
Arch
(
..
),
buildArch
)
import
Distribution.PackageDescription
import
Distribution.PackageDescription.
Types
import
Distribution.PackageDescription.
Configuration
import
Distribution.PackageDescription.Parse
import
Distribution.PackageDescription.QA
(
sanityCheckPackage
)
import
Distribution.PackageDescription.Check
import
qualified
Distribution.Simple.PackageIndex
as
PackageIndex
import
Data.Maybe
(
catMaybes
)
import
Data.List
(
sortBy
)
...
...
@@ -123,7 +125,7 @@ compatTestPkgDesc = unlines [
compatTestPkgDescAnswer
::
PackageDescription
compatTestPkgDescAnswer
=
PackageDescription
empty
PackageDescription
{
package
=
PackageIdentifier
{
pkgName
=
"Cabal"
,
pkgVersion
=
Version
{
versionBranch
=
[
0
,
1
,
1
,
1
,
1
],
...
...
@@ -187,7 +189,8 @@ compatTestPkgDescAnswer =
compatParseDescription
::
String
->
ParseResult
PackageDescription
compatParseDescription
descr
=
do
gpd
<-
parsePackageDescription
descr
case
finalizePackageDescription
[]
Nothing
""
""
(
""
,
Version
[]
[]
)
gpd
of
case
finalizePackageDescription
[]
(
Nothing
::
Maybe
(
PackageIndex
.
PackageIndex
PackageIdentifier
))
buildOS
buildArch
(
CompilerId
GHC
(
Version
[]
[]
))
[]
gpd
of
Left
_
->
syntaxError
(
-
1
)
"finalize failed"
Right
(
pd
,
_
)
->
return
pd
...
...
@@ -251,7 +254,9 @@ hunitTests =
++
(
unlines
$
comparePackageDescriptions
d
d'
))
(
d
==
d'
)
,
TestLabel
"Sanity checker"
$
TestCase
$
do
(
warns
,
ers
)
<-
sanityCheckPackage
emptyPackageDescription
let
checks
=
checkConfiguredPackage
emptyPackageDescription
ers
=
[
s
|
PackageBuildImpossible
s
<-
checks
]
warns
=
[
s
|
PackageBuildWarning
s
<-
checks
]
assertEqual
"Wrong number of errors"
2
(
length
ers
)
assertEqual
"Wrong number of warnings"
3
(
length
warns
)
]
...
...
@@ -395,17 +400,17 @@ test_finalizePD =
case
parsePackageDescription
testFile
of
ParseFailed
err
->
print
err
ParseOk
_
ppd
->
do
case
finalizePackageDescription
[(
"debug"
,
True
)]
(
Just
pkgs
)
os
arch
impl
ppd
of
case
finalizePackageDescription
[(
FlagName
"debug"
,
True
)]
(
Just
pkgs
)
os
arch
impl
[]
ppd
of
Right
(
pd
,
fs
)
->
do
putStrLn
$
showPackageDescription
pd
print
fs
Left
missing
->
putStrLn
$
"missing: "
++
show
missing
putStrLn
$
showPackageDescription
$
flattenPackageDescription
ppd
where
pkgs
=
[
PackageIdentifier
"blub"
(
Version
[
1
,
0
]
[]
)
pkgs
=
PackageIndex
.
fromList
[
PackageIdentifier
"blub"
(
Version
[
1
,
0
]
[]
)
--, PackageIdentifier "hunit" (Version [1,1] [])
,
PackageIdentifier
"blab"
(
Version
[
0
,
1
]
[]
)
]
os
=
"win32"
arch
=
"amd
64
"
impl
=
(
"ghc"
,
Version
[
6
,
6
]
[]
)
os
=
Windows
arch
=
X86_
64
impl
=
CompilerId
GHC
(
Version
[
6
,
6
]
[]
)
tests/UnitTest/Distribution/Version.hs
View file @
3c689f00
...
...
@@ -43,6 +43,8 @@ OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE. -}
module
UnitTest.Distribution.Version
(
hunitTests
)
where
import
Distribution.Version
import
Distribution.Text
(
simpleParse
)
import
Data.Version
(
Version
(
..
),
showVersion
)
import
Control.Monad
(
liftM
)
...
...
@@ -57,14 +59,6 @@ import Test.HUnit
-- * Testing
-- ------------------------------------------------------------
-- |Simple version parser wrapper
doVersionParse
::
String
->
Either
String
Version
doVersionParse
input
=
case
results
of
[
y
]
->
Right
y
[]
->
Left
"No parse"
_
->
Left
"Ambigous parse"
where
results
=
[
x
|
(
x
,
""
)
<-
readP_to_S
parseVersion
input
]
branch1
::
[
Int
]
branch1
=
[
1
]
...
...
@@ -87,9 +81,9 @@ hunitTests :: [Test]
hunitTests
=
[
"released version 1"
~:
"failed"
~:
(
Right
$
release1
)
~=?
doVersion
Parse
"1"
,
~:
(
Just
release1
)
~=?
simple
Parse
"1"
,
"released version 3"
~:
"failed"
~:
(
Right
$
release3
)
~=?
doVersion
Parse
"1.2.3"
,
~:
(
Just
release3
)
~=?
simple
Parse
"1.2.3"
,
"range comparison LaterVersion 1"
~:
"failed"
~:
True
...
...
tests/hackage/check.sh
View file @
3c689f00
#!/bin/sh
base_version
=
1.2.3.0
test_version
=
1.3.
9
test_version
=
1.3.
10
for
setup
in
archive/
*
/
*
/Setup.hs archive/
*
/
*
/Setup.lhs
;
do
...
...
Write
Preview
Supports
Markdown
0%
Try again
or
attach a new file
.
Attach a file
Cancel
You are about to add
0
people
to the discussion. Proceed with caution.
Finish editing this message first!
Cancel
Please
register
or
sign in
to comment