Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / THH.hs @ e9aaa3c6

History | View | Annotate | Download (6 kB)

1
{-# LANGUAGE TemplateHaskell, QuasiQuotes #-}
2

    
3
{-| TemplateHaskell helper for HTools.
4

    
5
As TemplateHaskell require that splices be defined in a separate
6
module, we combine all the TemplateHaskell functionality that HTools
7
needs in this module (except the one for unittests).
8

    
9
-}
10

    
11
{-
12

    
13
Copyright (C) 2011 Google Inc.
14

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

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

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

    
30
-}
31

    
32
module Ganeti.THH ( declareSADT
33
                  , makeJSONInstance
34
                  ) where
35

    
36
import Data.Char
37
import Language.Haskell.TH
38

    
39
import qualified Text.JSON as JSON
40

    
41
-- | Ensure first letter is lowercase.
42
--
43
-- Used to convert type name to function prefix, e.g. in @data Aa ->
44
-- aaToString@.
45
ensureLower :: String -> String
46
ensureLower [] = []
47
ensureLower (x:xs) = toLower x:xs
48

    
49
-- | ToString function name.
50
toStrName :: String -> Name
51
toStrName = mkName . (++ "ToString") . ensureLower
52

    
53
-- | FromString function name.
54
fromStrName :: String -> Name
55
fromStrName = mkName . (++ "FromString") . ensureLower
56

    
57
-- | Generates a data type declaration.
58
--
59
-- The type will have a fixed list of instances.
60
strADTDecl :: Name -> [String] -> Dec
61
strADTDecl name constructors =
62
    DataD [] name []
63
              (map (flip NormalC [] . mkName) constructors)
64
              [''Show, ''Read, ''Eq, ''Enum, ''Bounded, ''Ord]
65

    
66
-- | Generates a toString function.
67
--
68
-- This generates a simple function of the form:
69
--
70
-- @
71
-- nameToString :: Name -> String
72
-- nameToString Cons1 = var1
73
-- nameToString Cons2 = \"value2\"
74
-- @
75
genToString :: Name -> Name -> [(String, Name)] -> Q [Dec]
76
genToString fname tname constructors = do
77
  sigt <- [t| $(conT tname) -> String |]
78
  -- the body clauses, matching on the constructor and returning the
79
  -- string value
80
  clauses <- mapM  (\(c, v) -> clause [recP (mkName c) []]
81
                             (normalB (varE  v)) []) constructors
82
  return [SigD fname sigt, FunD fname clauses]
83

    
84
-- | Generates a fromString function.
85
--
86
-- The function generated is monadic and can fail parsing the
87
-- string. It is of the form:
88
--
89
-- @
90
-- nameFromString :: (Monad m) => String -> m Name
91
-- nameFromString s | s == var1       = Cons1
92
--                  | s == \"value2\" = Cons2
93
--                  | otherwise = fail /.../
94
-- @
95
genFromString :: Name -> Name -> [(String, Name)] -> Q [Dec]
96
genFromString fname tname constructors = do
97
  -- signature of form (Monad m) => String -> m $name
98
  sigt <- [t| (Monad m) => String -> m $(conT tname) |]
99
  -- clauses for a guarded pattern
100
  let varp = mkName "s"
101
      varpe = varE varp
102
  clauses <- mapM (\(c, v) -> do
103
                     -- the clause match condition
104
                     g <- normalG [| $varpe == $(varE v) |]
105
                     -- the clause result
106
                     r <- [| return $(conE (mkName c)) |]
107
                     return (g, r)) constructors
108
  -- the otherwise clause (fallback)
109
  oth_clause <- do
110
    g <- normalG [| otherwise |]
111
    r <- [|fail ("Invalid string value for type " ++
112
                 $(litE (stringL (nameBase tname))) ++ ": " ++ $varpe) |]
113
    return (g, r)
114
  let fun = FunD fname [Clause [VarP varp]
115
                        (GuardedB (clauses++[oth_clause])) []]
116
  return [SigD fname sigt, fun]
117

    
118
-- | Generates a data type from a given string format.
119
--
120
-- The format is expected to multiline. The first line contains the
121
-- type name, and the rest of the lines must contain two words: the
122
-- constructor name and then the string representation of the
123
-- respective constructor.
124
--
125
-- The function will generate the data type declaration, and then two
126
-- functions:
127
--
128
-- * /name/ToString, which converts the type to a string
129
--
130
-- * /name/FromString, which (monadically) converts from a string to the type
131
--
132
-- Note that this is basically just a custom show/read instance,
133
-- nothing else.
134
declareSADT :: String -> [(String, Name)] -> Q [Dec]
135
declareSADT sname cons = do
136
  let name = mkName sname
137
      ddecl = strADTDecl name (map fst cons)
138
  tostr <- genToString (toStrName sname) name cons
139
  fromstr <- genFromString (fromStrName sname) name cons
140
  return $ ddecl:tostr ++ fromstr
141

    
142

    
143
-- | Creates the showJSON member of a JSON instance declaration.
144
--
145
-- This will create what is the equivalent of:
146
--
147
-- @
148
-- showJSON = showJSON . /name/ToString
149
-- @
150
--
151
-- in an instance JSON /name/ declaration
152
genShowJSON :: String -> Q [Dec]
153
genShowJSON name = [d| showJSON = JSON.showJSON . $(varE (toStrName name)) |]
154

    
155
-- | Creates the readJSON member of a JSON instance declaration.
156
--
157
-- This will create what is the equivalent of:
158
--
159
-- @
160
-- readJSON s = case readJSON s of
161
--                Ok s' -> /name/FromString s'
162
--                Error e -> Error /description/
163
-- @
164
--
165
-- in an instance JSON /name/ declaration
166
genReadJSON :: String -> Q Dec
167
genReadJSON name = do
168
  let s = mkName "s"
169
  body <- [| case JSON.readJSON $(varE s) of
170
               JSON.Ok s' -> $(varE (fromStrName name)) s'
171
               JSON.Error e ->
172
                   JSON.Error $ "Can't parse string value for type " ++
173
                           $(litE (StringL name)) ++ ": " ++ e
174
           |]
175
  return $ FunD (mkName "readJSON") [Clause [VarP s] (NormalB body) []]
176

    
177
-- | Generates a JSON instance for a given type.
178
--
179
-- This assumes that the /name/ToString and /name/FromString functions
180
-- have been defined as by the 'declareSADT' function.
181
makeJSONInstance :: Name -> Q [Dec]
182
makeJSONInstance name = do
183
  let base = nameBase name
184
  showJ <- genShowJSON base
185
  readJ <- genReadJSON base
186
  return [InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name)) (readJ:showJ)]