summaryrefslogtreecommitdiff
path: root/ghc/lib/misc/tests
diff options
context:
space:
mode:
authorsimonm <unknown>1998-02-02 17:35:59 +0000
committersimonm <unknown>1998-02-02 17:35:59 +0000
commit28139aea50376444d56f43f0914291348a51a7e7 (patch)
tree595c378188638ef16462972c1e7fcdb8409c7f16 /ghc/lib/misc/tests
parent98a1ebecb6d22d793b1d9f8e1d24ecbb5a2d130f (diff)
downloadhaskell-28139aea50376444d56f43f0914291348a51a7e7.tar.gz
[project @ 1998-02-02 17:27:26 by simonm]
Library re-organisation: All libraries now live under ghc/lib, which has the following structure: ghc/lib/std -- all prelude files (libHS.a) ghc/lib/std/cbits ghc/lib/exts -- standard Hugs/GHC extensions (libHSexts.a) -- available with '-fglasgow-exts' ghc/lib/posix -- POSIX library (libHSposix.a) ghc/lib/posix/cbits -- available with '-syslib posix' ghc/lib/misc -- used to be hslibs/ghc (libHSmisc.a) ghc/lib/misc/cbits -- available with '-syslib misc' ghc/lib/concurrent -- Concurrent libraries (libHSconc.a) -- available with '-concurrent' Also, several non-standard prelude modules had their names changed to begin with 'Prel' to reduce namespace pollution. Addr ==> PrelAddr (Addr interface available in 'exts') ArrBase ==> PrelArr CCall ==> PrelCCall (CCall interface available in 'exts') ConcBase ==> PrelConc GHCerr ==> PrelErr Foreign ==> PrelForeign (Foreign interface available in 'exts') GHC ==> PrelGHC IOHandle ==> PrelHandle IOBase ==> PrelIOBase GHCmain ==> PrelMain STBase ==> PrelST Unsafe ==> PrelUnsafe UnsafeST ==> PrelUnsafeST
Diffstat (limited to 'ghc/lib/misc/tests')
-rw-r--r--ghc/lib/misc/tests/finite-maps/Main.hs77
-rw-r--r--ghc/lib/misc/tests/finite-maps/Makefile5
-rw-r--r--ghc/lib/misc/tests/finite-maps/ghclib001.stdin2
-rw-r--r--ghc/lib/misc/tests/finite-maps/ghclib001.stdout11
4 files changed, 95 insertions, 0 deletions
diff --git a/ghc/lib/misc/tests/finite-maps/Main.hs b/ghc/lib/misc/tests/finite-maps/Main.hs
new file mode 100644
index 0000000000..b5ceae4f31
--- /dev/null
+++ b/ghc/lib/misc/tests/finite-maps/Main.hs
@@ -0,0 +1,77 @@
+-- Test module for Finite Maps
+
+module Main where
+
+import IO
+import FiniteMap
+import Util
+
+main = hGetContents stdin >>= \ input ->
+ let (s1, rest1) = rd_int input
+ r1 = test1 s1
+
+ (s2, rest2) = rd_int rest1
+ r2 = test2 s2
+ in
+ putStr r1 >>
+ putStr r2
+
+rd_int = \ i -> (head (reads i)) :: (Int,String)
+
+
+-------------------------------------------------------------
+--Test 1 creates two big maps with the same domain, mapping
+--each domain elt to 1.
+
+test1 :: Int -- Size of maps
+ -> String
+
+test1 size
+ = "Test 1" ++ "\n" ++
+ "N = " ++ show size ++ "\n" ++
+ "Tot sum = " ++
+-- show (fmToList fm1) ++ show (fmToList fm2) ++ show (fmToList sum_fm) ++
+ show tot_sum ++ "\n" ++
+ "Differences: " ++ diff ++ "\n" ++
+ "Sum intersection:" ++ show sum_int ++ "\n\n"
+ where
+ fm1,fm2 :: FiniteMap Int Int
+ fm1 = listToFM [(i,1) | i <- [1..size-1]]
+ fm2 = listToFM [(i,1) | i <- [size,size-1..2]]
+
+ -- Take their sum
+ sum_fm = plusFM_C (+) fm1 fm2
+ tot_sum = sum (map get [1..size])
+ get n = lookupWithDefaultFM sum_fm (error ("lookup" ++ show n)) n
+ -- Should be 1 + (size-2)*2 + 1 = 2*size - 2
+
+
+ -- Take their difference
+ diff_fm1 = fm1 `minusFM` fm2 -- Should be a singleton
+ diff_fm2 = fm2 `minusFM` fm1 -- Should be a singleton
+ diff = show (fmToList diff_fm1) ++ "; " ++ show (fmToList diff_fm2)
+
+ -- Take their intersection
+ int_fm = intersectFM_C (+) fm1 fm2
+ sum_int = foldFM (\k n tot -> n+tot) 0 int_fm
+
+
+test2 :: Int -- No of maps
+ -> String
+
+test2 size
+ = "Test 2" ++ "\n" ++
+ "N = " ++ show size ++ "\n" ++
+ "Sizes =" ++ show [sizeFM fm1,sizeFM fm2] ++ "\n" ++
+ "Sums = " ++ show [sum1,sum2] ++ "\n\n"
+ where
+ fm1,fm2 :: FiniteMap Int Int
+
+ fms1 = [unitFM i 1 | i <- [1..size]]
+ fm1 = foldr (plusFM_C (+)) emptyFM fms1
+
+ fms2 = [unitFM 1 i | i <- [1..size]]
+ fm2 = foldr (plusFM_C (+)) emptyFM fms2
+
+ sum1 = foldr (+) 0 (eltsFM fm1)
+ sum2 = foldr (+) 0 (eltsFM fm2)
diff --git a/ghc/lib/misc/tests/finite-maps/Makefile b/ghc/lib/misc/tests/finite-maps/Makefile
new file mode 100644
index 0000000000..05055dd2b5
--- /dev/null
+++ b/ghc/lib/misc/tests/finite-maps/Makefile
@@ -0,0 +1,5 @@
+TOP = ../../..
+include $(TOP)/mk/boilerplate.mk
+SRC_HC_OPTS += -syslib ghc
+SRC_RUNTEST_OPTS += +RTS -H25m -RTS
+include $(TOP)/mk/target.mk
diff --git a/ghc/lib/misc/tests/finite-maps/ghclib001.stdin b/ghc/lib/misc/tests/finite-maps/ghclib001.stdin
new file mode 100644
index 0000000000..628db6e8a5
--- /dev/null
+++ b/ghc/lib/misc/tests/finite-maps/ghclib001.stdin
@@ -0,0 +1,2 @@
+13133
+9798
diff --git a/ghc/lib/misc/tests/finite-maps/ghclib001.stdout b/ghc/lib/misc/tests/finite-maps/ghclib001.stdout
new file mode 100644
index 0000000000..e989373e1e
--- /dev/null
+++ b/ghc/lib/misc/tests/finite-maps/ghclib001.stdout
@@ -0,0 +1,11 @@
+Test 1
+N = 13133
+Tot sum = 26264
+Differences: [(1, 1)]; [(13133, 1)]
+Sum intersection:26262
+
+Test 2
+N = 9798
+Sizes =[9798, 1]
+Sums = [9798, 48005301]
+