Statistics
| Branch: | Tag: | Revision:

root / Ganeti / Luxi.hs @ a1b5eeaf

History | View | Annotate | Download (4.8 kB)

1
{-| Implementation of the Ganeti LUXI interface.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2009 Google Inc.
8

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

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

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

    
24
-}
25

    
26
module Ganeti.Luxi
27
    ( LuxiOp(..)
28
    , Client
29
    , getClient
30
    , closeClient
31
    , callMethod
32
    ) where
33

    
34
import Data.List
35
import Data.IORef
36
import Control.Monad
37
import Text.JSON (JSObject, JSValue, toJSObject, encodeStrict, decodeStrict)
38
import qualified Text.JSON as J
39
import Text.JSON.Types
40
import System.Timeout
41
import qualified Network.Socket as S
42

    
43
import Ganeti.HTools.Utils
44
import Ganeti.HTools.Types
45

    
46
-- * Utility functions
47

    
48
-- | Wrapper over System.Timeout.timeout that fails in the IO monad.
49
withTimeout :: Int -> String -> IO a -> IO a
50
withTimeout secs descr action = do
51
    result <- timeout (secs * 1000000) action
52
    (case result of
53
       Nothing -> fail $ "Timeout in " ++ descr
54
       Just v -> return v)
55

    
56
-- * Generic protocol functionality
57

    
58
-- | Currently supported Luxi operations.
59
data LuxiOp = QueryInstances
60
            | QueryNodes
61
            | QueryJobs
62
            | SubmitManyJobs
63

    
64
-- | The serialisation of LuxiOps into strings in messages.
65
strOfOp :: LuxiOp -> String
66
strOfOp QueryNodes = "QueryNodes"
67
strOfOp QueryInstances = "QueryInstances"
68
strOfOp QueryJobs = "QueryJobs"
69
strOfOp SubmitManyJobs = "SubmitManyJobs"
70

    
71
-- | The end-of-message separator.
72
eOM :: Char
73
eOM = '\3'
74

    
75
-- | Valid keys in the requests and responses.
76
data MsgKeys = Method
77
             | Args
78
             | Success
79
             | Result
80

    
81
-- | The serialisation of MsgKeys into strings in messages.
82
strOfKey :: MsgKeys -> String
83
strOfKey Method = "method"
84
strOfKey Args = "args"
85
strOfKey Success = "success"
86
strOfKey Result = "result"
87

    
88
-- | Luxi client encapsulation.
89
data Client = Client { socket :: S.Socket   -- ^ The socket of the client
90
                     , rbuf :: IORef String -- ^ Already received buffer
91
                     }
92

    
93
-- | Connects to the master daemon and returns a luxi Client.
94
getClient :: String -> IO Client
95
getClient path = do
96
    s <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
97
    withTimeout connTimeout "creating luxi connection" $
98
                S.connect s (S.SockAddrUnix path)
99
    rf <- newIORef ""
100
    return Client { socket=s, rbuf=rf}
101

    
102
-- | Closes the client socket.
103
closeClient :: Client -> IO ()
104
closeClient = S.sClose . socket
105

    
106
-- | Sends a message over a luxi transport.
107
sendMsg :: Client -> String -> IO ()
108
sendMsg s buf =
109
    let _send obuf = do
110
          sbytes <- withTimeout queryTimeout
111
                    "sending luxi message" $
112
                    S.send (socket s) obuf
113
          (if sbytes == length obuf
114
           then return ()
115
           else _send (drop sbytes obuf))
116
    in _send (buf ++ [eOM])
117

    
118
-- | Waits for a message over a luxi transport.
119
recvMsg :: Client -> IO String
120
recvMsg s = do
121
  let _recv obuf = do
122
              nbuf <- withTimeout queryTimeout "reading luxi response" $
123
                      S.recv (socket s) 4096
124
              let (msg, remaining) = break ((==) eOM) (obuf ++ nbuf)
125
              (if null remaining
126
               then _recv msg
127
               else return (msg, tail remaining))
128
  cbuf <- readIORef $ rbuf s
129
  (msg, nbuf) <- _recv cbuf
130
  writeIORef (rbuf s) nbuf
131
  return msg
132

    
133
-- | Serialize a request to String.
134
buildCall :: LuxiOp  -- ^ The method
135
          -> JSValue -- ^ The arguments
136
          -> String  -- ^ The serialized form
137
buildCall msg args =
138
    let ja = [(strOfKey Method,
139
               JSString $ toJSString $ strOfOp msg::JSValue),
140
              (strOfKey Args,
141
               args::JSValue)
142
             ]
143
        jo = toJSObject ja
144
    in encodeStrict jo
145

    
146
-- | Check that luxi responses contain the required keys and that the
147
-- call was successful.
148
validateResult :: String -> Result JSValue
149
validateResult s = do
150
  arr <- fromJResult $ decodeStrict s::Result (JSObject JSValue)
151
  status <- fromObj (strOfKey Success) arr::Result Bool
152
  let rkey = strOfKey Result
153
  (if status
154
   then fromObj rkey arr
155
   else fromObj rkey arr >>= fail)
156

    
157
-- | Generic luxi method call.
158
callMethod :: LuxiOp -> JSValue -> Client -> IO (Result JSValue)
159
callMethod method args s = do
160
  sendMsg s $ buildCall method args
161
  result <- recvMsg s
162
  let rval = validateResult result
163
  return rval