Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Utils.hs @ a59d5fa1

History | View | Annotate | Download (12.2 kB)

1 80a0546b Michele Tartara
{-# LANGUAGE TemplateHaskell, CPP #-}
2 e1ee7d5a Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 e1ee7d5a Iustin Pop
4 e1ee7d5a Iustin Pop
{-| Unittests for ganeti-htools.
5 e1ee7d5a Iustin Pop
6 e1ee7d5a Iustin Pop
-}
7 e1ee7d5a Iustin Pop
8 e1ee7d5a Iustin Pop
{-
9 e1ee7d5a Iustin Pop
10 45566243 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
11 e1ee7d5a Iustin Pop
12 e1ee7d5a Iustin Pop
This program is free software; you can redistribute it and/or modify
13 e1ee7d5a Iustin Pop
it under the terms of the GNU General Public License as published by
14 e1ee7d5a Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 e1ee7d5a Iustin Pop
(at your option) any later version.
16 e1ee7d5a Iustin Pop
17 e1ee7d5a Iustin Pop
This program is distributed in the hope that it will be useful, but
18 e1ee7d5a Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 e1ee7d5a Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 e1ee7d5a Iustin Pop
General Public License for more details.
21 e1ee7d5a Iustin Pop
22 e1ee7d5a Iustin Pop
You should have received a copy of the GNU General Public License
23 e1ee7d5a Iustin Pop
along with this program; if not, write to the Free Software
24 e1ee7d5a Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 e1ee7d5a Iustin Pop
02110-1301, USA.
26 e1ee7d5a Iustin Pop
27 e1ee7d5a Iustin Pop
-}
28 e1ee7d5a Iustin Pop
29 26d62e4c Iustin Pop
module Test.Ganeti.Utils (testUtils) where
30 e1ee7d5a Iustin Pop
31 01e52493 Iustin Pop
import Test.QuickCheck hiding (Result)
32 04edfc99 Iustin Pop
import Test.HUnit
33 e1ee7d5a Iustin Pop
34 256e28c4 Iustin Pop
import Data.Char (isSpace)
35 04edfc99 Iustin Pop
import Data.List
36 b6aeda4a Dato Simó
import System.Time
37 e1ee7d5a Iustin Pop
import qualified Text.JSON as J
38 80a0546b Michele Tartara
#ifndef NO_REGEX_PCRE
39 80a0546b Michele Tartara
import Text.Regex.PCRE
40 80a0546b Michele Tartara
#endif
41 e1ee7d5a Iustin Pop
42 e1ee7d5a Iustin Pop
import Test.Ganeti.TestHelper
43 e1ee7d5a Iustin Pop
import Test.Ganeti.TestCommon
44 e1ee7d5a Iustin Pop
45 01e52493 Iustin Pop
import Ganeti.BasicTypes
46 80a0546b Michele Tartara
import qualified Ganeti.Constants as C
47 f3baf5ef Iustin Pop
import qualified Ganeti.JSON as JSON
48 a5b270c5 Iustin Pop
import Ganeti.Utils
49 e1ee7d5a Iustin Pop
50 e1ee7d5a Iustin Pop
-- | Helper to generate a small string that doesn't contain commas.
51 5b11f8db Iustin Pop
genNonCommaString :: Gen String
52 e1ee7d5a Iustin Pop
genNonCommaString = do
53 e1ee7d5a Iustin Pop
  size <- choose (0, 20) -- arbitrary max size
54 5b11f8db Iustin Pop
  vectorOf size (arbitrary `suchThat` (/=) ',')
55 e1ee7d5a Iustin Pop
56 e1ee7d5a Iustin Pop
-- | If the list is not just an empty element, and if the elements do
57 e1ee7d5a Iustin Pop
-- not contain commas, then join+split should be idempotent.
58 20bc5360 Iustin Pop
prop_commaJoinSplit :: Property
59 20bc5360 Iustin Pop
prop_commaJoinSplit =
60 e1ee7d5a Iustin Pop
  forAll (choose (0, 20)) $ \llen ->
61 5b11f8db Iustin Pop
  forAll (vectorOf llen genNonCommaString `suchThat` (/=) [""]) $ \lst ->
62 a5b270c5 Iustin Pop
  sepSplit ',' (commaJoin lst) ==? lst
63 e1ee7d5a Iustin Pop
64 e1ee7d5a Iustin Pop
-- | Split and join should always be idempotent.
65 5b11f8db Iustin Pop
prop_commaSplitJoin :: String -> Property
66 20bc5360 Iustin Pop
prop_commaSplitJoin s =
67 a5b270c5 Iustin Pop
  commaJoin (sepSplit ',' s) ==? s
68 e1ee7d5a Iustin Pop
69 e1ee7d5a Iustin Pop
-- | fromObjWithDefault, we test using the Maybe monad and an integer
70 e1ee7d5a Iustin Pop
-- value.
71 20bc5360 Iustin Pop
prop_fromObjWithDefault :: Integer -> String -> Bool
72 20bc5360 Iustin Pop
prop_fromObjWithDefault def_value random_key =
73 e1ee7d5a Iustin Pop
  -- a missing key will be returned with the default
74 e1ee7d5a Iustin Pop
  JSON.fromObjWithDefault [] random_key def_value == Just def_value &&
75 e1ee7d5a Iustin Pop
  -- a found key will be returned as is, not with default
76 e1ee7d5a Iustin Pop
  JSON.fromObjWithDefault [(random_key, J.showJSON def_value)]
77 e1ee7d5a Iustin Pop
       random_key (def_value+1) == Just def_value
78 e1ee7d5a Iustin Pop
79 e1ee7d5a Iustin Pop
-- | Test that functional if' behaves like the syntactic sugar if.
80 20bc5360 Iustin Pop
prop_if'if :: Bool -> Int -> Int -> Gen Prop
81 20bc5360 Iustin Pop
prop_if'if cnd a b =
82 a5b270c5 Iustin Pop
  if' cnd a b ==? if cnd then a else b
83 e1ee7d5a Iustin Pop
84 e1ee7d5a Iustin Pop
-- | Test basic select functionality
85 20bc5360 Iustin Pop
prop_select :: Int      -- ^ Default result
86 20bc5360 Iustin Pop
            -> [Int]    -- ^ List of False values
87 20bc5360 Iustin Pop
            -> [Int]    -- ^ List of True values
88 20bc5360 Iustin Pop
            -> Gen Prop -- ^ Test result
89 20bc5360 Iustin Pop
prop_select def lst1 lst2 =
90 a5b270c5 Iustin Pop
  select def (flist ++ tlist) ==? expectedresult
91 72747d91 Iustin Pop
    where expectedresult = defaultHead def lst2
92 e1ee7d5a Iustin Pop
          flist = zip (repeat False) lst1
93 e1ee7d5a Iustin Pop
          tlist = zip (repeat True)  lst2
94 e1ee7d5a Iustin Pop
95 72747d91 Iustin Pop
{-# ANN prop_select_undefd "HLint: ignore Use alternative" #-}
96 e1ee7d5a Iustin Pop
-- | Test basic select functionality with undefined default
97 20bc5360 Iustin Pop
prop_select_undefd :: [Int]            -- ^ List of False values
98 20bc5360 Iustin Pop
                   -> NonEmptyList Int -- ^ List of True values
99 20bc5360 Iustin Pop
                   -> Gen Prop         -- ^ Test result
100 20bc5360 Iustin Pop
prop_select_undefd lst1 (NonEmpty lst2) =
101 72747d91 Iustin Pop
  -- head is fine as NonEmpty "guarantees" a non-empty list, but not
102 72747d91 Iustin Pop
  -- via types
103 a5b270c5 Iustin Pop
  select undefined (flist ++ tlist) ==? head lst2
104 e1ee7d5a Iustin Pop
    where flist = zip (repeat False) lst1
105 e1ee7d5a Iustin Pop
          tlist = zip (repeat True)  lst2
106 e1ee7d5a Iustin Pop
107 72747d91 Iustin Pop
{-# ANN prop_select_undefv "HLint: ignore Use alternative" #-}
108 e1ee7d5a Iustin Pop
-- | Test basic select functionality with undefined list values
109 20bc5360 Iustin Pop
prop_select_undefv :: [Int]            -- ^ List of False values
110 20bc5360 Iustin Pop
                   -> NonEmptyList Int -- ^ List of True values
111 20bc5360 Iustin Pop
                   -> Gen Prop         -- ^ Test result
112 20bc5360 Iustin Pop
prop_select_undefv lst1 (NonEmpty lst2) =
113 72747d91 Iustin Pop
  -- head is fine as NonEmpty "guarantees" a non-empty list, but not
114 72747d91 Iustin Pop
  -- via types
115 a5b270c5 Iustin Pop
  select undefined cndlist ==? head lst2
116 e1ee7d5a Iustin Pop
    where flist = zip (repeat False) lst1
117 e1ee7d5a Iustin Pop
          tlist = zip (repeat True)  lst2
118 e1ee7d5a Iustin Pop
          cndlist = flist ++ tlist ++ [undefined]
119 e1ee7d5a Iustin Pop
120 20bc5360 Iustin Pop
prop_parseUnit :: NonNegative Int -> Property
121 20bc5360 Iustin Pop
prop_parseUnit (NonNegative n) =
122 01e52493 Iustin Pop
  conjoin
123 01e52493 Iustin Pop
  [ parseUnit (show n) ==? (Ok n::Result Int)
124 01e52493 Iustin Pop
  , parseUnit (show n ++ "m") ==? (Ok n::Result Int)
125 01e52493 Iustin Pop
  , parseUnit (show n ++ "M") ==? (Ok (truncate n_mb)::Result Int)
126 01e52493 Iustin Pop
  , parseUnit (show n ++ "g") ==? (Ok (n*1024)::Result Int)
127 01e52493 Iustin Pop
  , parseUnit (show n ++ "G") ==? (Ok (truncate n_gb)::Result Int)
128 01e52493 Iustin Pop
  , parseUnit (show n ++ "t") ==? (Ok (n*1048576)::Result Int)
129 01e52493 Iustin Pop
  , parseUnit (show n ++ "T") ==? (Ok (truncate n_tb)::Result Int)
130 01e52493 Iustin Pop
  , printTestCase "Internal error/overflow?"
131 01e52493 Iustin Pop
    (n_mb >=0 && n_gb >= 0 && n_tb >= 0)
132 01e52493 Iustin Pop
  , property (isBad (parseUnit (show n ++ "x")::Result Int))
133 01e52493 Iustin Pop
  ]
134 e1ee7d5a Iustin Pop
  where n_mb = (fromIntegral n::Rational) * 1000 * 1000 / 1024 / 1024
135 e1ee7d5a Iustin Pop
        n_gb = n_mb * 1000
136 e1ee7d5a Iustin Pop
        n_tb = n_gb * 1000
137 e1ee7d5a Iustin Pop
138 04edfc99 Iustin Pop
{-# ANN case_niceSort_static "HLint: ignore Use camelCase" #-}
139 04edfc99 Iustin Pop
140 04edfc99 Iustin Pop
case_niceSort_static :: Assertion
141 04edfc99 Iustin Pop
case_niceSort_static = do
142 04edfc99 Iustin Pop
  assertEqual "empty list" [] $ niceSort []
143 04edfc99 Iustin Pop
  assertEqual "punctuation" [",", "."] $ niceSort [",", "."]
144 04edfc99 Iustin Pop
  assertEqual "decimal numbers" ["0.1", "0.2"] $ niceSort ["0.1", "0.2"]
145 04edfc99 Iustin Pop
  assertEqual "various numbers" ["0,099", "0.1", "0.2", "0;099"] $
146 04edfc99 Iustin Pop
              niceSort ["0;099", "0,099", "0.1", "0.2"]
147 04edfc99 Iustin Pop
148 04edfc99 Iustin Pop
  assertEqual "simple concat" ["0000", "a0", "a1", "a2", "a20", "a99",
149 04edfc99 Iustin Pop
                               "b00", "b10", "b70"] $
150 04edfc99 Iustin Pop
    niceSort ["a0", "a1", "a99", "a20", "a2", "b10", "b70", "b00", "0000"]
151 04edfc99 Iustin Pop
152 04edfc99 Iustin Pop
  assertEqual "ranges" ["A", "Z", "a0-0", "a0-4", "a1-0", "a9-1", "a09-2",
153 04edfc99 Iustin Pop
                      "a20-3", "a99-3", "a99-10", "b"] $
154 04edfc99 Iustin Pop
    niceSort ["a0-0", "a1-0", "a99-10", "a20-3", "a0-4", "a99-3", "a09-2",
155 04edfc99 Iustin Pop
              "Z", "a9-1", "A", "b"]
156 04edfc99 Iustin Pop
157 04edfc99 Iustin Pop
  assertEqual "large"
158 04edfc99 Iustin Pop
    ["3jTwJPtrXOY22bwL2YoW", "Eegah9ei", "KOt7vn1dWXi",
159 04edfc99 Iustin Pop
     "KVQqLPDjcPjf8T3oyzjcOsfkb", "WvNJd91OoXvLzdEiEXa6",
160 04edfc99 Iustin Pop
     "Z8Ljf1Pf5eBfNg171wJR", "a07h8feON165N67PIE", "bH4Q7aCu3PUPjK3JtH",
161 04edfc99 Iustin Pop
     "cPRi0lM7HLnSuWA2G9", "guKJkXnkULealVC8CyF1xefym",
162 04edfc99 Iustin Pop
     "pqF8dkU5B1cMnyZuREaSOADYx", "uHXAyYYftCSG1o7qcCqe",
163 04edfc99 Iustin Pop
     "xij88brTulHYAv8IEOyU", "xpIUJeVT1Rp"] $
164 04edfc99 Iustin Pop
    niceSort ["Eegah9ei", "xij88brTulHYAv8IEOyU", "3jTwJPtrXOY22bwL2YoW",
165 04edfc99 Iustin Pop
             "Z8Ljf1Pf5eBfNg171wJR", "WvNJd91OoXvLzdEiEXa6",
166 04edfc99 Iustin Pop
             "uHXAyYYftCSG1o7qcCqe", "xpIUJeVT1Rp", "KOt7vn1dWXi",
167 04edfc99 Iustin Pop
             "a07h8feON165N67PIE", "bH4Q7aCu3PUPjK3JtH",
168 04edfc99 Iustin Pop
             "cPRi0lM7HLnSuWA2G9", "KVQqLPDjcPjf8T3oyzjcOsfkb",
169 04edfc99 Iustin Pop
             "guKJkXnkULealVC8CyF1xefym", "pqF8dkU5B1cMnyZuREaSOADYx"]
170 04edfc99 Iustin Pop
171 45566243 Iustin Pop
-- | Tests single-string behaviour of 'niceSort'.
172 04edfc99 Iustin Pop
prop_niceSort_single :: Property
173 04edfc99 Iustin Pop
prop_niceSort_single =
174 5006418e Iustin Pop
  forAll genName $ \name ->
175 04edfc99 Iustin Pop
  conjoin
176 04edfc99 Iustin Pop
  [ printTestCase "single string" $ [name] ==? niceSort [name]
177 04edfc99 Iustin Pop
  , printTestCase "single plus empty" $ ["", name] ==? niceSort [name, ""]
178 04edfc99 Iustin Pop
  ]
179 04edfc99 Iustin Pop
180 04edfc99 Iustin Pop
-- | Tests some generic 'niceSort' properties. Note that the last test
181 04edfc99 Iustin Pop
-- must add a non-digit prefix; a digit one might change ordering.
182 04edfc99 Iustin Pop
prop_niceSort_generic :: Property
183 04edfc99 Iustin Pop
prop_niceSort_generic =
184 04edfc99 Iustin Pop
  forAll (resize 20 arbitrary) $ \names ->
185 04edfc99 Iustin Pop
  let n_sorted = niceSort names in
186 04edfc99 Iustin Pop
  conjoin [ printTestCase "length" $ length names ==? length n_sorted
187 04edfc99 Iustin Pop
          , printTestCase "same strings" $ sort names ==? sort n_sorted
188 04edfc99 Iustin Pop
          , printTestCase "idempotence" $ n_sorted ==? niceSort n_sorted
189 04edfc99 Iustin Pop
          , printTestCase "static prefix" $ n_sorted ==?
190 04edfc99 Iustin Pop
              map tail (niceSort $ map (" "++) names)
191 04edfc99 Iustin Pop
          ]
192 04edfc99 Iustin Pop
193 04edfc99 Iustin Pop
-- | Tests that niceSorting numbers is identical to actual sorting
194 04edfc99 Iustin Pop
-- them (in numeric form).
195 04edfc99 Iustin Pop
prop_niceSort_numbers :: Property
196 04edfc99 Iustin Pop
prop_niceSort_numbers =
197 04edfc99 Iustin Pop
  forAll (listOf (arbitrary::Gen (NonNegative Int))) $ \numbers ->
198 04edfc99 Iustin Pop
  map show (sort numbers) ==? niceSort (map show numbers)
199 04edfc99 Iustin Pop
200 04edfc99 Iustin Pop
-- | Tests that 'niceSort' and 'niceSortKey' are equivalent.
201 04edfc99 Iustin Pop
prop_niceSortKey_equiv :: Property
202 04edfc99 Iustin Pop
prop_niceSortKey_equiv =
203 04edfc99 Iustin Pop
  forAll (resize 20 arbitrary) $ \names ->
204 04edfc99 Iustin Pop
  forAll (vectorOf (length names) (arbitrary::Gen Int)) $ \numbers ->
205 04edfc99 Iustin Pop
  let n_sorted = niceSort names in
206 04edfc99 Iustin Pop
  conjoin
207 04edfc99 Iustin Pop
  [ printTestCase "key id" $ n_sorted ==? niceSortKey id names
208 04edfc99 Iustin Pop
  , printTestCase "key rev" $ niceSort (map reverse names) ==?
209 04edfc99 Iustin Pop
                              map reverse (niceSortKey reverse names)
210 04edfc99 Iustin Pop
  , printTestCase "key snd" $ n_sorted ==? map snd (niceSortKey snd $
211 04edfc99 Iustin Pop
                                                    zip numbers names)
212 04edfc99 Iustin Pop
  ]
213 04edfc99 Iustin Pop
214 f1f6f117 Dato Simó
-- | Tests 'rStripSpace'.
215 256e28c4 Iustin Pop
prop_rStripSpace :: NonEmptyList Char -> Property
216 256e28c4 Iustin Pop
prop_rStripSpace (NonEmpty str) =
217 256e28c4 Iustin Pop
  forAll (resize 50 $ listOf1 (arbitrary `suchThat` isSpace)) $ \whitespace ->
218 256e28c4 Iustin Pop
  conjoin [ printTestCase "arb. string last char is not space" $
219 256e28c4 Iustin Pop
              case rStripSpace str of
220 256e28c4 Iustin Pop
                [] -> True
221 256e28c4 Iustin Pop
                xs -> not . isSpace $ last xs
222 256e28c4 Iustin Pop
          , printTestCase "whitespace suffix is stripped" $
223 256e28c4 Iustin Pop
              rStripSpace str ==? rStripSpace (str ++ whitespace)
224 256e28c4 Iustin Pop
          , printTestCase "whitespace reduced to null" $
225 256e28c4 Iustin Pop
              rStripSpace whitespace ==? ""
226 256e28c4 Iustin Pop
          , printTestCase "idempotent on empty strings" $
227 256e28c4 Iustin Pop
              rStripSpace "" ==? ""
228 256e28c4 Iustin Pop
          ]
229 256e28c4 Iustin Pop
230 80a0546b Michele Tartara
#ifndef NO_REGEX_PCRE
231 dccf6eaf Michele Tartara
{-# ANN case_new_uuid "HLint: ignore Use camelCase" #-}
232 dccf6eaf Michele Tartara
233 80a0546b Michele Tartara
-- | Tests that the newUUID function produces valid UUIDs.
234 80a0546b Michele Tartara
case_new_uuid :: Assertion
235 80a0546b Michele Tartara
case_new_uuid = do
236 80a0546b Michele Tartara
  uuid <- newUUID
237 80a0546b Michele Tartara
  assertBool "newUUID" $ uuid =~ C.uuidRegex
238 80a0546b Michele Tartara
#endif
239 80a0546b Michele Tartara
240 b6aeda4a Dato Simó
prop_clockTimeToString :: Integer -> Integer -> Property
241 b6aeda4a Dato Simó
prop_clockTimeToString ts pico =
242 b6aeda4a Dato Simó
  clockTimeToString (TOD ts pico) ==? show ts
243 b6aeda4a Dato Simó
244 b009f682 Dato Simó
-- | Test normal operation for 'chompPrefix'.
245 b009f682 Dato Simó
--
246 b009f682 Dato Simó
-- Any random prefix of a string must be stripped correctly, including the empty
247 b009f682 Dato Simó
-- prefix, and the whole string.
248 b009f682 Dato Simó
prop_chompPrefix_normal :: String -> Property
249 b009f682 Dato Simó
prop_chompPrefix_normal str =
250 b009f682 Dato Simó
  forAll (choose (0, length str)) $ \size ->
251 b009f682 Dato Simó
  chompPrefix (take size str) str ==? (Just $ drop size str)
252 b009f682 Dato Simó
253 b009f682 Dato Simó
-- | Test that 'chompPrefix' correctly allows the last char (the separator) to
254 b009f682 Dato Simó
-- be absent if the string terminates there.
255 b009f682 Dato Simó
prop_chompPrefix_last :: Property
256 b009f682 Dato Simó
prop_chompPrefix_last =
257 b009f682 Dato Simó
  forAll (choose (1, 20)) $ \len ->
258 b009f682 Dato Simó
  forAll (vectorOf len arbitrary) $ \pfx ->
259 b009f682 Dato Simó
  chompPrefix pfx pfx ==? Just "" .&&.
260 b009f682 Dato Simó
  chompPrefix pfx (init pfx) ==? Just ""
261 b009f682 Dato Simó
262 b009f682 Dato Simó
-- | Test that chompPrefix on the empty string always returns Nothing for
263 b009f682 Dato Simó
-- prefixes of length 2 or more.
264 b009f682 Dato Simó
prop_chompPrefix_empty_string :: Property
265 b009f682 Dato Simó
prop_chompPrefix_empty_string =
266 b009f682 Dato Simó
  forAll (choose (2, 20)) $ \len ->
267 b009f682 Dato Simó
  forAll (vectorOf len arbitrary) $ \pfx ->
268 b009f682 Dato Simó
  chompPrefix pfx "" ==? Nothing
269 b009f682 Dato Simó
270 b009f682 Dato Simó
-- | Test 'chompPrefix' returns Nothing when the prefix doesn't match.
271 b009f682 Dato Simó
prop_chompPrefix_nothing :: Property
272 b009f682 Dato Simó
prop_chompPrefix_nothing =
273 b009f682 Dato Simó
  forAll (choose (1, 20)) $ \len ->
274 b009f682 Dato Simó
  forAll (vectorOf len arbitrary) $ \pfx ->
275 b009f682 Dato Simó
  forAll (arbitrary `suchThat`
276 b009f682 Dato Simó
          (\s -> not (pfx `isPrefixOf` s) && s /= init pfx)) $ \str ->
277 b009f682 Dato Simó
  chompPrefix pfx str ==? Nothing
278 b009f682 Dato Simó
279 9fb621af Yiannis Tsiouris
-- | Tests 'trim'.
280 9fb621af Yiannis Tsiouris
prop_trim :: NonEmptyList Char -> Property
281 9fb621af Yiannis Tsiouris
prop_trim (NonEmpty str) =
282 9fb621af Yiannis Tsiouris
  forAll (listOf1 $ elements " \t\n\r\f") $ \whitespace ->
283 9fb621af Yiannis Tsiouris
  forAll (choose (0, length whitespace)) $ \n ->
284 9fb621af Yiannis Tsiouris
  let (preWS, postWS) = splitAt n whitespace in
285 9fb621af Yiannis Tsiouris
  conjoin [ printTestCase "arb. string first and last char are not space" $
286 9fb621af Yiannis Tsiouris
              case trim str of
287 9fb621af Yiannis Tsiouris
                [] -> True
288 9fb621af Yiannis Tsiouris
                xs -> (not . isSpace . head) xs && (not . isSpace . last) xs
289 9fb621af Yiannis Tsiouris
          , printTestCase "whitespace is striped" $
290 9fb621af Yiannis Tsiouris
              trim str ==? trim (preWS ++ str ++ postWS)
291 9fb621af Yiannis Tsiouris
          , printTestCase "whitespace reduced to null" $
292 9fb621af Yiannis Tsiouris
              trim whitespace ==? ""
293 9fb621af Yiannis Tsiouris
          , printTestCase "idempotent on empty strings" $
294 9fb621af Yiannis Tsiouris
              trim "" ==? ""
295 9fb621af Yiannis Tsiouris
          ]
296 b009f682 Dato Simó
297 e1ee7d5a Iustin Pop
-- | Test list for the Utils module.
298 26d62e4c Iustin Pop
testSuite "Utils"
299 20bc5360 Iustin Pop
            [ 'prop_commaJoinSplit
300 20bc5360 Iustin Pop
            , 'prop_commaSplitJoin
301 20bc5360 Iustin Pop
            , 'prop_fromObjWithDefault
302 20bc5360 Iustin Pop
            , 'prop_if'if
303 20bc5360 Iustin Pop
            , 'prop_select
304 20bc5360 Iustin Pop
            , 'prop_select_undefd
305 20bc5360 Iustin Pop
            , 'prop_select_undefv
306 20bc5360 Iustin Pop
            , 'prop_parseUnit
307 04edfc99 Iustin Pop
            , 'case_niceSort_static
308 04edfc99 Iustin Pop
            , 'prop_niceSort_single
309 04edfc99 Iustin Pop
            , 'prop_niceSort_generic
310 04edfc99 Iustin Pop
            , 'prop_niceSort_numbers
311 04edfc99 Iustin Pop
            , 'prop_niceSortKey_equiv
312 256e28c4 Iustin Pop
            , 'prop_rStripSpace
313 9fb621af Yiannis Tsiouris
            , 'prop_trim
314 80a0546b Michele Tartara
#ifndef NO_REGEX_PCRE
315 80a0546b Michele Tartara
            , 'case_new_uuid
316 80a0546b Michele Tartara
#endif
317 b6aeda4a Dato Simó
            , 'prop_clockTimeToString
318 b009f682 Dato Simó
            , 'prop_chompPrefix_normal
319 b009f682 Dato Simó
            , 'prop_chompPrefix_last
320 b009f682 Dato Simó
            , 'prop_chompPrefix_empty_string
321 b009f682 Dato Simó
            , 'prop_chompPrefix_nothing
322 e1ee7d5a Iustin Pop
            ]