Add function for generating arbitrary non-negative numbers
[ganeti-local] / test / hs / Test / Ganeti / TestCommon.hs
index 72ae311..09785f9 100644 (file)
@@ -4,7 +4,7 @@
 
 {-
 
-Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
+Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
 
 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
@@ -23,12 +23,53 @@ Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
 
 -}
 
-module Test.Ganeti.TestCommon where
+module Test.Ganeti.TestCommon
+  ( maxMem
+  , maxDsk
+  , maxCpu
+  , maxVcpuRatio
+  , maxSpindleRatio
+  , maxNodes
+  , maxOpCodes
+  , (==?)
+  , (/=?)
+  , failTest
+  , passTest
+  , pythonCmd
+  , runPython
+  , checkPythonResult
+  , DNSChar(..)
+  , genName
+  , genFQDN
+  , genMaybe
+  , genTags
+  , genFields
+  , genUniquesList
+  , SmallRatio(..)
+  , genSetHelper
+  , genSet
+  , genIp4AddrStr
+  , genIp4Addr
+  , genIp4NetWithNetmask
+  , genIp4Net
+  , genIp6Addr
+  , genIp6Net
+  , netmask2NumHosts
+  , testSerialisation
+  , resultProp
+  , readTestData
+  , genSample
+  , testParser
+  , genNonNegative
+  ) where
 
 import Control.Applicative
 import Control.Exception (catchJust)
 import Control.Monad
+import Data.Attoparsec.Text (Parser, parseOnly)
 import Data.List
+import Data.Text (pack)
+import Data.Word
 import qualified Data.Set as Set
 import System.Environment (getEnv)
 import System.Exit (ExitCode(..))
@@ -244,7 +285,7 @@ genIp4Net = do
 
 -- | Helper function to compute the number of hosts in a network
 -- given the netmask. (For IPv4 only.)
-netmask2NumHosts :: Int -> Int
+netmask2NumHosts :: Word8 -> Int
 netmask2NumHosts n = 2^(32-n)
 
 -- | Generates an arbitrary IPv6 network address in textual form.
@@ -289,14 +330,30 @@ testDataFilename datadir name = do
         src <- getSourceDir
         return $ src ++ datadir ++ name
 
--- | Returns the content of the specified python test data file.
-readPythonTestData :: String -> IO String
-readPythonTestData filename = do
-    name <- testDataFilename "/test/data/" filename
-    readFile name
-
 -- | Returns the content of the specified haskell test data file.
 readTestData :: String -> IO String
 readTestData filename = do
-    name <- testDataFilename "/test/data/htools/" filename
+    name <- testDataFilename "/test/data/" filename
     readFile name
+
+-- | Generate arbitrary values in the IO monad. This is a simple
+-- wrapper over 'sample''.
+genSample :: Gen a -> IO a
+genSample gen = do
+  values <- sample' gen
+  case values of
+    [] -> error "sample' returned an empty list of values??"
+    x:_ -> return x
+
+-- | Function for testing whether a file is parsed correctly.
+testParser :: (Show a, Eq a) => Parser a -> String -> a -> HUnit.Assertion
+testParser parser fileName expectedContent = do
+  fileContent <- readTestData fileName
+  case parseOnly parser $ pack fileContent of
+    Left msg -> HUnit.assertFailure $ "Parsing failed: " ++ msg
+    Right obtained -> HUnit.assertEqual fileName expectedContent obtained
+
+-- | Generate an arbitrary non negative integer number
+genNonNegative :: Gen Int
+genNonNegative =
+  fmap fromIntegral (arbitrary::Gen (Test.QuickCheck.NonNegative Int))