Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / THH / PyRPC.hs @ 857a05fe

History | View | Annotate | Download (6.3 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 t                     = do
102
      report False $ "Don't know how to make a Python variable name from "
103
                     ++ show t ++ "; using a numbered one."
104
      return $ text ('_' : show idx)
105

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

    
111
    lowerFirstNameQ :: Name -> Q Doc
112
    lowerFirstNameQ = return . text . lowerFirst . nameBase
113

    
114
-- | Creates a method declaration by inspecting (reifying) Haskell's function
115
-- name.
116
nameToFunc :: Name -> Q Doc
117
nameToFunc name = do
118
    (as, _) <- funArgs `liftM` typeOfFun name
119
    -- If the function has just one argument, try if it isn't a tuple;
120
    -- if not, use the arguments as they are.
121
    let as' = fromMaybe as $ case as of
122
                                [t] -> tupleArgs t -- TODO CHECK!
123
                                _   -> Nothing
124
    toFunc (upperFirst $ nameBase name) as'
125

    
126
-- | Generates a Python class stub, given a class name, the list of Haskell
127
-- functions to expose as methods, and a optionally a piece of code to
128
-- include.
129
namesToClass
130
  :: String       -- ^ the class name
131
  -> Doc          -- ^ Python code to include in the class
132
  -> [Name]       -- ^ the list of functions to include
133
  -> Q Doc
134
namesToClass cname pycode fns = do
135
  fnsCode <- mapM (liftM ($+$ emptyLine) . nameToFunc) fns
136
  return $ vcat [ text "class" <+> apply cname [text "object"] <> colon
137
                , nest' (
138
                    pycode $+$ vcat fnsCode
139
                  )
140
                ]
141

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

    
170
-- The same as 'genPyUDSRpcStub', but returns the result as a @String@
171
-- expression.
172
genPyUDSRpcStubStr
173
  :: String   -- ^ the name of the class to be generated
174
  -> String   -- ^ the constant in @pathutils.py@ holding the socket path
175
  -> [Name]   -- ^ functions to include
176
  -> Q Exp
177
genPyUDSRpcStubStr className constName names =
178
    liftString . render =<< genPyUDSRpcStub className constName names