Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / HTools / QCHelper.hs @ 23fe06c2

History | View | Annotate | Download (1.4 kB)

1 23fe06c2 Iustin Pop
{-# LANGUAGE TemplateHaskell #-}
2 23fe06c2 Iustin Pop
3 23fe06c2 Iustin Pop
{-| Unittest helpers for ganeti-htools
4 23fe06c2 Iustin Pop
5 23fe06c2 Iustin Pop
-}
6 23fe06c2 Iustin Pop
7 23fe06c2 Iustin Pop
{-
8 23fe06c2 Iustin Pop
9 23fe06c2 Iustin Pop
Copyright (C) 2011 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 23fe06c2 Iustin Pop
module Ganeti.HTools.QCHelper
29 23fe06c2 Iustin Pop
    ( testSuite
30 23fe06c2 Iustin Pop
    ) where
31 23fe06c2 Iustin Pop
32 23fe06c2 Iustin Pop
import Test.QuickCheck
33 23fe06c2 Iustin Pop
import Language.Haskell.TH
34 23fe06c2 Iustin Pop
35 23fe06c2 Iustin Pop
run :: Testable prop => prop -> Args -> IO Result
36 23fe06c2 Iustin Pop
run = flip quickCheckWithResult
37 23fe06c2 Iustin Pop
38 23fe06c2 Iustin Pop
testSuite :: String -> [Name] -> Q [Dec]
39 23fe06c2 Iustin Pop
testSuite tsname tdef = do
40 23fe06c2 Iustin Pop
  let fullname = mkName $ "test" ++ tsname
41 23fe06c2 Iustin Pop
  tests <- mapM (\n -> [| (run $(varE n), $(litE . StringL . nameBase $ n)) |])
42 23fe06c2 Iustin Pop
           tdef
43 23fe06c2 Iustin Pop
  sigtype <- [t| (String, [(Args -> IO Result, String)]) |]
44 23fe06c2 Iustin Pop
  return $ [ SigD fullname sigtype
45 23fe06c2 Iustin Pop
           , ValD (VarP fullname) (NormalB (TupE [LitE (StringL tsname),
46 23fe06c2 Iustin Pop
                                                  ListE tests])) []
47 23fe06c2 Iustin Pop
           ]