Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Query / Language.hs @ 63b068c1

History | View | Annotate | Download (3.2 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-orphans #-}
3

    
4
{-| Unittests for ganeti-htools.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11

    
12
This program is free software; you can redistribute it and/or modify
13
it under the terms of the GNU General Public License as published by
14
the Free Software Foundation; either version 2 of the License, or
15
(at your option) any later version.
16

    
17
This program is distributed in the hope that it will be useful, but
18
WITHOUT ANY WARRANTY; without even the implied warranty of
19
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20
General Public License for more details.
21

    
22
You should have received a copy of the GNU General Public License
23
along with this program; if not, write to the Free Software
24
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25
02110-1301, USA.
26

    
27
-}
28

    
29
module Test.Ganeti.Query.Language
30
  ( testQuery_Language
31
  , genFilter
32
  ) where
33

    
34
import Test.QuickCheck
35

    
36
import Control.Applicative
37

    
38
import Test.Ganeti.TestHelper
39
import Test.Ganeti.TestCommon
40

    
41
import qualified Ganeti.Query.Language as Qlang
42

    
43
-- | Custom 'Qlang.Filter' generator (top-level), which enforces a
44
-- (sane) limit on the depth of the generated filters.
45
genFilter :: Gen (Qlang.Filter Qlang.FilterField)
46
genFilter = choose (0, 10) >>= genFilter'
47

    
48
-- | Custom generator for filters that correctly halves the state of
49
-- the generators at each recursive step, per the QuickCheck
50
-- documentation, in order not to run out of memory.
51
genFilter' :: Int -> Gen (Qlang.Filter Qlang.FilterField)
52
genFilter' 0 =
53
  oneof [ return Qlang.EmptyFilter
54
        , Qlang.TrueFilter     <$> getName
55
        , Qlang.EQFilter       <$> getName <*> value
56
        , Qlang.LTFilter       <$> getName <*> value
57
        , Qlang.GTFilter       <$> getName <*> value
58
        , Qlang.LEFilter       <$> getName <*> value
59
        , Qlang.GEFilter       <$> getName <*> value
60
        , Qlang.RegexpFilter   <$> getName <*> arbitrary
61
        , Qlang.ContainsFilter <$> getName <*> value
62
        ]
63
    where value = oneof [ Qlang.QuotedString <$> getName
64
                        , Qlang.NumericValue <$> arbitrary
65
                        ]
66
genFilter' n = do
67
  oneof [ Qlang.AndFilter  <$> vectorOf n'' (genFilter' n')
68
        , Qlang.OrFilter   <$> vectorOf n'' (genFilter' n')
69
        , Qlang.NotFilter  <$> genFilter' n'
70
        ]
71
  where n' = n `div` 2 -- sub-filter generator size
72
        n'' = max n' 2 -- but we don't want empty or 1-element lists,
73
                       -- so use this for and/or filter list length
74

    
75
instance Arbitrary Qlang.ItemType where
76
  arbitrary = elements [minBound..maxBound]
77

    
78
instance Arbitrary Qlang.FilterRegex where
79
  arbitrary = getName >>= Qlang.mkRegex -- a name should be a good regex
80

    
81
-- | Tests that serialisation/deserialisation of filters is
82
-- idempotent.
83
prop_Serialisation :: Property
84
prop_Serialisation =
85
  forAll genFilter testSerialisation
86

    
87
prop_FilterRegex_instances :: Qlang.FilterRegex -> Property
88
prop_FilterRegex_instances rex =
89
  printTestCase "failed JSON encoding" (testSerialisation rex) .&&.
90
  printTestCase "failed read/show instances" (read (show rex) ==? rex)
91

    
92
testSuite "Query/Language"
93
  [ 'prop_Serialisation
94
  , 'prop_FilterRegex_instances
95
  ]