Statistics
| Branch: | Tag: | Revision:

root / test / hs / Test / Ganeti / TestHelper.hs @ 147fd319

History | View | Annotate | Download (4.8 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Unittest helpers for TemplateHaskell components.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2011, 2012, 2013 Google Inc.
10

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

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

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

    
26
-}
27

    
28
module Test.Ganeti.TestHelper
29
  ( testSuite
30
  , genArbitrary
31
  ) where
32

    
33
import Control.Applicative
34
import Data.List (stripPrefix, isPrefixOf)
35
import Data.Maybe (fromMaybe)
36
import Test.Framework
37
import Test.Framework.Providers.HUnit
38
import Test.Framework.Providers.QuickCheck2
39
import Test.HUnit (Assertion)
40
import Test.QuickCheck
41
import Language.Haskell.TH
42

    
43
-- | Test property prefix.
44
propPrefix :: String
45
propPrefix = "prop_"
46

    
47
-- | Test case prefix.
48
casePrefix :: String
49
casePrefix = "case_"
50

    
51
-- | Test case prefix without underscore.
52
case2Pfx :: String
53
case2Pfx = "case"
54

    
55
-- | Tries to drop a prefix from a string.
56
simplifyName :: String -> String -> String
57
simplifyName pfx string = fromMaybe string (stripPrefix pfx string)
58

    
59
-- | Builds a test from a QuickCheck property.
60
runProp :: Testable prop => String -> prop -> Test
61
runProp = testProperty . simplifyName propPrefix
62

    
63
-- | Builds a test for a HUnit test case.
64
runCase :: String -> Assertion -> Test
65
runCase = testCase . simplifyName casePrefix
66

    
67
-- | Runs the correct test provider for a given test, based on its
68
-- name (not very nice, but...).
69
run :: Name -> Q Exp
70
run name =
71
  let str = nameBase name
72
      nameE = varE name
73
      strE = litE (StringL str)
74
  in case () of
75
       _ | propPrefix `isPrefixOf` str -> [| runProp $strE $nameE |]
76
         | casePrefix `isPrefixOf` str -> [| runCase $strE $nameE |]
77
         | case2Pfx `isPrefixOf` str ->
78
           [| (testCase . simplifyName case2Pfx) $strE $nameE |]
79
         | otherwise -> fail $ "Unsupported test function name '" ++ str ++ "'"
80

    
81
-- | Convert slashes in a name to underscores.
82
mapSlashes :: String -> String
83
mapSlashes = map (\c -> if c == '/' then '_' else c)
84

    
85
-- | Builds a test suite.
86
testSuite :: String -> [Name] -> Q [Dec]
87
testSuite tsname tdef = do
88
  let fullname = mkName $ "test" ++ mapSlashes tsname
89
  tests <- mapM run tdef
90
  sigtype <- [t| Test |]
91
  body <- [| testGroup $(litE $ stringL tsname) $(return $ ListE tests) |]
92
  return [ SigD fullname sigtype
93
         , ValD (VarP fullname) (NormalB body) []
94
         ]
95

    
96
-- | Builds an arbitrary value for a given constructor. This doesn't
97
-- use the actual types of the fields, since we expect arbitrary
98
-- instances for all of the types anyway, we only care about the
99
-- number of fields.
100
mkConsArbitrary :: (Name, [a]) -> Exp
101
mkConsArbitrary (name, types) =
102
  let infix_arb a = InfixE (Just a) (VarE '(<*>)) (Just (VarE 'arbitrary))
103
      constr = AppE (VarE 'pure) (ConE name)
104
  in foldl (\a _ -> infix_arb a) constr types
105

    
106
-- | Extracts the name and the types from a constructor.
107
conInfo :: Con -> (Name, [Type])
108
conInfo (NormalC name t)     = (name, map snd t)
109
conInfo (RecC    name t)     = (name, map (\(_, _, x) -> x) t)
110
conInfo (InfixC t1 name t2)  = (name, [snd t1, snd t2])
111
conInfo (ForallC _ _ subcon) = conInfo subcon
112

    
113
-- | Builds an arbitrary instance for a regular data type (i.e. not Bounded).
114
mkRegularArbitrary :: Name -> [Con] -> Q [Dec]
115
mkRegularArbitrary name cons = do
116
  expr <- case cons of
117
            [] -> fail "Can't make Arbitrary instance for an empty data type"
118
            [x] -> return $ mkConsArbitrary (conInfo x)
119
            xs -> appE (varE 'oneof) $
120
                  listE (map (return . mkConsArbitrary . conInfo) xs)
121
  return [InstanceD [] (AppT (ConT ''Arbitrary) (ConT name))
122
          [ValD (VarP 'arbitrary) (NormalB expr) []]]
123

    
124
-- | Builds a default Arbitrary instance for a type. This requires
125
-- that all members are of types that already have Arbitrary
126
-- instances, and that the arbitrary instances are well behaved
127
-- (w.r.t. recursive data structures, or similar concerns). In that
128
-- sense, this is not appropriate for all data types, just those that
129
-- are simple but very repetitive or have many simple fields.
130
genArbitrary :: Name -> Q [Dec]
131
genArbitrary name = do
132
  r <- reify name
133
  case r of
134
    TyConI (DataD _ _ _ cons _) ->
135
      mkRegularArbitrary name cons
136
    TyConI (NewtypeD _ _ _ con _) ->
137
      mkRegularArbitrary name [con]
138
    TyConI (TySynD _ _ (ConT tn)) -> genArbitrary tn
139
    _ -> fail $ "Invalid type in call to genArbitrary for " ++ show name
140
         ++ ", type " ++ show r