Statistics
| Branch: | Tag: | Revision:

root / htools / Ganeti / THH.hs @ 6111e296

History | View | Annotate | Download (7.4 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
                  , genOpID
35
                  ) where
36

    
37
import Control.Monad (liftM)
38
import Data.Char
39
import Data.List
40
import Language.Haskell.TH
41

    
42
import qualified Text.JSON as JSON
43

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

    
52
-- | ToString function name.
53
toStrName :: String -> Name
54
toStrName = mkName . (++ "ToString") . ensureLower
55

    
56
-- | FromString function name.
57
fromStrName :: String -> Name
58
fromStrName = mkName . (++ "FromString") . ensureLower
59

    
60
-- | Converts a name to it's varE/litE representations.
61
--
62
reprE :: Either String Name -> Q Exp
63
reprE (Left name) = litE (StringL name)
64
reprE (Right name) = varE name
65

    
66
-- | Generates a data type declaration.
67
--
68
-- The type will have a fixed list of instances.
69
strADTDecl :: Name -> [String] -> Dec
70
strADTDecl name constructors =
71
    DataD [] name []
72
              (map (flip NormalC [] . mkName) constructors)
73
              [''Show, ''Read, ''Eq, ''Enum, ''Bounded, ''Ord]
74

    
75
-- | Generates a toString function.
76
--
77
-- This generates a simple function of the form:
78
--
79
-- @
80
-- nameToString :: Name -> String
81
-- nameToString Cons1 = var1
82
-- nameToString Cons2 = \"value2\"
83
-- @
84
genToString :: Name -> Name -> [(String, Either String Name)] -> Q [Dec]
85
genToString fname tname constructors = do
86
  sigt <- [t| $(conT tname) -> String |]
87
  -- the body clauses, matching on the constructor and returning the
88
  -- string value
89
  clauses <- mapM  (\(c, v) -> clause [recP (mkName c) []]
90
                             (normalB (reprE v)) []) constructors
91
  return [SigD fname sigt, FunD fname clauses]
92

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

    
127
-- | Generates a data type from a given string format.
128
--
129
-- The format is expected to multiline. The first line contains the
130
-- type name, and the rest of the lines must contain two words: the
131
-- constructor name and then the string representation of the
132
-- respective constructor.
133
--
134
-- The function will generate the data type declaration, and then two
135
-- functions:
136
--
137
-- * /name/ToString, which converts the type to a string
138
--
139
-- * /name/FromString, which (monadically) converts from a string to the type
140
--
141
-- Note that this is basically just a custom show/read instance,
142
-- nothing else.
143
declareSADT :: String -> [(String, Name)] -> Q [Dec]
144
declareSADT sname cons = do
145
  let name = mkName sname
146
      ddecl = strADTDecl name (map fst cons)
147
      -- process cons in the format expected by genToString
148
      cons' = map (\(a, b) -> (a, Right b)) cons
149
  tostr <- genToString (toStrName sname) name cons'
150
  fromstr <- genFromString (fromStrName sname) name cons
151
  return $ ddecl:tostr ++ fromstr
152

    
153

    
154
-- | Creates the showJSON member of a JSON instance declaration.
155
--
156
-- This will create what is the equivalent of:
157
--
158
-- @
159
-- showJSON = showJSON . /name/ToString
160
-- @
161
--
162
-- in an instance JSON /name/ declaration
163
genShowJSON :: String -> Q [Dec]
164
genShowJSON name = [d| showJSON = JSON.showJSON . $(varE (toStrName name)) |]
165

    
166
-- | Creates the readJSON member of a JSON instance declaration.
167
--
168
-- This will create what is the equivalent of:
169
--
170
-- @
171
-- readJSON s = case readJSON s of
172
--                Ok s' -> /name/FromString s'
173
--                Error e -> Error /description/
174
-- @
175
--
176
-- in an instance JSON /name/ declaration
177
genReadJSON :: String -> Q Dec
178
genReadJSON name = do
179
  let s = mkName "s"
180
  body <- [| case JSON.readJSON $(varE s) of
181
               JSON.Ok s' -> $(varE (fromStrName name)) s'
182
               JSON.Error e ->
183
                   JSON.Error $ "Can't parse string value for type " ++
184
                           $(litE (StringL name)) ++ ": " ++ e
185
           |]
186
  return $ FunD (mkName "readJSON") [Clause [VarP s] (NormalB body) []]
187

    
188
-- | Generates a JSON instance for a given type.
189
--
190
-- This assumes that the /name/ToString and /name/FromString functions
191
-- have been defined as by the 'declareSADT' function.
192
makeJSONInstance :: Name -> Q [Dec]
193
makeJSONInstance name = do
194
  let base = nameBase name
195
  showJ <- genShowJSON base
196
  readJ <- genReadJSON base
197
  return [InstanceD [] (AppT (ConT ''JSON.JSON) (ConT name)) (readJ:showJ)]
198

    
199
-- | Transforms a CamelCase string into an_underscore_based_one.
200
deCamelCase :: String -> String
201
deCamelCase =
202
    intercalate "_" . map (map toUpper) . groupBy (\_ b -> not $ isUpper b)
203

    
204
-- | Computes the name of a given constructor
205
constructorName :: Con -> Q Name
206
constructorName (NormalC name _) = return name
207
constructorName (RecC name _)    = return name
208
constructorName x                = fail $ "Unhandled constructor " ++ show x
209

    
210
-- | Builds the constructor-to-string function.
211
--
212
-- This generates a simple function of the following form:
213
--
214
-- @
215
-- fname (ConStructorOne {}) = "CON_STRUCTOR_ONE"
216
-- fname (ConStructorTwo {}) = "CON_STRUCTOR_TWO"
217
-- @
218
--
219
-- This builds a custom list of name/string pairs and then uses
220
-- 'genToString' to actually generate the function
221
genOpID :: Name -> String -> Q [Dec]
222
genOpID name fname = do
223
  TyConI (DataD _ _ _ cons _) <- reify name
224
  cnames <- mapM (liftM nameBase . constructorName) cons
225
  let svalues = map (Left . deCamelCase) cnames
226
  genToString (mkName fname) name $ zip cnames svalues