root / htest / Test / Ganeti / TestHelper.hs @ 22381768
History | View | Annotate | Download (4.7 kB)
1 | 23fe06c2 | Iustin Pop | {-# LANGUAGE TemplateHaskell #-} |
---|---|---|---|
2 | 23fe06c2 | Iustin Pop | |
3 | ff247692 | Michele Tartara | {-| Unittest helpers for TemplateHaskell components. |
4 | 23fe06c2 | Iustin Pop | |
5 | 23fe06c2 | Iustin Pop | -} |
6 | 23fe06c2 | Iustin Pop | |
7 | 23fe06c2 | Iustin Pop | {- |
8 | 23fe06c2 | Iustin Pop | |
9 | 95f6c931 | Iustin Pop | Copyright (C) 2011, 2012 Google Inc. |
10 | 23fe06c2 | Iustin Pop | |
11 | 23fe06c2 | Iustin Pop | This program is free software; you can redistribute it and/or modify |
12 | 23fe06c2 | Iustin Pop | it under the terms of the GNU General Public License as published by |
13 | 23fe06c2 | Iustin Pop | the Free Software Foundation; either version 2 of the License, or |
14 | 23fe06c2 | Iustin Pop | (at your option) any later version. |
15 | 23fe06c2 | Iustin Pop | |
16 | 23fe06c2 | Iustin Pop | This program is distributed in the hope that it will be useful, but |
17 | 23fe06c2 | Iustin Pop | WITHOUT ANY WARRANTY; without even the implied warranty of |
18 | 23fe06c2 | Iustin Pop | MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU |
19 | 23fe06c2 | Iustin Pop | General Public License for more details. |
20 | 23fe06c2 | Iustin Pop | |
21 | 23fe06c2 | Iustin Pop | You should have received a copy of the GNU General Public License |
22 | 23fe06c2 | Iustin Pop | along with this program; if not, write to the Free Software |
23 | 23fe06c2 | Iustin Pop | Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA |
24 | 23fe06c2 | Iustin Pop | 02110-1301, USA. |
25 | 23fe06c2 | Iustin Pop | |
26 | 23fe06c2 | Iustin Pop | -} |
27 | 23fe06c2 | Iustin Pop | |
28 | e4cc4c11 | Iustin Pop | module Test.Ganeti.TestHelper |
29 | ebf38064 | Iustin Pop | ( testSuite |
30 | 8492daa3 | Iustin Pop | , genArbitrary |
31 | ebf38064 | Iustin Pop | ) where |
32 | 23fe06c2 | Iustin Pop | |
33 | 8492daa3 | Iustin Pop | import Control.Applicative |
34 | 6dd92942 | Iustin Pop | import Data.List (stripPrefix, isPrefixOf) |
35 | 95f6c931 | Iustin Pop | import Data.Maybe (fromMaybe) |
36 | 95f6c931 | Iustin Pop | import Test.Framework |
37 | 6dd92942 | Iustin Pop | import Test.Framework.Providers.HUnit |
38 | 95f6c931 | Iustin Pop | import Test.Framework.Providers.QuickCheck2 |
39 | 6dd92942 | Iustin Pop | import Test.HUnit (Assertion) |
40 | 6dd92942 | Iustin Pop | import Test.QuickCheck |
41 | 23fe06c2 | Iustin Pop | import Language.Haskell.TH |
42 | 23fe06c2 | Iustin Pop | |
43 | 20bc5360 | Iustin Pop | -- | Test property prefix. |
44 | 20bc5360 | Iustin Pop | propPrefix :: String |
45 | 20bc5360 | Iustin Pop | propPrefix = "prop_" |
46 | 20bc5360 | Iustin Pop | |
47 | 20bc5360 | Iustin Pop | -- | Test case prefix. |
48 | 20bc5360 | Iustin Pop | casePrefix :: String |
49 | 20bc5360 | Iustin Pop | casePrefix = "case_" |
50 | 20bc5360 | Iustin Pop | |
51 | 95f6c931 | Iustin Pop | -- | Tries to drop a prefix from a string. |
52 | 95f6c931 | Iustin Pop | simplifyName :: String -> String -> String |
53 | 95f6c931 | Iustin Pop | simplifyName pfx string = fromMaybe string (stripPrefix pfx string) |
54 | 23fe06c2 | Iustin Pop | |
55 | 6dd92942 | Iustin Pop | -- | Builds a test from a QuickCheck property. |
56 | 20bc5360 | Iustin Pop | runProp :: Testable prop => String -> prop -> Test |
57 | 20bc5360 | Iustin Pop | runProp = testProperty . simplifyName propPrefix |
58 | 6dd92942 | Iustin Pop | |
59 | 6dd92942 | Iustin Pop | -- | Builds a test for a HUnit test case. |
60 | 20bc5360 | Iustin Pop | runCase :: String -> Assertion -> Test |
61 | 20bc5360 | Iustin Pop | runCase = testCase . simplifyName casePrefix |
62 | 6dd92942 | Iustin Pop | |
63 | 6dd92942 | Iustin Pop | -- | Runs the correct test provider for a given test, based on its |
64 | 6dd92942 | Iustin Pop | -- name (not very nice, but...). |
65 | 20bc5360 | Iustin Pop | run :: Name -> Q Exp |
66 | 20bc5360 | Iustin Pop | run name = |
67 | 6dd92942 | Iustin Pop | let str = nameBase name |
68 | 6dd92942 | Iustin Pop | nameE = varE name |
69 | 6dd92942 | Iustin Pop | strE = litE (StringL str) |
70 | 6dd92942 | Iustin Pop | in case () of |
71 | 20bc5360 | Iustin Pop | _ | propPrefix `isPrefixOf` str -> [| runProp $strE $nameE |] |
72 | 20bc5360 | Iustin Pop | | casePrefix `isPrefixOf` str -> [| runCase $strE $nameE |] |
73 | 6dd92942 | Iustin Pop | | otherwise -> fail $ "Unsupported test function name '" ++ str ++ "'" |
74 | 95f6c931 | Iustin Pop | |
75 | e09c1fa0 | Iustin Pop | -- | Convert slashes in a name to underscores. |
76 | e09c1fa0 | Iustin Pop | mapSlashes :: String -> String |
77 | e09c1fa0 | Iustin Pop | mapSlashes = map (\c -> if c == '/' then '_' else c) |
78 | e09c1fa0 | Iustin Pop | |
79 | 95f6c931 | Iustin Pop | -- | Builds a test suite. |
80 | 23fe06c2 | Iustin Pop | testSuite :: String -> [Name] -> Q [Dec] |
81 | 23fe06c2 | Iustin Pop | testSuite tsname tdef = do |
82 | e09c1fa0 | Iustin Pop | let fullname = mkName $ "test" ++ mapSlashes tsname |
83 | 20bc5360 | Iustin Pop | tests <- mapM run tdef |
84 | f842aecd | Iustin Pop | sigtype <- [t| Test |] |
85 | f842aecd | Iustin Pop | body <- [| testGroup $(litE $ stringL tsname) $(return $ ListE tests) |] |
86 | 05ff7a00 | Agata Murawska | return [ SigD fullname sigtype |
87 | f842aecd | Iustin Pop | , ValD (VarP fullname) (NormalB body) [] |
88 | 05ff7a00 | Agata Murawska | ] |
89 | 8492daa3 | Iustin Pop | |
90 | 8492daa3 | Iustin Pop | -- | Builds an arbitrary value for a given constructor. This doesn't |
91 | 8492daa3 | Iustin Pop | -- use the actual types of the fields, since we expect arbitrary |
92 | 8492daa3 | Iustin Pop | -- instances for all of the types anyway, we only care about the |
93 | 8492daa3 | Iustin Pop | -- number of fields. |
94 | 8492daa3 | Iustin Pop | mkConsArbitrary :: (Name, [a]) -> Exp |
95 | 8492daa3 | Iustin Pop | mkConsArbitrary (name, types) = |
96 | 8492daa3 | Iustin Pop | let infix_arb a = InfixE (Just a) (VarE '(<*>)) (Just (VarE 'arbitrary)) |
97 | 8492daa3 | Iustin Pop | constr = AppE (VarE 'pure) (ConE name) |
98 | 5b11f8db | Iustin Pop | in foldl (\a _ -> infix_arb a) constr types |
99 | 8492daa3 | Iustin Pop | |
100 | 8492daa3 | Iustin Pop | -- | Extracts the name and the types from a constructor. |
101 | 8492daa3 | Iustin Pop | conInfo :: Con -> (Name, [Type]) |
102 | 8492daa3 | Iustin Pop | conInfo (NormalC name t) = (name, map snd t) |
103 | 8492daa3 | Iustin Pop | conInfo (RecC name t) = (name, map (\(_, _, x) -> x) t) |
104 | 8492daa3 | Iustin Pop | conInfo (InfixC t1 name t2) = (name, [snd t1, snd t2]) |
105 | 8492daa3 | Iustin Pop | conInfo (ForallC _ _ subcon) = conInfo subcon |
106 | 8492daa3 | Iustin Pop | |
107 | 8492daa3 | Iustin Pop | -- | Builds an arbitrary instance for a regular data type (i.e. not Bounded). |
108 | 8492daa3 | Iustin Pop | mkRegularArbitrary :: Name -> [Con] -> Q [Dec] |
109 | 8492daa3 | Iustin Pop | mkRegularArbitrary name cons = do |
110 | 8492daa3 | Iustin Pop | expr <- case cons of |
111 | 5b11f8db | Iustin Pop | [] -> fail "Can't make Arbitrary instance for an empty data type" |
112 | 8492daa3 | Iustin Pop | [x] -> return $ mkConsArbitrary (conInfo x) |
113 | 8492daa3 | Iustin Pop | xs -> appE (varE 'oneof) $ |
114 | 8492daa3 | Iustin Pop | listE (map (return . mkConsArbitrary . conInfo) xs) |
115 | 8492daa3 | Iustin Pop | return [InstanceD [] (AppT (ConT ''Arbitrary) (ConT name)) |
116 | 8492daa3 | Iustin Pop | [ValD (VarP 'arbitrary) (NormalB expr) []]] |
117 | 8492daa3 | Iustin Pop | |
118 | 8492daa3 | Iustin Pop | -- | Builds a default Arbitrary instance for a type. This requires |
119 | 8492daa3 | Iustin Pop | -- that all members are of types that already have Arbitrary |
120 | 8492daa3 | Iustin Pop | -- instances, and that the arbitrary instances are well behaved |
121 | 8492daa3 | Iustin Pop | -- (w.r.t. recursive data structures, or similar concerns). In that |
122 | 8492daa3 | Iustin Pop | -- sense, this is not appropriate for all data types, just those that |
123 | 8492daa3 | Iustin Pop | -- are simple but very repetitive or have many simple fields. |
124 | 8492daa3 | Iustin Pop | genArbitrary :: Name -> Q [Dec] |
125 | 8492daa3 | Iustin Pop | genArbitrary name = do |
126 | 8492daa3 | Iustin Pop | r <- reify name |
127 | 8492daa3 | Iustin Pop | case r of |
128 | 8492daa3 | Iustin Pop | TyConI (DataD _ _ _ cons _) -> |
129 | 8492daa3 | Iustin Pop | mkRegularArbitrary name cons |
130 | 8492daa3 | Iustin Pop | TyConI (NewtypeD _ _ _ con _) -> |
131 | 8492daa3 | Iustin Pop | mkRegularArbitrary name [con] |
132 | 8492daa3 | Iustin Pop | TyConI (TySynD _ _ (ConT tn)) -> genArbitrary tn |
133 | 8492daa3 | Iustin Pop | _ -> fail $ "Invalid type in call to genArbitrary for " ++ show name |
134 | 8492daa3 | Iustin Pop | ++ ", type " ++ show r |