[Pkg-haskell-commits] [SCM] haskell-testpack branch, master, updated. debian/1.0.2-1-4-gb0d6b36

John Goerzen jgoerzen at complete.org
Fri Apr 23 15:24:16 UTC 2010


The following commit has been merged in the master branch:
commit 7cb1e8b5aac6c6980b27d04fb0367b93079bd619
Author: John Goerzen <jgoerzen at complete.org>
Date:   Fri Jan 23 11:01:12 2009 -0600

    Removed more MissingH stuff

diff --git a/testsrc/Bitstest.hs b/testsrc/Bitstest.hs
deleted file mode 100644
index bd66d0c..0000000
--- a/testsrc/Bitstest.hs
+++ /dev/null
@@ -1,52 +0,0 @@
-{- arch-tag: Bits tests main file
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module Bitstest(tests) where
-import Test.HUnit
-import Data.Bits.Utils
-import Data.Word
-
-test_fromBytes =
-    let f :: [Word32] -> Word32 -> Test
-        f inp exp = TestCase $ exp @=? fromBytes inp in
-        [
-         f [] 0
-        ,f [0] 0
-        ,f [1] 1
-        ,f [0xff, 0] 0xff00
-        ,f [0x0, 0xff] 0xff
-        ,f [0x12, 0x34, 0x56, 0x78] 0x12345678
-        ,f [0xff, 0xff, 0xff, 0xff] 0xffffffff
-        ,f [0xff, 0, 0, 0] 0xff000000
-        ]
-
-test_getBytes =
-    let f :: Word32 -> [Word32] -> Test
-        f inp exp = TestCase $ exp @=? getBytes inp in
-        [
-         f 0 [0, 0, 0, 0]
-        ,f 0x1200 [0, 0, 0x12, 0]
-        ,f 0x0012 [0, 0, 0, 0x12]
-        ,f 0xffffffff [0xff, 0xff, 0xff, 0xff]
-        ,f 0x12345678 [0x12, 0x34, 0x56, 0x78]
-        ,f 0xf0000000 [0xf0, 0, 0, 0]
-        ]
-
-tests = TestList [TestLabel "getBytes" (TestList test_getBytes),
-                  TestLabel "fromBytes" (TestList test_fromBytes)
-                 ]
diff --git a/testsrc/CRC32GZIPtest.hs b/testsrc/CRC32GZIPtest.hs
deleted file mode 100644
index 4345400..0000000
--- a/testsrc/CRC32GZIPtest.hs
+++ /dev/null
@@ -1,37 +0,0 @@
-{- arch-tag: Tests for Gzip CRC-32 module
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module CRC32GZIPtest(tests) where
-import Test.HUnit
-import Data.Hash.CRC32.GZip
-
-test_crcgzip =
-    let f msg inp exp = TestLabel msg $ TestCase $ assertEqual "" exp (calc_crc32 inp) in
-        [f "Simple" "Test 1" 0x9927f819
-        ,f "Empty" "" 0x0
-         --f "Empty" "" 4294967295,
-         --f "1" "1" 433426081,
-         --f "some numbers" "153141341309874102987412" 2083856642,
-         --f "Some text" "This is a test of the crc32 thing\n" 2449124888
-
-        ]
-
-tests = TestList [TestLabel "crcgzip" (TestList test_crcgzip)
-
-                 ]
-
diff --git a/testsrc/CRC32POSIXtest.hs b/testsrc/CRC32POSIXtest.hs
deleted file mode 100644
index 394ef84..0000000
--- a/testsrc/CRC32POSIXtest.hs
+++ /dev/null
@@ -1,36 +0,0 @@
-{- arch-tag: Tests for CRC-32 module
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module CRC32POSIXtest(tests) where
-import Test.HUnit
-import Data.Hash.CRC32.Posix
-
-test_crc32 =
-    let f msg inp exp = TestLabel msg $ TestCase $ assertEqual "" exp (crc32 inp) in
-        [
-         f "Empty" "" 4294967295,
-         f "1" "1" 433426081,
-         f "some numbers" "153141341309874102987412" 2083856642,
-         f "Some text" "This is a test of the crc32 thing\n" 2449124888
-
-        ]
-
-tests = TestList [TestLabel "crc32" (TestList test_crc32)
-
-                 ]
-
diff --git a/testsrc/Eithertest.hs b/testsrc/Eithertest.hs
deleted file mode 100644
index 8a3d8f1..0000000
--- a/testsrc/Eithertest.hs
+++ /dev/null
@@ -1,48 +0,0 @@
-{- arch-tag: Data.Either.Utils tests
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module Eithertest(tests) where
-import Test.HUnit
-import Data.Either.Utils
-import Test.HUnit.Utils
-import Control.Exception
-
-test_maybeToEither =
-    let f msg inp exp = TestLabel msg $ TestCase $ assertEqual "" exp inp in
-        [
-         f "Nothing" (maybeToEither "error" (Nothing::Maybe String))
-           (Left "error"),
-         f "Nothing diff types" (maybeToEither "error" (Nothing::Maybe Int))
-           (Left "error"),
-         f "Just" (maybeToEither "error" (Just "good")) (Right "good"),
-         f "Diff types" (maybeToEither "error" (Just (5::Int))) 
-           (Right (5::Int))
-        ]
-
-test_forceEither =
-    let f msg inp exp = TestLabel msg $ TestCase $ assertEqual "" exp inp in
-    [
-     f "Right" (forceEither ((Right "foo")::Either Int String)) "foo",
-     TestLabel "Left" $ TestCase $ assertRaises "" (ErrorCall "\"wrong\"")
-           ("" @=? forceEither (Left "wrong"))
-    ]
-
-tests = TestList [TestLabel "test_maybeToEither" (TestList test_maybeToEither),
-                  TestLabel "test_forceEither" (TestList test_forceEither)
-                 ]
-
diff --git a/testsrc/GZiptest.hs b/testsrc/GZiptest.hs
deleted file mode 100644
index eabac89..0000000
--- a/testsrc/GZiptest.hs
+++ /dev/null
@@ -1,99 +0,0 @@
-{- arch-tag: Tests for GZip module
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module GZiptest(tests) where
-import Test.HUnit
-import System.FileArchive.GZip
-import System.FilePath
-import Data.Compression.Inflate
-import System.IO.Binary
-import System.IO
-import Data.Either.Utils
-import Data.List
-
-mf fn exp conf = TestLabel fn $ TestCase $
-                     do c <- readBinaryFile $
-                          joinPath ["testsrc", "gzfiles", fn]
-                        assertEqual "" exp (conf c)
-
-{-
-import System.FileArchive.GZip
-import System.IO
-import Data.Either.Utils
-
-main = do
-       c <- hGetContents stdin
-       let x = snd . forceEither . read_header $ c
-       putStr x
-
-test_bunches =
-    let f fn exp conv = mf fn exp (conv . snd . forceEither . read_header)
-        f2 c = let fn = "t/z" ++ (show c) ++ ".gz" in
-                   f fn c (length . inflate_string)
-        in
-        map f2 [0..1000]
--}
-test_inflate = 
-    let f fn exp conv = mf fn exp (conv . snd . forceEither . read_header) in
-        [
-         f "t1.gz" "Test 1" inflate_string
-        ,f "t1.gz" 6 (length . inflate_string)
-        ,f "t1.gz" ("Test 1",
-                    "\x19\xf8\x27\x99\x06\x00\x00\x00") inflate_string_remainder
-        ,f "empty.gz" "" inflate_string
-        --,f "zeros.gz" 10485760 (length . inflate_string)
-        -- BAD BAD ,f "zeros.gz" (replicate (10 * 1048576) '\0') inflate_string
-        -- This line tests Igloo's code:
-        --,f "zeros.gz" True (\x -> (replicate 10485760 '\0') == inflate_string x)
-        ]
-
-test_header =
-    let f fn exp = mf fn exp (fst . forceEither . read_header)
-        in
-        [
-         f "t1.gz" Header {method = 8, flags = 0, extra = Nothing,
-                            filename = Nothing, comment = Nothing,
-                          mtime = 1102111446, xfl = 2, os = 3}
-        ,f "empty.gz" Header {method = 8, flags = 8, extra = Nothing,
-                              filename = Just "empty", 
-                              comment = Nothing,
-                             mtime = 1102127257, xfl = 0, os = 3}
-        ]
-
-test_gunzip =
-    let f fn exp = mf fn exp decompress
-        in
-        [
-         f "t1.gz" ("Test 1", Nothing)
-        ,f "t1bad.gz" ("Test 1", Just CRCError)
-        ,f "t2.gz" ("Test 1Test 2", Nothing)
-        -- The following tests my code
-         {-
-        ,mf "zeros.gz" True (\x -> case decompress x of
-                             (y, _) -> y == replicate 10485760 '\0'
-                            )
-         -}
-        ]
-
-tests = TestList [TestLabel "inflate" (TestList test_inflate),
-                  TestLabel "header" (TestList test_header),
---                  TestLabel "bunches" (TestList test_bunches),
-                  TestLabel "gunzip" (TestList test_gunzip)
-
-                 ]
-
diff --git a/testsrc/Globtest.hs b/testsrc/Globtest.hs
deleted file mode 100644
index b77a0e1..0000000
--- a/testsrc/Globtest.hs
+++ /dev/null
@@ -1,113 +0,0 @@
-{- 
-Copyright (C) 2006 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-
-module Globtest(tests) where
-import Test.HUnit
-import System.Path.Glob
-import System.Path
-import Test.HUnit.Utils
-import System.IO.HVFS
-import System.Directory(createDirectory)
-#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
-import System.Posix.Directory hiding (createDirectory)
-import System.Posix.Files
-#endif
-import Control.Exception
-import Data.List
-
-bp = "testtmp"
-touch x = writeFile x ""
-
-globtest thetest = 
-    bracket_ (setupfs)
-             (recursiveRemove SystemFS bp)
-             thetest
-    where setupfs =
-              do mapM_ (\x -> createDirectory x)
-                       [bp, bp ++ "/a", bp ++ "/aab", bp ++ "/aaa",
-                        bp ++ "/ZZZ", bp ++ "/a/bcd",
-                        bp ++ "/a/bcd/efg"]
-                 mapM_ touch [bp ++ "/a/D", bp ++ "/aab/F", bp ++ "/aaa/zzzF",
-                              bp ++ "/a/bcd/EF", bp ++ "/a/bcd/efg/ha",
-                             bp ++ "/a/foo", bp ++ "/a/afoo",
-                             bp ++ "/a/a-foo", bp ++ "/a/a.foo"]
-#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
-                 createSymbolicLink (preppath "broken") (preppath "sym1")
-                 createSymbolicLink (preppath "broken") (preppath "sym2")
-#endif
-                 
-eq msg exp res =
-    assertEqual msg (sort exp) (sort res)
-mf msg func = TestLabel msg $ TestCase $ globtest func
-f func = TestCase $ globtest func
-preppath x = bp ++ "/" ++ x
-
-test_literal =
-    map f
-            [glob (preppath "a") >>= eq "" [preppath "a"]
-            ,glob (preppath "a/D") >>= eq "" [preppath "a/D"]
-            ,glob (preppath "aab") >>= eq "" [preppath "aab"]
-            ,glob (preppath "nonexistant") >>= eq "empty" []
-            ]
-
-test_one_dir =
-    map f
-        [glob (preppath "a*") >>= eq "a*" (map preppath ["a", "aab", "aaa"]),
-         glob (preppath "*a") >>= eq "*a" (map preppath ["a", "aaa"]),
-         glob (preppath "aa?") >>= eq "aa?" (map preppath ["aaa", "aab"]),
-         glob (preppath "aa[ab]") >>= eq "aa[ab]" (map preppath ["aaa", "aab"]),
-         glob (preppath "*q") >>= eq "*q" []
-        ]
-
-test_nested_dir =
-    map f
-        [glob (preppath "a/bcd/E*") >>= eq "a/bcd/E*" [preppath "a/bcd/EF"],
-         glob (preppath "a/bcd/*g") >>= eq "a/bcd/*g" [preppath "a/bcd/efg"],
-         glob (preppath "a/*.foo") >>= eq "a/*.foo" [preppath "a/a.foo"]
-        ]
-
-test_dirnames = 
-    map f
-        [glob (preppath "*/D") >>= eq "*/D" [preppath "a/D"],
-         glob (preppath "*/*a") >>= eq "*/*a" [],
-         glob (preppath "a/*/*/*a") >>= eq "a/*/*/*a" [preppath "a/bcd/efg/ha"],
-         glob (preppath "?a?/*F") >>= eq "?a?/*F" (map preppath ["aaa/zzzF", "aab/F"])
-        ]
-
-test_brokensymlinks =
-#if !(defined(mingw32_HOST_OS) || defined(mingw32_TARGET_OS) || defined(__MINGW32__))
-    map f
-        [glob (preppath "sym*") >>= eq "sym*" (map preppath ["sym1", "sym2"]),
-         glob (preppath "sym1") >>= eq "sym1" [preppath "sym1"],
-         glob (preppath "sym2") >>= eq "sym2" [preppath "sym2"]
-        ]
-#else
-    []
-#endif
-         
-
-tests = TestList [TestLabel "test_literal" (TestList test_literal),
-                  TestLabel "test_one_dir" (TestList test_one_dir),
-                  TestLabel "test_nested_dir" (TestList test_nested_dir),
-                  TestLabel "test_dirnames" (TestList test_dirnames),
-                  TestLabel "test_brokensymlinks" (TestList test_brokensymlinks)]
-
-
-
-
diff --git a/testsrc/HVFStest.hs b/testsrc/HVFStest.hs
deleted file mode 100644
index 289c32d..0000000
--- a/testsrc/HVFStest.hs
+++ /dev/null
@@ -1,126 +0,0 @@
-{- arch-tag: HVFS tests main file
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module HVFStest(tests) where
-import Test.HUnit
-import System.IO.HVIO
-import System.IO.HVFS
-import System.IO.HVFS.InstanceHelpers
-import System.IO.HVFS.Combinators
-import Test.HUnit.Utils
-import System.IO
-import System.IO.Error
-import Control.Exception
-
-ioeq :: (Show a, Eq a) => a -> IO a -> Assertion
-ioeq exp inp = do x <- inp
-                  exp @=? x
-
-testTree = [("test.txt", MemoryFile "line1\nline2\n"),
-            ("file2.txt", MemoryFile "line3\nline4\n"),
-            ("emptydir", MemoryDirectory []),
-            ("dir1", MemoryDirectory
-             [("file3.txt", MemoryFile "line5\n"),
-              ("test.txt", MemoryFile "subdir test"),
-              ("dir2", MemoryDirectory [])
-             ]
-            )
-           ]
-
-test_nice_slice =
-    let f exp fp = TestLabel fp $ TestCase $ exp @=? nice_slice fp
-        in [
-            f [] "/"
-           ,f ["foo", "bar"] "/foo/bar"
-           --,f [] "."
-           ]
-
-test_content = 
-    let f exp fp = TestLabel fp $ TestCase $
-                     do x <- newMemoryVFS testTree
-                        h <- vOpen x fp ReadMode
-                        case h of
-                           HVFSOpenEncap h2 -> exp `ioeq` vGetContents h2
-        in
-        [
-         f "line1\nline2\n" "test.txt",
-         f "line1\nline2\n" "/test.txt",
-         f "line5\n" "dir1/file3.txt",
-         f "subdir test" "/dir1/test.txt"
-        ]
-
-test_chroot =
-    let f msg testfunc = TestLabel msg $ TestCase $ 
-                         do x <- newMemoryVFS testTree
-                            vSetCurrentDirectory x "/emptydir"
-                            y <- newHVFSChroot x "/dir1"
-                            testfunc y
-        in
-        [
-         f "root" (\x -> ["file3.txt", "test.txt", "dir2"]
-                   `ioeq` vGetDirectoryContents x "/")
-        ,f "cwd" (\x -> "/" `ioeq` vGetCurrentDirectory x)
-        ,f "dir2" (\x -> [] `ioeq` vGetDirectoryContents x "/dir2")
-        ,f "dot" (\x -> ["file3.txt", "test.txt", "dir2"]
-                  `ioeq` vGetDirectoryContents x ".")
-        ,f "cwd tests" $
-          (\x -> do a <- vGetDirectoryContents x "/"
-                    ["file3.txt", "test.txt", "dir2"] @=? a
-                    vSetCurrentDirectory x "/dir2"
-                    cwd <- vGetCurrentDirectory x
-                    "/dir2" @=? cwd
-                    y <- vGetDirectoryContents x "."
-                    [] @=? y
-                    vSetCurrentDirectory x ".."
-                    "/" `ioeq` vGetCurrentDirectory x
-                    --vSetCurrentDirectory x ".."
-                    --"/" `ioeq` vGetCurrentDirectory x
-          )
-        --,f "test.txt" (\x -> "subdir test" `ioeq` 
-        --               (vOpen x "/test.txt" ReadMode >>= vGetContents))
-        ]
-
-
-test_structure =
-    let f msg testfunc = TestLabel msg $ TestCase $ do x <- newMemoryVFS testTree
-                                                       testfunc x
-        in
-        [
-         f "root" (\x -> ["test.txt", "file2.txt", "emptydir", "dir1"]
-                         `ioeq` vGetDirectoryContents x "/")
-        ,f "dot" (\x -> ["test.txt", "file2.txt", "emptydir", "dir1"]
-                  `ioeq` vGetDirectoryContents x ".")
-        ,f "dot2" (\x -> ["file3.txt", "test.txt", "dir2"]
-                   `ioeq` do vSetCurrentDirectory x "./dir1"
-                             vGetDirectoryContents x ".")
-        ,f "emptydir" (\x -> [] `ioeq` vGetDirectoryContents x "/emptydir")
-        ,f "dir1" (\x -> ["file3.txt", "test.txt", "dir2"] `ioeq`
-                   vGetDirectoryContents x "/dir1")
-        ,f "dir1/dir2" (\x -> [] `ioeq` vGetDirectoryContents x "/dir1/dir2")
-        ,f "relative tests" (\x -> 
-            do vSetCurrentDirectory x "dir1"
-               [] `ioeq` vGetDirectoryContents x "dir2"
-                            )
-        ]
-                            
-
-tests = TestList [TestLabel "nice_slice" (TestList test_nice_slice)
-                 ,TestLabel "structure" (TestList test_structure)
-                 ,TestLabel "content" (TestList test_content)
-                 ,TestLabel "chroot" (TestList test_chroot)
-                 ]
diff --git a/testsrc/HVIOtest.hs b/testsrc/HVIOtest.hs
deleted file mode 100644
index e9204e1..0000000
--- a/testsrc/HVIOtest.hs
+++ /dev/null
@@ -1,95 +0,0 @@
-{- arch-tag: HVIO tests main file
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module HVIOtest(tests) where
-import Test.HUnit
-import System.IO.HVIO
-import Test.HUnit.Utils
-import System.IO
-import System.IO.Error
-import Control.Exception
-
-ioeq :: (Show a, Eq a) => a -> IO a -> Assertion
-ioeq exp inp = do x <- inp
-                  exp @=? x
-
-test_MemoryBuffer =
-    let f inp testfunc = TestLabel inp $ TestCase $ do x <- newMemoryBuffer inp mbDefaultCloseFunc
-                                                       testfunc x
-        in
-        [
-         f "" (\x -> do True `ioeq` vIsOpen x
-                        assertRaises "eof error" (IOException $ mkIOError eofErrorType "" Nothing Nothing) (vGetChar x)
-                        vPutStrLn x "Line1"
-                        vPutStrLn x "Line2"
-                        vRewind x
-                        "Line1" `ioeq` vGetLine x
-                        "Line2" `ioeq` vGetLine x
-                        12 `ioeq` vTell x
-                        vSeek x AbsoluteSeek 1
-                        "ine1" `ioeq` vGetLine x
-                        vSeek x RelativeSeek (-3)
-                        "e1" `ioeq` vGetLine x
-                        vSeek x SeekFromEnd (-3)
-                        "e2" `ioeq` vGetLine x
-                        vSeek x AbsoluteSeek 1
-                        vPutStr x "IN"
-                        vRewind x
-                        "LINe1" `ioeq` vGetLine x
-                        "Line2" `ioeq` vGetLine x                        
-                        vSeek x SeekFromEnd 0
-                        vPutChar x 'c'
-                        assertRaises "eof error" (IOException $ mkIOError eofErrorType "" Nothing Nothing) (vGetLine x)
-                        vRewind x
-                        "LINe1\nLine2\nc" `ioeq` vGetContents x
-              )
-        ]
-
-test_StreamReader =
-    let f inp testfunc = TestLabel inp $ TestCase $ do x <- newStreamReader inp
-                                                       testfunc x
-        in 
-        [
-         f "" (\x -> do True `ioeq` vIsEOF x
-                        True `ioeq` vIsOpen x
-                        assertRaises "eof error" (IOException $ mkIOError eofErrorType "" Nothing Nothing) (vGetChar x)
-                        vClose x
-                        False `ioeq` vIsOpen x
-                        
-              )
-        ,f "abcd" (\x -> do False `ioeq` vIsEOF x
-                            True `ioeq` vIsOpen x
-                            'a' `ioeq` vGetChar x
-                            "bcd" `ioeq` vGetContents x
-                            vClose x
-               )
-        ,f "line1\nline2\n\n\nline5\nlastline"
-           (\x -> do False `ioeq` vIsEOF x
-                     "line1" `ioeq` vGetLine x
-                     "line2" `ioeq` vGetLine x
-                     "" `ioeq` vGetLine x
-                     "" `ioeq` vGetLine x
-                     "line5" `ioeq` vGetLine x
-                     "lastline" `ioeq` vGetLine x
-                     assertRaises "eof error" (IOException $ mkIOError eofErrorType "" Nothing Nothing) (vGetLine x)
-           )
-        ]
-
-tests = TestList [TestLabel "streamReader" (TestList test_StreamReader),
-                  TestLabel "MemoryBuffer" (TestList test_MemoryBuffer)
-                 ]
diff --git a/testsrc/IOtest.hs b/testsrc/IOtest.hs
deleted file mode 100644
index f4a55ba..0000000
--- a/testsrc/IOtest.hs
+++ /dev/null
@@ -1,28 +0,0 @@
-{- arch-tag: IO tests main file
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module IOtest() where
-import Test.HUnit
-import System.IO
-import Test.HUnit.Utils
-
-
-
-
-
-
diff --git a/testsrc/Listtest.hs b/testsrc/Listtest.hs
deleted file mode 100644
index ff829b1..0000000
--- a/testsrc/Listtest.hs
+++ /dev/null
@@ -1,256 +0,0 @@
-{- arch-tag: List tests main file
-Copyright (C) 2004-2005 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module Listtest(tests) where
-import Test.HUnit
-import Data.List.Utils
-import Data.List
-import Test.HUnit
-import Test.QuickCheck as QC
-import Test.HUnit.Utils
-
-test_delFromAL = 
-    let f :: [(String, Int)] -> [(String, Int)] -> Test
-        f inp exp = TestCase $ exp @=? (delFromAL inp "testkey") in
-        [
-                 f [] []
-                 ,f [("one", 1)] [("one", 1)]
-                 ,f [("1", 1), ("2", 2), ("testkey", 3)] [("1", 1), ("2", 2)]
-                 ,f [("testkey", 1)] []
-                 ,f [("testkey", 1), ("testkey", 2)] []
-                 ,f [("testkey", 1), ("2", 2), ("3", 3)] [("2", 2), ("3", 3)]
-                 ,f [("testkey", 1), ("2", 2), ("testkey", 3), ("4", 4)]
-                    [("2", 2), ("4", 4)]
-        ]
-
-test_addToAL =
-    let f :: [(String, Int)] -> [(String, Int)] -> Test
-        f inp exp = TestCase $ exp @=? (addToAL inp "testkey" 101) in
-        [
-         f [] [("testkey", 101)]
-        ,f [("testkey", 5)] [("testkey", 101)]
-        ,f [("testkey", 5), ("testkey", 6)] [("testkey", 101)]
-        ]
-
-test_split =
-    let f delim inp exp = TestCase $ exp @=? split delim inp in
-        [
-         f "," "foo,bar,,baz," ["foo", "bar", "", "baz", ""]
-        ,f "ba" ",foo,bar,,baz," [",foo,","r,,","z,"]
-        ,f "," "" []
-        ,f "," "," ["", ""]
-        ]
-
-test_join =
-    let f :: (Eq a, Show a) => [a] -> [[a]] -> [a] -> Test
-        f delim inp exp = TestCase $ exp @=? join delim inp in
-        [
-         f "|" ["foo", "bar", "baz"] "foo|bar|baz"
-        ,f "|" [] ""
-        ,f "|" ["foo"] "foo"
-         -- f 5 [[1, 2], [3, 4]] [1, 2, 5, 3, 4]
-        ]
-
-test_replace =
-    let f old new inp exp = TestCase $ exp @=? replace old new inp in
-        [
-         f "" "" "" ""
-        ,f "foo" "bar" "" ""
-        ,f "foo" "bar" "foo" "bar"
-        ,f "foo" "bar" "footestfoothisisabarfoo" "bartestbarthisisabarbar"
-        ,f "," ", " "1,2,3,4" "1, 2, 3, 4"
-        ,f "," "." "1,2,3,4" "1.2.3.4"
-        ]
-
-test_genericJoin =
-    let f delim inp exp = TestCase $ exp @=? genericJoin delim inp in
-        [
-         f ", " [1, 2, 3, 4] "1, 2, 3, 4"
-        ,f ", " ([] :: [Int]) ""
-        ,f "|" ["foo", "bar", "baz"] "\"foo\"|\"bar\"|\"baz\""
-        ,f ", " [5] "5"
-        ]
-
-test_flipAL =
-    let f inp exp = TestCase $ exp @=? flipAL inp in
-        [
-         f ([]::[(Int,Int)]) ([]::[(Int,[Int])])
-        ,f [("a", "b")] [("b", ["a"])]
-        ,f [("a", "b"),
-            ("c", "b"),
-            ("d", "e"),
-            ("b", "b")] [("b", ["b", "c", "a"]),
-                         ("e", ["d"])]
-        ]
-
-test_uniq =
-    let f inp exp = TestCase $ exp @=? uniq inp in
-    [f ([]::[Int]) [],
-     f "asdf" "asdf",
-     f "aabbcc" "abc",
-     f "abcabc" "abc",
-     f "aaaaaa" "a",
-     f "aaaaaab" "ab",
-     f "111111111111111" "1",
-     f "baaaaaaaaa" "ba",
-     f "baaaaaaaaab" "ba",
-     f "aaacccdbbbefff" "acdbef",
-     f "foo" "fo",
-     f "15553344409" "153409",
-     f "Mississippi" "Misp"]
-
-test_trunc =
-    let f len inp exp = TestCase $ exp @=? take len inp in
-        [
-         f 2 "Hello" "He"
-        ,f 1 "Hello" "H"
-        ,f 0 "Hello" ""
-        ,f 2 "H" "H"
-        ,f 2 "" ""
-        ,f 2 [1, 2, 3, 4, 5] [1, 2]
-        ,f 10 "Hello" "Hello"
-        ,f 0 "" ""
-        ]              
-
-test_contains =
-    let f msg sub testlist exp = TestCase $ assertEqual msg exp (contains sub testlist) in
-        [
-         f "t1" "Haskell" "I really like Haskell." True
-        ,f "t2" "" "Foo" True
-        ,f "t3" "" "" True
-        ,f "t4" "Hello" "" False
-        ,f "t5" "Haskell" "Haskell" True
-        ,f "t6" "Haskell" "1Haskell" True
-        ,f "t7" "Haskell" "Haskell1" True
-        ,f "t8" "Haskell" "Ocaml" False
-        ,f "t9" "Haskell" "OCamlasfasfasdfasfd" False
-        ,f "t10" "a" "Hello" False
-        ,f "t11" "e" "Hello" True
-        ]
-
-test_elemRIndex =
-    let f item inp exp = TestCase $ exp @=? elemRIndex item inp in
-        [
-         f "foo" [] Nothing
-        ,f "foo" ["bar", "baz"] Nothing
-        ,f "foo" ["foo"] (Just 0)
-        ,f "foo" ["foo", "bar"] (Just 0)
-        ,f "foo" ["bar", "foo"] (Just 1)
-        ,f "foo" ["foo", "bar", "foo", "bar", "foo"] (Just 4)
-        ,f 'f' ['f', 'b', 'f', 'f', 'b'] (Just 3)
-        ,f 'f' ['b', 'b', 'f'] (Just 2)
-        ]
-
-test_alwaysElemRIndex =
-    let f item inp exp = TestCase $ exp @=? alwaysElemRIndex item inp in
-        [
-         f "foo" [] (-1)
-        ,f 'f' ['b', 'q'] (-1)
-        ,f 'f' ['f', 'b', 'f', 'f', 'b'] 3
-        ]
-
-test_subIndex = 
-    let f item inp exp = TestCase $ exp @=? subIndex item inp in 
-        [f "foo" "asdfoobar" (Just 3)
-        ,f "foo" [] (Nothing)
-        ,f "" [] (Just 0)
-        ,f "" "asdf" (Just 0)
-        ,f "test" "asdftestbartest" (Just 4)
-        ,f [(1::Int), 2] [0, 5, 3, 2, 1, 2, 4] (Just 4)
-        ]
-
-test_fixedWidth =
-    let f inplen inplist exp = TestLabel ((show inplen) ++ ", " ++
-                                          (show inplist)) $ TestCase $
-                               wholeMap (fixedWidth inplen) inplist @=? exp in
-        [
-         f [] ([]::[Int]) ([]::[[Int]])
-        ,f [1] [5] [[5]]
-        ,f [1] [3, 4, 5, 6] [[3], [4, 5, 6]]
-        ,f [1] ([]::[Int]) ([]::[[Int]])
-        ,f [2] [3] [[3]]
-        ,f [2] [3, 4, 5, 6] [[3, 4], [5, 6]]
-        ,f [2] [3, 4, 5] [[3, 4], [5]]
-        ,f [1, 2, 3] "1234567890"  ["1","23","456","7890"]
-        ,f (repeat 2) "123456789" ["12","34","56","78","9"]
-        ,f [] "123456789" ["123456789"]
-        ,f [5, 3, 6, 1] "Hello, This is a test." 
-               ["Hello",", T","his is"," ","a test."]
-        ]
-
-test_strToAL =
-    let f inp exp = TestLabel (show inp) $ TestCase $ do let r = strFromAL inp
-                                                         exp @=? r
-                                                         inp @=? strToAL r
-        in
-        [
-         f ([]::[(String, String)]) ""
-        ,f [("foo", "bar")] "\"foo\",\"bar\"\n"
-        ,f [("foo", "bar"), ("baz", "quux")] "\"foo\",\"bar\"\n\"baz\",\"quux\"\n"
-        ,f [(1::Int, 2::Int), (3, 4)] "1,2\n3,4\n"
-        ,f [(1::Int, "one"), (2, "two")] "1,\"one\"\n2,\"two\"\n"
-        ,f [("one", 1::Double), ("n\nl", 2::Double)]
-           "\"one\",1.0\n\"n\\nl\",2.0\n"
-        ]
-
-test_spanList =
-    let f func inp exp = TestLabel (show inp) $ TestCase $ exp @=? spanList func inp
-        in
-          [f (contains "foo") "Testfoobar" ("Testf", "oobar"),
-           f (\_ -> True) "Testasdf" ("Testasdf", ""),
-           f (\_ -> False) "Testasdf" ("", "Testasdf"),
-           f (contains "foo") "" ("", ""),
-           f (contains "foo") "foo" ("f", "oo")]
-
-
-test_merge =
-    qctest "prop_merge" prop_merge
-
-prop_merge xs ys =
-    merge (sort xs) (sort ys) == sort (xs ++ ys)
-          where types = xs :: [Int]
-
-test_mergeBy =
-    qctest "test_mergeBy" prop_mergeBy
-
-prop_mergeBy xs ys =
-    mergeBy cmp (sortBy cmp xs) (sortBy cmp ys) == sortBy cmp (xs ++ ys)
-          where types = xs :: [Int]
-                cmp = compare
-
-tests = TestList [test_merge,
-                  test_mergeBy,
-                  TestLabel "delFromAL" (TestList test_delFromAL),
-                  TestLabel "uniq" (TestList test_uniq),
-                  TestLabel "addToAL" (TestList test_addToAL),
-                  TestLabel "split" (TestList test_split),
-                  TestLabel "join" (TestList test_join),
-                  TestLabel "genericJoin" (TestList test_genericJoin),
-                  TestLabel "trunc" (TestList test_trunc),
-                  TestLabel "flipAL" (TestList test_flipAL),
-                  TestLabel "elemRIndex" (TestList test_elemRIndex),
-                  TestLabel "alwaysElemRIndex" (TestList test_alwaysElemRIndex),
-                  TestLabel "replace" (TestList test_replace),
-                  TestLabel "contains" (TestList test_contains),
-                  TestLabel "strFromAL & strToAL" (TestList test_strToAL),
-                  TestLabel "fixedWidth" (TestList test_fixedWidth),
-                  TestLabel "subIndex" (TestList test_subIndex),
-                  TestLabel "spanList" (TestList test_spanList)]
-
-
-
diff --git a/testsrc/MIMETypestest.hs b/testsrc/MIMETypestest.hs
deleted file mode 100644
index be6416d..0000000
--- a/testsrc/MIMETypestest.hs
+++ /dev/null
@@ -1,75 +0,0 @@
-{- arch-tag: MIMETypes tests main file
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module MIMETypestest(tests) where
-import Test.HUnit
-import Data.List
-import Data.MIME.Types
-
-test_readMIMETypes =
-    let omtd = readMIMETypes defaultmtd True "testsrc/mime.types.test"
-        f = \strict inp exp -> TestCase $ do 
-                                          mtd <- omtd
-                                          exp @=? guessType mtd strict inp
-        fe = \strict inp exp -> TestCase $ do mtd <- omtd
-                                              (sort exp) @=? sort (guessAllExtensions mtd strict inp)
-        in [
-            f True "foo.bar.baz" (Nothing, Nothing)
-           ,f True "" (Nothing, Nothing)
-           ,f True "foo.ez" (Just "application/andrew-inset", Nothing)
-           ,fe True "application/andrew-inset" [".ez"]
-           ,f True "foo.dv" (Just "video/x-dv", Nothing)
-           ,fe True "video/x-dv" [".dif", ".dv"]
-           ,f True "test.h++" (Just "text/x-c++hdr", Nothing)
-           ,fe True "text/x-c++hdr" [".h++", ".hpp", ".hxx", ".hh"]
-           ,f True "foo.tgz" (Just "application/x-tar", Just "gzip")
-           ]
-
-
-test_guessAllExtensions =
-    let f strict inp exp = TestCase $ (sort exp) @=? sort (guessAllExtensions defaultmtd strict inp) in
-        [
-         f True "" []
-        ,f True "foo" []
-        ,f True "application/octet-stream" [".obj", ".so", ".bin", ".a", ".dll", ".exe", ".o"]
-        ,f True "text/plain" [".pl", ".ksh", ".bat", ".c", ".h", ".txt"]
-        ,f True "application/rtf" []
-        ,f False "application/rtf" [".rtf"]
-        ]
-
-test_guessType =
-    let f strict inp exp = TestCase $ exp @=? guessType defaultmtd strict inp in 
-         [
-            f True "" (Nothing, Nothing)
-           ,f True "foo" (Nothing, Nothing)
-           ,f True "foo.txt" (Just "text/plain", Nothing)
-           ,f True "foo.txt.gz" (Just "text/plain", Just "gzip")
-           ,f True "foo.txt.blah" (Nothing, Nothing)
-           ,f True "foo.tar" (Just "application/x-tar", Nothing)
-           ,f True "foo.tar.gz" (Just "application/x-tar", Just "gzip")
-           ,f True "foo.tgz" (Just "application/x-tar", Just "gzip")
-           ,f True "http://foo/test.dir/blah.rtf" (Nothing, Nothing)
-           ,f False "http://foo/test.dir/blah.rtf" (Just "application/rtf", Nothing)
-           ,f True "foo.pict" (Nothing, Nothing)
-           ,f False "foo.pict" (Just "image/pict", Nothing)
-           ]
-
-tests = TestList [TestLabel "guessType" (TestList test_guessType),
-                  TestLabel "guessAllExtensions" (TestList test_guessAllExtensions),
-                  TestLabel "readMIMETypes" (TestList test_readMIMETypes)
-                 ]
diff --git a/testsrc/Maptest.hs b/testsrc/Maptest.hs
deleted file mode 100644
index 4f102cf..0000000
--- a/testsrc/Maptest.hs
+++ /dev/null
@@ -1,47 +0,0 @@
-{-
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module Maptest(tests) where
-import Test.HUnit
-import Data.Map.Utils
-import Data.Map as M
-
-test_flipM =
-    let f inp exp = TestCase $ (M.fromList exp) @=? flipM (M.fromList inp) in
-        [
-         f ([]::[(Int,Int)]) ([]::[(Int,[Int])])
-        ,f [("a", "b")] [("b", ["a"])]
-        ,f [("a", "b"),
-            ("c", "b"),
-            ("d", "e"),
-            ("b", "b")] [("b", ["c", "b", "a"]),
-                         ("e", ["d"])]
-        ]
-
-test_flippedLookupM =
-    let f item inp exp = TestCase $ exp @=? flippedLookupM item (M.fromList inp) in
-        [
-         f 'a' ([]::[(Char, Char)]) []
-        ,f 'a' [("Test1", 'a'), ("Test2", 'b')] ["Test1"]
-        ,f 'a' [("Test1", 'b'), ("Test2", 'b')] []
-        ,f 'a' [("Test1", 'a'), ("Test2", 'a')] ["Test2", "Test1"]
-        ]
-
-tests = TestList [TestLabel "flipM" (TestList test_flipM),
-                  TestLabel "flippedLookupM" (TestList test_flippedLookupM)
-                 ]
diff --git a/testsrc/Pathtest.hs b/testsrc/Pathtest.hs
deleted file mode 100644
index 7da2aa3..0000000
--- a/testsrc/Pathtest.hs
+++ /dev/null
@@ -1,77 +0,0 @@
-{- arch-tag: Path tests main file
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module Pathtest(tests) where
-import Test.HUnit
-import System.Path
-
-test_absNormPath =
-    let f base p exp = TestLabel (show (base, p)) $ TestCase $ exp @=? absNormPath base p
-        f2 = f "/usr/1/2" in
-        [ 
-         f "/" "" (Just "/")
-        ,f "/usr/test" "" (Just "/usr/test")
-        ,f "/usr/test" ".." (Just "/usr")
-        ,f "/usr/1/2" "/foo/bar" (Just "/foo/bar")
-        ,f2 "jack/./.." (Just "/usr/1/2")
-        ,f2 "jack///../foo" (Just "/usr/1/2/foo")
-        ,f2 "../bar" (Just "/usr/1/bar")
-        ,f2 "../" (Just "/usr/1")
-        ,f2 "../.." (Just "/usr")
-        ,f2 "../../" (Just "/usr")
-        ,f2 "../../.." (Just "/")
-        ,f2 "../../../" (Just "/")
-        ,f2 "../../../.." Nothing
-        ]
-
-test_secureAbsNormPath =
-    let f base p exp = TestLabel (show (base, p)) $ TestCase $ exp @=? secureAbsNormPath base p
-        f2 = f "/usr/1/2" in
-        [ 
-         f "/" "" (Just "/")
-        ,f "/usr/test" "" (Just "/usr/test")
-        ,f "/usr/test" ".." Nothing
-        ,f "/usr/1/2" "/foo/bar" Nothing
-        ,f "/usr/1/2" "/usr/1/2" (Just "/usr/1/2")
-        ,f "/usr/1/2" "/usr/1/2/foo/bar" (Just "/usr/1/2/foo/bar")
-        ,f2 "jack/./.." (Just "/usr/1/2")
-        ,f2 "jack///../foo" (Just "/usr/1/2/foo")
-        ,f2 "../bar" Nothing
-        ,f2 "../" Nothing
-        ,f2 "../.." Nothing
-        ,f2 "../../" Nothing
-        ,f2 "../../.." Nothing
-        ,f2 "../../../" Nothing
-        ,f2 "../../../.." Nothing
-        ]
-
-test_splitExt =
-    let f inp exp = TestCase $ exp @=? splitExt inp in
-        [
-         f "" ("", "")
-        ,f "/usr/local" ("/usr/local", "")
-        ,f "../foo.txt" ("../foo", ".txt")
-        ,f "../bar.txt.gz" ("../bar.txt", ".gz")
-        ,f "foo.txt/bar" ("foo.txt/bar", "")
-        ,f "foo.txt/bar.bz" ("foo.txt/bar", ".bz")
-        ]
-
-tests = TestList [TestLabel "splitExt" (TestList test_splitExt)
-                 ,TestLabel "absNormPath" (TestList test_absNormPath)
-                 ,TestLabel "secureAbsNormPath" (TestList test_secureAbsNormPath)
-                 ]
diff --git a/testsrc/ProgressTrackertest.hs b/testsrc/ProgressTrackertest.hs
deleted file mode 100644
index 56157da..0000000
--- a/testsrc/ProgressTrackertest.hs
+++ /dev/null
@@ -1,144 +0,0 @@
-{- 
-Copyright (C) 2006 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module ProgressTrackertest(tests) where
-import Data.Progress.Tracker
-import Test.HUnit
-import Control.Concurrent.MVar
-
-setup =
-    do timem <- newMVar 0
-       let timesource = readMVar timem
-       po <- newProgress' (ProgressStatus 0 100 0 "" timesource) []
-       return (po, timem)
-
-settime timem newval = swapMVar timem newval >> return ()
-
-test_incrP = 
-    do (po, timem) <- setup
-       incrP po 5
-       withStatus po $ \s ->
-                  do assertEqual "completedUnits" 5 (completedUnits s)
-                     assertEqual "totalUnits" 100 (totalUnits s)
-       incrP po 95
-       withStatus po $ \s ->
-                  do assertEqual "completedUnits" 100 (completedUnits s)
-                     assertEqual "totalUnits" 100 (totalUnits s)
-       incrP po 5
-       withStatus po $ \s ->
-                  do assertEqual "completedUnits" 105 (completedUnits s)
-                     assertEqual "totalUnits" 105 (totalUnits s)
-       incrP' po 5
-       withStatus po $ \s ->
-                  do assertEqual "completedUnits" 110 (completedUnits s)
-                     assertEqual "totalUnits" 105 (totalUnits s)
-       incrTotal po 10
-       withStatus po $ \s ->
-                  do 110 @=? completedUnits s
-                     115 @=? totalUnits s
-
-test_setP =
-    do (po, timem) <- setup
-       setP po 5
-       withStatus po $ \s ->
-           do 5 @=? completedUnits s
-              100 @=? totalUnits s
-       setP po 100
-       withStatus po $ \s ->
-           do 100 @=? completedUnits s
-              100 @=? totalUnits s
-       setP po 105
-       withStatus po $ \s ->
-           do 105 @=? completedUnits s
-              105 @=? totalUnits s
-       setP' po 110
-       withStatus po $ \s ->
-           do 110 @=? completedUnits s
-              105 @=? totalUnits s
-       setTotal po 115
-       withStatus po $ \s ->
-           do 110 @=? completedUnits s
-              115 @=? totalUnits s
-
-test_speed =
-    do (po, timem) <- setup
-       getSpeed po >>= assertEqual "initial speed" 0
-       getETR po >>= assertEqual "initial ETR" 0
-       getETA po >>= assertEqual "initial ETA" 0
-
-       incrP po 10
-       getSpeed po >>= assertEqual "speed after incr" 0
-       getETR po >>= assertEqual "ETR after incr" 0
-       getETA po >>= assertEqual "ETA after incr" 0
-
-       settime timem 5
-       getSpeed po >>= assertEqual "first speed" 2.0
-       getETR po >>= assertEqual "first ETR" 45
-       getETA po >>= assertEqual "first ETA" 50
-
-       incrP po 90
-       getSpeed po >>= assertEqual "speed 2" 20.0
-       getETR po >>= assertEqual "etr 2" 0
-       getETA po >>= assertEqual "eta 2" 5
-
-       settime timem 400
-       setP po 90
-       getSpeed po >>= assertEqual "speed 3" 0.225
-       getETR po >>= assertEqual "etr 2" 44
-       getETA po >>= assertEqual "eta 2" 444
-
-test_callback =       
-    do (po, _) <- setup
-       mcounter <- newMVar (0::Int)
-       mcounter1 <- newMVar (0::Int)
-       mcounter2 <- newMVar (0::Int)
-       (po2, _) <- setup
-       (po3, _) <- setup
-       
-       addCallback po (minc mcounter)
-       addParent po po2
-       incrP po 5
-       readMVar mcounter >>= assertEqual "cb1" 1
-       withStatus po (\x -> 5 @=? completedUnits x)
-       withStatus po2 (\x -> do 5 @=? completedUnits x
-                                200 @=? totalUnits x)
-       
-       addCallback po2 (minc mcounter2)
-       incrP po 100
-       readMVar mcounter2 >>= (\x -> assertBool "cb2" (0 /= x))
-       withStatus po2 (\x -> do 105 @=? completedUnits x
-                                205 @=? totalUnits x)
-       
-       incrP' po 5
-       withStatus po2 (\x -> do 110 @=? completedUnits x
-                                205 @=? totalUnits x)
-
-       finishP po
-       withStatus po2 (\x -> do 110 @=? completedUnits x
-                                210 @=? totalUnits x)
-       
-       
-    where minc mv _ _ = modifyMVar_ mv (\x -> return $ x + 1)
-
-tests = TestList [TestLabel "incrP" (TestCase test_incrP),
-                  TestLabel "setP" (TestCase test_setP),
-                  TestLabel "speed" (TestCase test_speed),
-                  TestLabel "test_callback" (TestCase test_callback)]
-
-
-
diff --git a/testsrc/Str/CSVtest.hs b/testsrc/Str/CSVtest.hs
deleted file mode 100644
index af44d48..0000000
--- a/testsrc/Str/CSVtest.hs
+++ /dev/null
@@ -1,42 +0,0 @@
-{- arch-tag: CSV tests main file
-Copyright (C) 2005 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module Str.CSVtest(tests) where
-import Test.HUnit
-import Data.CSV
-import Text.ParserCombinators.Parsec
-
-test_csv =
-    let f inp exp = TestLabel inp $ TestCase $ 
-                    exp @=? case parse csvFile "" inp of
-                                  Right x -> Right x
-                                  Left y -> Left (show y)
-        in [
-        f "" (Right []),
-        f "\n" (Right [[""]]),
-        f "1,2,3\n" (Right [["1", "2", "3"]]),
-        f "This is a,Test,Really\n" (Right [["This is a", "Test", "Really"]]),
-        f "l1\nl2\n" (Right [["l1"], ["l2"]]),
-        f "NQ,\"Quoted\"\n" (Right [["NQ", "Quoted"]]),
-        f "1Q,\"\"\"\"\n" (Right [["1Q", "\""]]),
-        f ",\"\"\n" (Right [["", ""]]),
-        f "\"Embedded\"\"Quote\"\n" (Right [["Embedded\"Quote"]])
-        ]
-
-tests = TestList [TestLabel "csv" (TestList test_csv)]
-
diff --git a/testsrc/Strtest.hs b/testsrc/Strtest.hs
deleted file mode 100644
index 33f64fe..0000000
--- a/testsrc/Strtest.hs
+++ /dev/null
@@ -1,85 +0,0 @@
-{- arch-tag: Str tests main file
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module Strtest(tests) where
-import Test.HUnit
-import Data.String.Utils
-import Test.HUnit.Utils
-import Text.Regex
-import Data.Char
-
-test_lstrip =
-    mapassertEqual "lstrip" lstrip
-                       [("", ""),
-                        ("a", "a"),
-                        (" a ", "a "),
-                        ("  abas", "abas"),
-                        ("\n\t fdsa", "fdsa"),
-                        ("abc def", "abc def")]
-
-test_rstrip =
-    mapassertEqual "rstrip" rstrip
-                   [("", ""),
-                    ("a", "a"),
-                    (" a ", " a"),
-                    ("abas  ", "abas"),
-                    ("fdsa \n\t", "fdsa"),
-                    ("abc def", "abc def")]
-
-test_strip =
-    mapassertEqual "strip" strip
-                   [("", ""),
-                    ("a", "a"),
-                    (" a ", "a"),
-                    ("abas  ", "abas"),
-                    ("  abas", "abas"),
-                    ("asdf\n\t ", "asdf"),
-                    ("\nbas", "bas"),
-                    ("abc def", "abc def")]
-
-test_splitWs =
-    let f exp inp = TestCase $ exp @=? splitWs inp
-        in [
-            f [] "    ",
-            f [] "",
-            f ["asdf"] " asdf\n",
-            f ["one", "two", "three"] "  one\ntwo \tthree \n"
-           ]
-
-
-test_escapeRe =
-    map (\i -> TestLabel (show $ chr i) $ TestCase $ assertEqual [chr i] (Just []) 
-                (matchRegex (mkRegex $ escapeRe $ [chr i]) [chr i]))
-             [1..255]
-    ++
-    [TestCase $ assertEqual "big string" 
-                     (Just ([], teststr, [], []))
-                     (matchRegexAll (mkRegex $ escapeRe teststr) teststr)
-    ]
-    where teststr = map chr [1..255]
-
-tests = TestList [TestLabel "lstrip" (TestList test_lstrip),
-                  TestLabel "rstrip" $ TestList test_rstrip,
-                  TestLabel "strip" $ TestList test_strip,
-                  TestLabel "splitWs" $ TestList test_splitWs,
-                  TestLabel "escapeRe" $ TestList test_escapeRe
-                  ]
-
-
-
-
diff --git a/testsrc/Tests.hs b/testsrc/Tests.hs
deleted file mode 100644
index 039a0c0..0000000
--- a/testsrc/Tests.hs
+++ /dev/null
@@ -1,61 +0,0 @@
-{- arch-tag: Tests main file
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module Tests(tests) where
-import Test.HUnit
-import qualified MIMETypestest
-import qualified Listtest
-import qualified Maptest
-import qualified Pathtest
-import qualified Strtest
-import qualified IOtest
-import qualified Bitstest
-import qualified Eithertest
-import qualified CRC32POSIXtest
-import qualified CRC32GZIPtest
-import qualified GZiptest
-import qualified HVIOtest
-import qualified HVFStest
-import qualified Timetest
-import qualified Str.CSVtest
-import qualified WildMatchtest
-import qualified Globtest
-import qualified ProgressTrackertest
-
-test1 = TestCase ("x" @=? "x")
-
-tests = TestList [TestLabel "test1" test1,
-                 TestLabel "List" Listtest.tests,
-                 TestLabel "Str" Strtest.tests,
-                 TestLabel "CSV" Str.CSVtest.tests,
-                 TestLabel "Time" Timetest.tests,
-                 TestLabel "Map" Maptest.tests,
-                 TestLabel "ProgressTracker" ProgressTrackertest.tests,
-                 TestLabel "Path" Pathtest.tests,
-                 TestLabel "WildMatch" WildMatchtest.tests,
-                 TestLabel "HVIO" HVIOtest.tests,
-                 TestLabel "HVFS" HVFStest.tests,
-                 TestLabel "Glob" Globtest.tests,
-                 TestLabel "MIMETypes" MIMETypestest.tests,
-                 TestLabel "Bitstest" Bitstest.tests,
-                 TestLabel "Eithertest" Eithertest.tests,
-                 TestLabel "CRC32POSIXtest" CRC32POSIXtest.tests,
-                 TestLabel "CRC32GZIPtest" CRC32GZIPtest.tests,
-                 TestLabel "GZiptest" GZiptest.tests]
-
-
diff --git a/testsrc/Timetest.hs b/testsrc/Timetest.hs
deleted file mode 100644
index 7f5c993..0000000
--- a/testsrc/Timetest.hs
+++ /dev/null
@@ -1,54 +0,0 @@
-{- arch-tag: Time tests main file
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module Timetest(tests) where
-import Test.HUnit
-import System.Time.Utils
-import System.Time
-
-base =CalendarTime {ctYear = 2005, ctMonth = January, ctDay = 21,
-                          ctHour = 1, ctMin = 1, ctSec = 20,
-                          ctPicosec = 0, ctWDay = Sunday, ctYDay = 0,
-                          ctTZName = "", ctTZ = 0, ctIsDST = False}
-test_ctu2e =
-    let f base exp = TestLabel (show base) $ TestCase $ exp @=? timegm base in
-        [
-         f (base {ctYear = 2005, ctMonth = January, ctDay = 21,
-                          ctHour = 1, ctMin = 1, ctSec = 20})
-           1106269280
-           
-         ,f (base {ctYear = 2004, ctMonth = July, ctDay = 1,
-                           ctHour = 17, ctMin = 0, ctSec = 0})
-           1088701200
-
-        ]
-
-test_ct2e =
-    let f base exp = TestLabel (show base) $ TestCase $ 
-                       do r <- timelocal base
-                          exp @=? r in
-        [
-         f (base {ctYear = 2005, ctMonth = January, ctDay = 20,
-                          ctHour = 19, ctMin = 1, ctSec = 20})
-           1106269280
-        ,f (base {ctYear = 2004, ctMonth = July, ctDay = 1,
-                           ctHour = 12, ctMin = 0, ctSec = 0})
-           1088701200
-        ]
-
-tests = TestList [TestLabel "ctu2e" (TestList test_ctu2e)]
diff --git a/testsrc/WildMatchtest.hs b/testsrc/WildMatchtest.hs
deleted file mode 100644
index 034c3fa..0000000
--- a/testsrc/WildMatchtest.hs
+++ /dev/null
@@ -1,52 +0,0 @@
-{- 
-Copyright (C) 2006 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-
-module WildMatchtest(tests) where
-import Test.HUnit
-import System.Path.WildMatch
-import Test.HUnit.Utils
-
-test_wildCheckCase =
-    let f patt name = TestCase $ assertBool (patt ++ "," ++ name ++ " was false")
-                      (wildCheckCase patt name)
-        f0 patt name = TestCase $ assertBool (patt ++ "," ++ name ++ " was true")
-                       (not $ wildCheckCase patt name)
-    in
-    [f "asdf" "asdf",
-     f "?*?" "abc",
-     f "???*" "asd",
-     f "*???" "asd",
-     f "???" "asd",
-     f "*" "asd",
-     f "ab[cd]" "abc",
-     f "ab[!de]" "abc",
-     f0 "ab[de]" "abc",
-     f0 "??" "a",
-     f0 "a" "b",
-     f "[\\]" "\\",
-     f "[!\\]" "a",
-     f0 "[!\\]" "\\",
-     f0 "*.deb" "thedebianthing",
-     f0 "a/*.foo" "testtmp/a/D"]
-     
-tests = TestList [TestLabel "wildCheckCase" (TestList test_wildCheckCase)]
-
-
-
-
diff --git a/testsrc/gzfiles/empty.gz b/testsrc/gzfiles/empty.gz
deleted file mode 100644
index 0782b98..0000000
Binary files a/testsrc/gzfiles/empty.gz and /dev/null differ
diff --git a/testsrc/gzfiles/t1.gz b/testsrc/gzfiles/t1.gz
deleted file mode 100644
index a89fb00..0000000
Binary files a/testsrc/gzfiles/t1.gz and /dev/null differ
diff --git a/testsrc/gzfiles/t1bad.gz b/testsrc/gzfiles/t1bad.gz
deleted file mode 100644
index b8bdf66..0000000
Binary files a/testsrc/gzfiles/t1bad.gz and /dev/null differ
diff --git a/testsrc/gzfiles/t2.gz b/testsrc/gzfiles/t2.gz
deleted file mode 100644
index 403eaa7..0000000
Binary files a/testsrc/gzfiles/t2.gz and /dev/null differ
diff --git a/testsrc/gzfiles/zeros.gz b/testsrc/gzfiles/zeros.gz
deleted file mode 100644
index 44f8f1f..0000000
Binary files a/testsrc/gzfiles/zeros.gz and /dev/null differ
diff --git a/testsrc/mime.types.test b/testsrc/mime.types.test
deleted file mode 100644
index 0577a55..0000000
--- a/testsrc/mime.types.test
+++ /dev/null
@@ -1,24 +0,0 @@
-# arch-tag: test file for MIMETypes
-# Here are some comments
-#
-##
-
-# and some fun blank lines
-
-     
-
-# Some types with nothing
-
-application/activemessage
-application/applefile   
-application/atomicmail         # comment here
-
-# Some lines with real stuff
-
-application/andrew-inset       ez     # blah
-
-# Some lines with multiple things
-
-video/x-dv                                      dif dv
-text/x-c++hdr                                   h++ hpp hxx hh # foo
-
diff --git a/testsrc/runtests.hs b/testsrc/runtests.hs
deleted file mode 100644
index 68700ca..0000000
--- a/testsrc/runtests.hs
+++ /dev/null
@@ -1,25 +0,0 @@
-{- arch-tag: Test runner
-Copyright (C) 2004 John Goerzen <jgoerzen at complete.org>
-
-This program is free software; you can redistribute it and/or modify
-it under the terms of the GNU General Public License as published by
-the Free Software Foundation; either version 2 of the License, or
-(at your option) any later version.
-
-This program is distributed in the hope that it will be useful,
-but WITHOUT ANY WARRANTY; without even the implied warranty of
-MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
-GNU General Public License for more details.
-
-You should have received a copy of the GNU General Public License
-along with this program; if not, write to the Free Software
-Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
--}
-
-module Main where 
-
-import Test.HUnit
-import Tests
-
-main = runTestTT tests
-

-- 
haskell-testpack



More information about the Pkg-haskell-commits mailing list