Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / THH.hs @ 93f1e606

History | View | Annotate | Download (2 kB)

1 f51eacf3 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 f51eacf3 Iustin Pop
3 f51eacf3 Iustin Pop
{-| Unittests for our template-haskell generated code.
4 f51eacf3 Iustin Pop
5 f51eacf3 Iustin Pop
-}
6 f51eacf3 Iustin Pop
7 f51eacf3 Iustin Pop
{-
8 f51eacf3 Iustin Pop
9 f51eacf3 Iustin Pop
Copyright (C) 2012 Google Inc.
10 f51eacf3 Iustin Pop
11 f51eacf3 Iustin Pop
This program is free software; you can redistribute it and/or modify
12 f51eacf3 Iustin Pop
it under the terms of the GNU General Public License as published by
13 f51eacf3 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
14 f51eacf3 Iustin Pop
(at your option) any later version.
15 f51eacf3 Iustin Pop
16 f51eacf3 Iustin Pop
This program is distributed in the hope that it will be useful, but
17 f51eacf3 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
18 f51eacf3 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
19 f51eacf3 Iustin Pop
General Public License for more details.
20 f51eacf3 Iustin Pop
21 f51eacf3 Iustin Pop
You should have received a copy of the GNU General Public License
22 f51eacf3 Iustin Pop
along with this program; if not, write to the Free Software
23 f51eacf3 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
24 f51eacf3 Iustin Pop
02110-1301, USA.
25 f51eacf3 Iustin Pop
26 f51eacf3 Iustin Pop
-}
27 f51eacf3 Iustin Pop
28 f51eacf3 Iustin Pop
module Test.Ganeti.THH
29 f51eacf3 Iustin Pop
  ( testTHH
30 f51eacf3 Iustin Pop
  ) where
31 f51eacf3 Iustin Pop
32 f51eacf3 Iustin Pop
import Test.QuickCheck
33 f51eacf3 Iustin Pop
34 f51eacf3 Iustin Pop
import Text.JSON
35 f51eacf3 Iustin Pop
36 f51eacf3 Iustin Pop
import Ganeti.THH
37 f51eacf3 Iustin Pop
38 f51eacf3 Iustin Pop
import Test.Ganeti.TestHelper
39 f51eacf3 Iustin Pop
import Test.Ganeti.TestCommon
40 f51eacf3 Iustin Pop
41 f51eacf3 Iustin Pop
{-# ANN module "HLint: ignore Use camelCase" #-}
42 f51eacf3 Iustin Pop
43 f51eacf3 Iustin Pop
-- * Custom types
44 f51eacf3 Iustin Pop
45 f51eacf3 Iustin Pop
-- | Type used to test optional field implementation. Equivalent to
46 f51eacf3 Iustin Pop
-- @data TestObj = TestObj { tobjA :: Maybe Int, tobjB :: Maybe Int
47 f51eacf3 Iustin Pop
-- }@.
48 5c03bcea Iustin Pop
$(buildObject "TestObj" "tobj"
49 f51eacf3 Iustin Pop
  [ optionalField $ simpleField "a" [t| Int |]
50 f51eacf3 Iustin Pop
  , optionalNullSerField $ simpleField "b" [t| Int |]
51 f51eacf3 Iustin Pop
  ])
52 f51eacf3 Iustin Pop
53 f51eacf3 Iustin Pop
-- | Arbitrary instance for 'TestObj'.
54 f51eacf3 Iustin Pop
$(genArbitrary ''TestObj)
55 f51eacf3 Iustin Pop
56 f51eacf3 Iustin Pop
-- | Tests that serialising an (arbitrary) 'TestObj' instance is
57 f51eacf3 Iustin Pop
-- correct: fully optional fields are represented in the resulting
58 f51eacf3 Iustin Pop
-- dictionary only when non-null, optional-but-required fields are
59 f51eacf3 Iustin Pop
-- always represented (with either null or an actual value).
60 f51eacf3 Iustin Pop
prop_OptFields :: TestObj -> Property
61 f51eacf3 Iustin Pop
prop_OptFields to =
62 f51eacf3 Iustin Pop
  let a_member = case tobjA to of
63 f51eacf3 Iustin Pop
                   Nothing -> []
64 f51eacf3 Iustin Pop
                   Just x -> [("a", showJSON x)]
65 f51eacf3 Iustin Pop
      b_member = [("b", case tobjB to of
66 f51eacf3 Iustin Pop
                          Nothing -> JSNull
67 f51eacf3 Iustin Pop
                          Just x -> showJSON x)]
68 f51eacf3 Iustin Pop
  in showJSON to ==? makeObj (a_member ++ b_member)
69 f51eacf3 Iustin Pop
70 f51eacf3 Iustin Pop
71 f51eacf3 Iustin Pop
testSuite "THH"
72 f51eacf3 Iustin Pop
            [ 'prop_OptFields
73 f51eacf3 Iustin Pop
            ]