Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / BasicTypes.hs @ 61899e64

History | View | Annotate | Download (5.1 kB)

1 93be1ced Iustin Pop
{-# LANGUAGE TemplateHaskell, FlexibleInstances, TypeSynonymInstances #-}
2 1493a93b Iustin Pop
{-# OPTIONS_GHC -fno-warn-orphans #-}
3 1493a93b Iustin Pop
4 1493a93b Iustin Pop
{-| Unittests for ganeti-htools.
5 1493a93b Iustin Pop
6 1493a93b Iustin Pop
-}
7 1493a93b Iustin Pop
8 1493a93b Iustin Pop
{-
9 1493a93b Iustin Pop
10 1493a93b Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 1493a93b Iustin Pop
12 1493a93b Iustin Pop
This program is free software; you can redistribute it and/or modify
13 1493a93b Iustin Pop
it under the terms of the GNU General Public License as published by
14 1493a93b Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 1493a93b Iustin Pop
(at your option) any later version.
16 1493a93b Iustin Pop
17 1493a93b Iustin Pop
This program is distributed in the hope that it will be useful, but
18 1493a93b Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 1493a93b Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 1493a93b Iustin Pop
General Public License for more details.
21 1493a93b Iustin Pop
22 1493a93b Iustin Pop
You should have received a copy of the GNU General Public License
23 1493a93b Iustin Pop
along with this program; if not, write to the Free Software
24 1493a93b Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 1493a93b Iustin Pop
02110-1301, USA.
26 1493a93b Iustin Pop
27 1493a93b Iustin Pop
-}
28 1493a93b Iustin Pop
29 1493a93b Iustin Pop
module Test.Ganeti.BasicTypes (testBasicTypes) where
30 1493a93b Iustin Pop
31 1493a93b Iustin Pop
import Test.QuickCheck hiding (Result)
32 1493a93b Iustin Pop
import Test.QuickCheck.Function
33 1493a93b Iustin Pop
34 1493a93b Iustin Pop
import Control.Applicative
35 1493a93b Iustin Pop
import Control.Monad
36 1493a93b Iustin Pop
37 1493a93b Iustin Pop
import Test.Ganeti.TestHelper
38 1493a93b Iustin Pop
import Test.Ganeti.TestCommon
39 1493a93b Iustin Pop
40 1493a93b Iustin Pop
import Ganeti.BasicTypes
41 1493a93b Iustin Pop
42 1493a93b Iustin Pop
-- Since we actually want to test these, don't tell us not to use them :)
43 1493a93b Iustin Pop
44 1493a93b Iustin Pop
{-# ANN module "HLint: ignore Functor law" #-}
45 1493a93b Iustin Pop
{-# ANN module "HLint: ignore Monad law, left identity" #-}
46 1493a93b Iustin Pop
{-# ANN module "HLint: ignore Monad law, right identity" #-}
47 1493a93b Iustin Pop
{-# ANN module "HLint: ignore Use >=>" #-}
48 66ad857a Iustin Pop
{-# ANN module "HLint: ignore Use ." #-}
49 1493a93b Iustin Pop
50 1493a93b Iustin Pop
-- * Arbitrary instances
51 1493a93b Iustin Pop
52 1493a93b Iustin Pop
instance (Arbitrary a) => Arbitrary (Result a) where
53 1493a93b Iustin Pop
  arbitrary = oneof [ Bad <$> arbitrary
54 1493a93b Iustin Pop
                    , Ok  <$> arbitrary
55 1493a93b Iustin Pop
                    ]
56 1493a93b Iustin Pop
57 1493a93b Iustin Pop
-- * Test cases
58 1493a93b Iustin Pop
59 1493a93b Iustin Pop
-- | Tests the functor identity law (fmap id == id).
60 1493a93b Iustin Pop
prop_functor_id :: Result Int -> Property
61 1493a93b Iustin Pop
prop_functor_id ri =
62 1493a93b Iustin Pop
  fmap id ri ==? ri
63 1493a93b Iustin Pop
64 1493a93b Iustin Pop
-- | Tests the functor composition law (fmap (f . g)  ==  fmap f . fmap g).
65 1493a93b Iustin Pop
prop_functor_composition :: Result Int
66 1493a93b Iustin Pop
                         -> Fun Int Int -> Fun Int Int -> Property
67 1493a93b Iustin Pop
prop_functor_composition ri (Fun _ f) (Fun _ g) =
68 1493a93b Iustin Pop
  fmap (f . g) ri ==? (fmap f . fmap g) ri
69 1493a93b Iustin Pop
70 1493a93b Iustin Pop
-- | Tests the applicative identity law (pure id <*> v = v).
71 1493a93b Iustin Pop
prop_applicative_identity :: Result Int -> Property
72 1493a93b Iustin Pop
prop_applicative_identity v =
73 1493a93b Iustin Pop
  pure id <*> v ==? v
74 1493a93b Iustin Pop
75 1493a93b Iustin Pop
-- | Tests the applicative composition law (pure (.) <*> u <*> v <*> w
76 1493a93b Iustin Pop
-- = u <*> (v <*> w)).
77 5b11f8db Iustin Pop
prop_applicative_composition :: Result (Fun Int Int)
78 5b11f8db Iustin Pop
                             -> Result (Fun Int Int)
79 1493a93b Iustin Pop
                             -> Result Int
80 1493a93b Iustin Pop
                             -> Property
81 1493a93b Iustin Pop
prop_applicative_composition u v w =
82 1493a93b Iustin Pop
  let u' = fmap apply u
83 1493a93b Iustin Pop
      v' = fmap apply v
84 1493a93b Iustin Pop
  in pure (.) <*> u' <*> v' <*> w ==? u' <*> (v' <*> w)
85 1493a93b Iustin Pop
86 1493a93b Iustin Pop
-- | Tests the applicative homomorphism law (pure f <*> pure x = pure (f x)).
87 1493a93b Iustin Pop
prop_applicative_homomorphism :: Fun Int Int -> Int -> Property
88 1493a93b Iustin Pop
prop_applicative_homomorphism (Fun _ f) x =
89 5b11f8db Iustin Pop
  ((pure f <*> pure x)::Result Int) ==? pure (f x)
90 1493a93b Iustin Pop
91 1493a93b Iustin Pop
-- | Tests the applicative interchange law (u <*> pure y = pure ($ y) <*> u).
92 1493a93b Iustin Pop
prop_applicative_interchange :: Result (Fun Int Int)
93 1493a93b Iustin Pop
                             -> Int -> Property
94 1493a93b Iustin Pop
prop_applicative_interchange f y =
95 1493a93b Iustin Pop
  let u = fmap apply f -- need to extract the actual function from Fun
96 1493a93b Iustin Pop
  in u <*> pure y ==? pure ($ y) <*> u
97 1493a93b Iustin Pop
98 1493a93b Iustin Pop
-- | Tests the applicative\/functor correspondence (fmap f x = pure f <*> x).
99 1493a93b Iustin Pop
prop_applicative_functor :: Fun Int Int -> Result Int -> Property
100 1493a93b Iustin Pop
prop_applicative_functor (Fun _ f) x =
101 1493a93b Iustin Pop
  fmap f x ==? pure f <*> x
102 1493a93b Iustin Pop
103 1493a93b Iustin Pop
-- | Tests the applicative\/monad correspondence (pure = return and
104 1493a93b Iustin Pop
-- (<*>) = ap).
105 1493a93b Iustin Pop
prop_applicative_monad :: Int -> Result (Fun Int Int) -> Property
106 1493a93b Iustin Pop
prop_applicative_monad v f =
107 1493a93b Iustin Pop
  let v' = pure v :: Result Int
108 1493a93b Iustin Pop
      f' = fmap apply f -- need to extract the actual function from Fun
109 1493a93b Iustin Pop
  in v' ==? return v .&&. (f' <*> v') ==? f' `ap` v'
110 1493a93b Iustin Pop
111 1493a93b Iustin Pop
-- | Tests the monad laws (return a >>= k == k a, m >>= return == m, m
112 1493a93b Iustin Pop
-- >>= (\x -> k x >>= h) == (m >>= k) >>= h).
113 1493a93b Iustin Pop
prop_monad_laws :: Int -> Result Int
114 1493a93b Iustin Pop
                -> Fun Int (Result Int)
115 1493a93b Iustin Pop
                -> Fun Int (Result Int)
116 1493a93b Iustin Pop
                -> Property
117 1493a93b Iustin Pop
prop_monad_laws a m (Fun _ k) (Fun _ h) =
118 942a9a6a Iustin Pop
  conjoin
119 942a9a6a Iustin Pop
  [ printTestCase "return a >>= k == k a" ((return a >>= k) ==? k a)
120 942a9a6a Iustin Pop
  , printTestCase "m >>= return == m" ((m >>= return) ==? m)
121 942a9a6a Iustin Pop
  , printTestCase "m >>= (\\x -> k x >>= h) == (m >>= k) >>= h)"
122 1493a93b Iustin Pop
    ((m >>= (\x -> k x >>= h)) ==? ((m >>= k) >>= h))
123 942a9a6a Iustin Pop
  ]
124 1493a93b Iustin Pop
125 1493a93b Iustin Pop
-- | Tests the monad plus laws ( mzero >>= f = mzero, v >> mzero = mzero).
126 1493a93b Iustin Pop
prop_monadplus_mzero :: Result Int -> Fun Int (Result Int) -> Property
127 1493a93b Iustin Pop
prop_monadplus_mzero v (Fun _ f) =
128 1493a93b Iustin Pop
  printTestCase "mzero >>= f = mzero" ((mzero >>= f) ==? mzero) .&&.
129 1493a93b Iustin Pop
  -- FIXME: since we have "many" mzeros, we can't test for equality,
130 1493a93b Iustin Pop
  -- just that we got back a 'Bad' value; I'm not sure if this means
131 1493a93b Iustin Pop
  -- our MonadPlus instance is not sound or not...
132 1493a93b Iustin Pop
  printTestCase "v >> mzero = mzero" (isBad (v >> mzero))
133 1493a93b Iustin Pop
134 1493a93b Iustin Pop
testSuite "BasicTypes"
135 1493a93b Iustin Pop
  [ 'prop_functor_id
136 1493a93b Iustin Pop
  , 'prop_functor_composition
137 1493a93b Iustin Pop
  , 'prop_applicative_identity
138 1493a93b Iustin Pop
  , 'prop_applicative_composition
139 1493a93b Iustin Pop
  , 'prop_applicative_homomorphism
140 1493a93b Iustin Pop
  , 'prop_applicative_interchange
141 1493a93b Iustin Pop
  , 'prop_applicative_functor
142 1493a93b Iustin Pop
  , 'prop_applicative_monad
143 1493a93b Iustin Pop
  , 'prop_monad_laws
144 1493a93b Iustin Pop
  , 'prop_monadplus_mzero
145 1493a93b Iustin Pop
  ]