]> git.rkrishnan.org Git - tahoe-lafs/zfec.git/commitdiff
Update README.txt with details on Haskell testing/documentation etc
authoragl <agl@imperialviolet.org>
Sun, 20 Jan 2008 19:33:57 +0000 (01:03 +0530)
committeragl <agl@imperialviolet.org>
Sun, 20 Jan 2008 19:33:57 +0000 (01:03 +0530)
darcs-hash:6e1ebc9c4af1cdb252325b9353a35d20d2e02185

zfec/README.txt
zfec/haskell/FECTest.hs [deleted file]
zfec/haskell/test/FECTest.hs [new file with mode: 0644]

index 6e4ed973144d76c94c8f01a8d51f05a0135e1e4c..e563ab6062218c163afaeac100470dfbbd2a3105 100644 (file)
@@ -40,7 +40,13 @@ Python installed, you can run "trial zfec" for nicer output and test options.)
 This will run the tests of the C API, the Python API, and the command-line
 tools.
 
-To run the tests of the Haskell API, do XYZ.
+To run the tests of the Haskell API:
+  % runhaskell haskell/test/FECTest.hs
+
+Note that you must have installed the library first in order for this to work
+due to the fact that the interpreter cannot process FEC.hs as it takes a
+reference to an FFI function.
+
 
 
  * Community
@@ -205,7 +211,8 @@ objects (e.g. Python strings) to hold the data that you pass to zfec.
 
  ** Haskell API
 
-XYZ
+The Haskell code is fully Haddocked, to generate the documentation, run
+  % runhaskell Setup.lhs haddock
 
 
  * Utilities
@@ -219,7 +226,7 @@ command-line tools from the bin/ directory.
 
 A C compiler is required.  To use the Python API or the command-line tools a
 Python interpreter is also required.  We have tested it with Python v2.4 and
-v2.5.  For the Haskell interface, a Haskell compiler is required XYZ.
+v2.5.  For the Haskell interface, GHC >= 6.8.1 is required.
 
 
  * Acknowledgements
diff --git a/zfec/haskell/FECTest.hs b/zfec/haskell/FECTest.hs
deleted file mode 100644 (file)
index 0f5a353..0000000
+++ /dev/null
@@ -1,57 +0,0 @@
-module Main where
-
-import qualified Data.ByteString as B
-import qualified Codec.FEC as FEC
-import System.IO (withFile, IOMode(..))
-import System.Random
-import Data.List (sortBy)
-
-import Test.QuickCheck
-
--- | Return true if the given @k@ and @n@ values are valid
-isValidConfig :: Int -> Int -> Bool
-isValidConfig k n
-  | k >= n = False
-  | k < 1 = False
-  | n < 1 = False
-  | otherwise = True
-
-randomTake :: Int -> Int -> [a] -> [a]
-randomTake seed n values = map snd $ take n sortedValues where
-  sortedValues = sortBy (\a b -> compare (fst a) (fst b)) taggedValues
-  taggedValues = zip rnds values
-  rnds :: [Float]
-  rnds = randoms gen
-  gen = mkStdGen seed
-
-testFEC k n len seed = FEC.decode fec someTaggedBlocks == origBlocks where
-  origBlocks = map (\i -> B.replicate len $ fromIntegral i) [0..(k - 1)]
-  fec = FEC.fec k n
-  secondaryBlocks = FEC.encode fec origBlocks
-  taggedBlocks = zip [0..] (origBlocks ++ secondaryBlocks)
-  someTaggedBlocks = randomTake seed k taggedBlocks
-
-prop_FEC :: Int -> Int -> Int -> Int -> Property
-prop_FEC k n len seed =
-  isValidConfig k n && n < 256 && len < 1024 ==> testFEC k n len seed
-
-checkDivide :: Int -> IO ()
-checkDivide n = do
-  let input = B.replicate 1024 65
-  parts <- FEC.secureDivide n input
-  if FEC.secureCombine parts == input
-     then return ()
-     else fail "checkDivide failed"
-
-checkEnFEC :: Int -> IO ()
-checkEnFEC len = do
-  testdata <- withFile "/dev/urandom" ReadMode (\handle -> B.hGet handle len)
-  let [a, b, c, d, e] = FEC.enFEC 3 5 testdata
-  if FEC.deFEC 3 5 [b, e, d] == testdata
-     then return ()
-     else fail "deFEC failure"
-
-main = do
-  mapM_ (check (defaultConfig { configMaxTest = 1000, configMaxFail = 10000 })) [prop_FEC]
-  mapM_ checkDivide [1, 2, 3, 4, 10]
-  mapM_ checkEnFEC [1, 2, 3, 4, 5, 1024 * 1024]
diff --git a/zfec/haskell/test/FECTest.hs b/zfec/haskell/test/FECTest.hs
new file mode 100644 (file)
index 0000000..0f5a353
--- /dev/null
@@ -0,0 +1,57 @@
+module Main where
+
+import qualified Data.ByteString as B
+import qualified Codec.FEC as FEC
+import System.IO (withFile, IOMode(..))
+import System.Random
+import Data.List (sortBy)
+
+import Test.QuickCheck
+
+-- | Return true if the given @k@ and @n@ values are valid
+isValidConfig :: Int -> Int -> Bool
+isValidConfig k n
+  | k >= n = False
+  | k < 1 = False
+  | n < 1 = False
+  | otherwise = True
+
+randomTake :: Int -> Int -> [a] -> [a]
+randomTake seed n values = map snd $ take n sortedValues where
+  sortedValues = sortBy (\a b -> compare (fst a) (fst b)) taggedValues
+  taggedValues = zip rnds values
+  rnds :: [Float]
+  rnds = randoms gen
+  gen = mkStdGen seed
+
+testFEC k n len seed = FEC.decode fec someTaggedBlocks == origBlocks where
+  origBlocks = map (\i -> B.replicate len $ fromIntegral i) [0..(k - 1)]
+  fec = FEC.fec k n
+  secondaryBlocks = FEC.encode fec origBlocks
+  taggedBlocks = zip [0..] (origBlocks ++ secondaryBlocks)
+  someTaggedBlocks = randomTake seed k taggedBlocks
+
+prop_FEC :: Int -> Int -> Int -> Int -> Property
+prop_FEC k n len seed =
+  isValidConfig k n && n < 256 && len < 1024 ==> testFEC k n len seed
+
+checkDivide :: Int -> IO ()
+checkDivide n = do
+  let input = B.replicate 1024 65
+  parts <- FEC.secureDivide n input
+  if FEC.secureCombine parts == input
+     then return ()
+     else fail "checkDivide failed"
+
+checkEnFEC :: Int -> IO ()
+checkEnFEC len = do
+  testdata <- withFile "/dev/urandom" ReadMode (\handle -> B.hGet handle len)
+  let [a, b, c, d, e] = FEC.enFEC 3 5 testdata
+  if FEC.deFEC 3 5 [b, e, d] == testdata
+     then return ()
+     else fail "deFEC failure"
+
+main = do
+  mapM_ (check (defaultConfig { configMaxTest = 1000, configMaxFail = 10000 })) [prop_FEC]
+  mapM_ checkDivide [1, 2, 3, 4, 10]
+  mapM_ checkEnFEC [1, 2, 3, 4, 5, 1024 * 1024]