Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / Utils.hs @ 896cc964

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