Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / THH / PyRPC.hs @ dee434c2

History | View | Annotate | Download (6.7 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# OPTIONS_GHC -fno-warn-warnings-deprecations #-}
3

    
4
{-| Combines the construction of RPC server components and their Python stubs.
5

    
6
-}
7

    
8
{-
9

    
10
Copyright (C) 2013 Google Inc.
11

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

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

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

    
27
-}
28

    
29
module Ganeti.THH.PyRPC
30
  ( genPyUDSRpcStub
31
  , genPyUDSRpcStubStr
32
  ) where
33

    
34
import Control.Monad
35
import Data.Char (toLower, toUpper)
36
import Data.Functor
37
import Data.Maybe (fromMaybe)
38
import Language.Haskell.TH
39
import Language.Haskell.TH.Syntax (liftString)
40
import Text.PrettyPrint
41

    
42
import Ganeti.THH.Types
43

    
44
-- | The indentation step in generated Python files.
45
pythonIndentStep :: Int
46
pythonIndentStep = 2
47

    
48
-- | A helper function that nests a block of generated output by the default
49
-- step (see 'pythonIndentStep').
50
nest' :: Doc -> Doc
51
nest' = nest pythonIndentStep
52

    
53
-- | The name of an abstract function to which all method in a Python stub
54
-- are forwarded to.
55
genericInvokeName :: String
56
genericInvokeName = "_GenericInvoke"
57

    
58
-- | The name of a function that returns the socket path for reaching the
59
-- appropriate RPC client.
60
socketPathName :: String
61
socketPathName = "_GetSocketPath"
62

    
63
-- | Create a Python expression that applies a given function to a list of
64
-- given expressions
65
apply :: String -> [Doc] -> Doc
66
apply name as = text name <> parens (hcat $ punctuate (text ", ") as)
67

    
68
-- | An empty line block.
69
emptyLine :: Doc
70
emptyLine = text "" -- apparently using 'empty' doesn't work
71

    
72
lowerFirst :: String -> String
73
lowerFirst (x:xs) = toLower x : xs
74
lowerFirst []     = []
75

    
76
upperFirst :: String -> String
77
upperFirst (x:xs) = toUpper x : xs
78
upperFirst []     = []
79

    
80
-- | Creates a method declaration given a function name and a list of
81
-- Haskell types corresponding to its arguments.
82
toFunc :: String -> [Type] -> Q Doc
83
toFunc fname as = do
84
    args <- zipWithM varName [1..] as
85
    let args' = text "self" : args
86
        callName = lowerFirst fname
87
    return $ (text "def" <+> apply fname args') <> colon $+$
88
             nest' (text "return" <+>
89
                    text "self." <>
90
                    apply genericInvokeName (text (show callName) : args)
91
             )
92
  where
93
    -- | Create a name for a method argument, given its index position
94
    -- and Haskell type.
95
    varName :: Int -> Type -> Q Doc
96
    varName _   (VarT n)              = lowerFirstNameQ n
97
    varName _   (ConT n)              = lowerFirstNameQ n
98
    varName idx (AppT ListT t)        = listOf idx t
99
    varName idx (AppT (ConT n) t)
100
      | n == ''[]                     = listOf idx t
101
    varName idx (AppT (AppT (TupleT 2) t) t')
102
                                      = pairOf idx t t'
103
    varName idx (AppT (AppT (ConT n) t) t')
104
      | n == ''(,)                    = pairOf idx t t'
105
    varName idx t                     = do
106
      report False $ "Don't know how to make a Python variable name from "
107
                     ++ show t ++ "; using a numbered one."
108
      return $ text ('_' : show idx)
109

    
110
    -- | Create a name for a method argument, knowing that its a list of
111
    -- a given type.
112
    listOf :: Int -> Type -> Q Doc
113
    listOf idx t = (<> text "List") <$> varName idx t
114

    
115
    -- | Create a name for a method argument, knowing that its a pair of
116
    -- the given types.
117
    pairOf :: Int -> Type -> Type -> Q Doc
118
    pairOf idx t t' = do
119
      tn <- varName idx t
120
      tn' <- varName idx t'
121
      return $ tn <> text "_" <> tn' <> text "_Pair"
122

    
123
    lowerFirstNameQ :: Name -> Q Doc
124
    lowerFirstNameQ = return . text . lowerFirst . nameBase
125

    
126
-- | Creates a method declaration by inspecting (reifying) Haskell's function
127
-- name.
128
nameToFunc :: Name -> Q Doc
129
nameToFunc name = do
130
    (as, _) <- funArgs `liftM` typeOfFun name
131
    -- If the function has just one argument, try if it isn't a tuple;
132
    -- if not, use the arguments as they are.
133
    let as' = fromMaybe as $ case as of
134
                                [t] -> tupleArgs t -- TODO CHECK!
135
                                _   -> Nothing
136
    toFunc (upperFirst $ nameBase name) as'
137

    
138
-- | Generates a Python class stub, given a class name, the list of Haskell
139
-- functions to expose as methods, and a optionally a piece of code to
140
-- include.
141
namesToClass
142
  :: String       -- ^ the class name
143
  -> Doc          -- ^ Python code to include in the class
144
  -> [Name]       -- ^ the list of functions to include
145
  -> Q Doc
146
namesToClass cname pycode fns = do
147
  fnsCode <- mapM (liftM ($+$ emptyLine) . nameToFunc) fns
148
  return $ vcat [ text "class" <+> apply cname [text "object"] <> colon
149
                , nest' (
150
                    pycode $+$ vcat fnsCode
151
                  )
152
                ]
153

    
154
-- | Takes a list of function names and creates a RPC handler that delegates
155
-- calls to them, as well as writes out the corresponding Python stub.
156
--
157
-- See 'mkRpcM' for the requirements on the passed functions and the returned
158
-- expression.
159
genPyUDSRpcStub
160
  :: String     -- ^ the name of the class to be generated
161
  -> String     -- ^ the name of the constant from @constants.py@ holding
162
                --   the path to a UDS socket
163
  -> [Name]     -- ^ names of functions to include
164
  -> Q Doc
165
genPyUDSRpcStub className constName = liftM (header $+$) .
166
                                      namesToClass className stubCode
167
  where
168
    header = text "# This file is automatically generated, do not edit!" $+$
169
             text "# pylint: disable-all"
170
    stubCode =
171
      abstrMethod genericInvokeName [ text "method", text "*args"] $+$
172
      method socketPathName [] (
173
         text "from ganeti import pathutils" $+$
174
         text "return" <+> text "pathutils." <> text constName)
175
    method name args body =
176
      text "def" <+> apply name (text "self" : args) <> colon $+$
177
      nest' body $+$
178
      emptyLine
179
    abstrMethod name args = method name args $
180
      text "raise" <+> apply "NotImplementedError" []
181

    
182
-- The same as 'genPyUDSRpcStub', but returns the result as a @String@
183
-- expression.
184
genPyUDSRpcStubStr
185
  :: String   -- ^ the name of the class to be generated
186
  -> String   -- ^ the constant in @pathutils.py@ holding the socket path
187
  -> [Name]   -- ^ functions to include
188
  -> Q Exp
189
genPyUDSRpcStubStr className constName names =
190
    liftString . render =<< genPyUDSRpcStub className constName names