Silence erroneous hlint warning
[ganeti-local] / htest / Test / Ganeti / Utils.hs
index 5aae3ac..23fe93b 100644 (file)
@@ -1,4 +1,4 @@
-{-# LANGUAGE TemplateHaskell #-}
+{-# LANGUAGE TemplateHaskell, CPP #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
 
 {-| Unittests for ganeti-htools.
@@ -31,13 +31,18 @@ module Test.Ganeti.Utils (testUtils) where
 import Test.QuickCheck hiding (Result)
 import Test.HUnit
 
+import Data.Char (isSpace)
 import Data.List
 import qualified Text.JSON as J
+#ifndef NO_REGEX_PCRE
+import Text.Regex.PCRE
+#endif
 
 import Test.Ganeti.TestHelper
 import Test.Ganeti.TestCommon
 
 import Ganeti.BasicTypes
+import qualified Ganeti.Constants as C
 import qualified Ganeti.JSON as JSON
 import Ganeti.Utils
 
@@ -161,7 +166,7 @@ case_niceSort_static = do
 -- itself, etc.).
 prop_niceSort_single :: Property
 prop_niceSort_single =
-  forAll getName $ \name ->
+  forAll genName $ \name ->
   conjoin
   [ printTestCase "single string" $ [name] ==? niceSort [name]
   , printTestCase "single plus empty" $ ["", name] ==? niceSort [name, ""]
@@ -202,6 +207,32 @@ prop_niceSortKey_equiv =
                                                     zip numbers names)
   ]
 
+-- | Tests 'rstripSpace'.
+prop_rStripSpace :: NonEmptyList Char -> Property
+prop_rStripSpace (NonEmpty str) =
+  forAll (resize 50 $ listOf1 (arbitrary `suchThat` isSpace)) $ \whitespace ->
+  conjoin [ printTestCase "arb. string last char is not space" $
+              case rStripSpace str of
+                [] -> True
+                xs -> not . isSpace $ last xs
+          , printTestCase "whitespace suffix is stripped" $
+              rStripSpace str ==? rStripSpace (str ++ whitespace)
+          , printTestCase "whitespace reduced to null" $
+              rStripSpace whitespace ==? ""
+          , printTestCase "idempotent on empty strings" $
+              rStripSpace "" ==? ""
+          ]
+
+#ifndef NO_REGEX_PCRE
+{-# ANN case_new_uuid "HLint: ignore Use camelCase" #-}
+
+-- | Tests that the newUUID function produces valid UUIDs.
+case_new_uuid :: Assertion
+case_new_uuid = do
+  uuid <- newUUID
+  assertBool "newUUID" $ uuid =~ C.uuidRegex
+#endif
+
 -- | Test list for the Utils module.
 testSuite "Utils"
             [ 'prop_commaJoinSplit
@@ -217,4 +248,8 @@ testSuite "Utils"
             , 'prop_niceSort_generic
             , 'prop_niceSort_numbers
             , 'prop_niceSortKey_equiv
+            , 'prop_rStripSpace
+#ifndef NO_REGEX_PCRE
+            , 'case_new_uuid
+#endif
             ]