Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / UDSServer.hs @ 78e0f701

History | View | Annotate | Download (12.9 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2
{-# LANGUAGE FlexibleContexts #-}
3

    
4
{-| Implementation of the Ganeti Unix Domain Socket JSON server interface.
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.UDSServer
30
  ( ConnectConfig(..)
31
  , Client
32
  , Server
33
  , RecvResult(..)
34
  , MsgKeys(..)
35
  , strOfKey
36
  -- * Unix sockets
37
  , openClientSocket
38
  , closeClientSocket
39
  , openServerSocket
40
  , closeServerSocket
41
  , acceptSocket
42
  -- * Client and server
43
  , connectClient
44
  , connectServer
45
  , acceptClient
46
  , closeClient
47
  , closeServer
48
  , buildResponse
49
  , parseCall
50
  , recvMsg
51
  , recvMsgExt
52
  , sendMsg
53
  -- * Client handler
54
  , Handler(..)
55
  , HandlerResult
56
  , listener
57
  ) where
58

    
59
import Control.Applicative
60
import Control.Concurrent.Lifted (fork)
61
import Control.Monad.Base
62
import Control.Monad.Trans.Control
63
import Control.Exception (catch)
64
import Control.Monad
65
import qualified Data.ByteString as B
66
import qualified Data.ByteString.Lazy as BL
67
import qualified Data.ByteString.UTF8 as UTF8
68
import qualified Data.ByteString.Lazy.UTF8 as UTF8L
69
import Data.IORef
70
import Data.List
71
import Data.Word (Word8)
72
import qualified Network.Socket as S
73
import System.Directory (removeFile)
74
import System.IO (hClose, hFlush, hWaitForInput, Handle, IOMode(..))
75
import System.IO.Error (isEOFError)
76
import System.Timeout
77
import Text.JSON (encodeStrict, decodeStrict)
78
import qualified Text.JSON as J
79
import Text.JSON.Types
80

    
81
import Ganeti.BasicTypes
82
import Ganeti.Errors (GanetiException)
83
import Ganeti.JSON
84
import Ganeti.Logging
85
import Ganeti.Runtime (GanetiDaemon(..), MiscGroup(..), GanetiGroup(..))
86
import Ganeti.THH
87
import Ganeti.Utils
88
import Ganeti.Constants (privateParametersBlacklist)
89

    
90
-- * Utility functions
91

    
92
-- | Wrapper over System.Timeout.timeout that fails in the IO monad.
93
withTimeout :: Int -> String -> IO a -> IO a
94
withTimeout secs descr action = do
95
  result <- timeout (secs * 1000000) action
96
  case result of
97
    Nothing -> fail $ "Timeout in " ++ descr
98
    Just v -> return v
99

    
100

    
101
-- * Generic protocol functionality
102

    
103
-- | Result of receiving a message from the socket.
104
data RecvResult = RecvConnClosed    -- ^ Connection closed
105
                | RecvError String  -- ^ Any other error
106
                | RecvOk String     -- ^ Successfull receive
107
                  deriving (Show, Eq)
108

    
109

    
110
-- | The end-of-message separator.
111
eOM :: Word8
112
eOM = 3
113

    
114
-- | The end-of-message encoded as a ByteString.
115
bEOM :: B.ByteString
116
bEOM = B.singleton eOM
117

    
118
-- | Valid keys in the requests and responses.
119
data MsgKeys = Method
120
             | Args
121
             | Success
122
             | Result
123

    
124
-- | The serialisation of MsgKeys into strings in messages.
125
$(genStrOfKey ''MsgKeys "strOfKey")
126

    
127

    
128
data ConnectConfig = ConnectConfig
129
                     { connDaemon :: GanetiDaemon
130
                     , recvTmo :: Int
131
                     , sendTmo :: Int
132
                     }
133

    
134
-- | A client encapsulation.
135
data Client = Client { socket :: Handle           -- ^ The socket of the client
136
                     , rbuf :: IORef B.ByteString -- ^ Already received buffer
137
                     , clientConfig :: ConnectConfig
138
                     }
139

    
140
-- | A server encapsulation.
141
data Server = Server { sSocket :: S.Socket        -- ^ The bound server socket
142
                     , sPath :: FilePath          -- ^ The scoket's path
143
                     , serverConfig :: ConnectConfig
144
                     }
145

    
146
-- * Unix sockets
147

    
148
-- | Creates a Unix socket and connects it to the specified @path@,
149
-- where @timeout@ specifies the connection timeout.
150
openClientSocket
151
  :: Int              -- ^ connection timeout
152
  -> FilePath         -- ^ socket path
153
  -> IO Handle
154
openClientSocket tmo path = do
155
  sock <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
156
  withTimeout tmo "creating a connection" $
157
              S.connect sock (S.SockAddrUnix path)
158
  S.socketToHandle sock ReadWriteMode
159

    
160
closeClientSocket :: Handle -> IO ()
161
closeClientSocket = hClose
162

    
163
-- | Creates a Unix socket and binds it to the specified @path@.
164
openServerSocket :: FilePath -> IO S.Socket
165
openServerSocket path = do
166
  sock <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
167
  S.bindSocket sock (S.SockAddrUnix path)
168
  return sock
169

    
170
closeServerSocket :: S.Socket -> FilePath -> IO ()
171
closeServerSocket sock path = do
172
  S.sClose sock
173
  removeFile path
174

    
175
acceptSocket :: S.Socket -> IO Handle
176
acceptSocket sock = do
177
  -- ignore client socket address
178
  (clientSock, _) <- S.accept sock
179
  S.socketToHandle clientSock ReadWriteMode
180

    
181
-- * Client and server
182

    
183
-- | Connects to the master daemon and returns a Client.
184
connectClient
185
  :: ConnectConfig    -- ^ configuration for the client
186
  -> Int              -- ^ connection timeout
187
  -> FilePath         -- ^ socket path
188
  -> IO Client
189
connectClient conf tmo path = do
190
  h <- openClientSocket tmo path
191
  rf <- newIORef B.empty
192
  return Client { socket=h, rbuf=rf, clientConfig=conf }
193

    
194
-- | Creates and returns a server endpoint.
195
connectServer :: ConnectConfig -> Bool -> FilePath -> IO Server
196
connectServer conf setOwner path = do
197
  s <- openServerSocket path
198
  when setOwner . setOwnerAndGroupFromNames path (connDaemon conf) $
199
    ExtraGroup DaemonsGroup
200
  S.listen s 5 -- 5 is the max backlog
201
  return Server { sSocket=s, sPath=path, serverConfig=conf }
202

    
203
-- | Closes a server endpoint.
204
closeServer :: (MonadBase IO m) => Server -> m ()
205
closeServer server =
206
  liftBase $ closeServerSocket (sSocket server) (sPath server)
207

    
208
-- | Accepts a client
209
acceptClient :: Server -> IO Client
210
acceptClient s = do
211
  handle <- acceptSocket (sSocket s)
212
  new_buffer <- newIORef B.empty
213
  return Client { socket=handle
214
                , rbuf=new_buffer
215
                , clientConfig=serverConfig s
216
                }
217

    
218
-- | Closes the client socket.
219
closeClient :: Client -> IO ()
220
closeClient = closeClientSocket . socket
221

    
222
-- | Sends a message over a transport.
223
sendMsg :: Client -> String -> IO ()
224
sendMsg s buf = withTimeout (sendTmo $ clientConfig s) "sending a message" $ do
225
  let encoded = UTF8L.fromString buf
226
      handle = socket s
227
  BL.hPut handle encoded
228
  B.hPut handle bEOM
229
  hFlush handle
230

    
231
-- | Given a current buffer and the handle, it will read from the
232
-- network until we get a full message, and it will return that
233
-- message and the leftover buffer contents.
234
recvUpdate :: ConnectConfig -> Handle -> B.ByteString
235
           -> IO (B.ByteString, B.ByteString)
236
recvUpdate conf handle obuf = do
237
  nbuf <- withTimeout (recvTmo conf) "reading a response" $ do
238
            _ <- hWaitForInput handle (-1)
239
            B.hGetNonBlocking handle 4096
240
  let (msg, remaining) = B.break (eOM ==) nbuf
241
      newbuf = B.append obuf msg
242
  if B.null remaining
243
    then recvUpdate conf handle newbuf
244
    else return (newbuf, B.tail remaining)
245

    
246
-- | Waits for a message over a transport.
247
recvMsg :: Client -> IO String
248
recvMsg s = do
249
  cbuf <- readIORef $ rbuf s
250
  let (imsg, ibuf) = B.break (eOM ==) cbuf
251
  (msg, nbuf) <-
252
    if B.null ibuf      -- if old buffer didn't contain a full message
253
                        -- then we read from network:
254
      then recvUpdate (clientConfig s) (socket s) cbuf
255
      else return (imsg, B.tail ibuf)   -- else we return data from our buffer
256
  writeIORef (rbuf s) nbuf
257
  return $ UTF8.toString msg
258

    
259
-- | Extended wrapper over recvMsg.
260
recvMsgExt :: Client -> IO RecvResult
261
recvMsgExt s =
262
  Control.Exception.catch (liftM RecvOk (recvMsg s)) $ \e ->
263
    return $ if isEOFError e
264
               then RecvConnClosed
265
               else RecvError (show e)
266

    
267

    
268
-- | Parse the required keys out of a call.
269
parseCall :: (J.JSON mth, J.JSON args) => String -> Result (mth, args)
270
parseCall s = do
271
  arr <- fromJResult "parsing top-level JSON message" $
272
           decodeStrict s :: Result (JSObject JSValue)
273
  let keyFromObj :: (J.JSON a) => MsgKeys -> Result a
274
      keyFromObj = fromObj (fromJSObject arr) . strOfKey
275
  (,) <$> keyFromObj Method <*> keyFromObj Args
276

    
277

    
278
-- | Serialize the response to String.
279
buildResponse :: Bool    -- ^ Success
280
              -> JSValue -- ^ The arguments
281
              -> String  -- ^ The serialized form
282
buildResponse success args =
283
  let ja = [ (strOfKey Success, JSBool success)
284
           , (strOfKey Result, args)]
285
      jo = toJSObject ja
286
  in encodeStrict jo
287

    
288
-- | Logs an outgoing message.
289
logMsg
290
    :: (Show e, J.JSON e, MonadLog m)
291
    => Handler i m o
292
    -> i                          -- ^ the received request (used for logging)
293
    -> GenericResult e J.JSValue  -- ^ A message to be sent
294
    -> m ()
295
logMsg handler req (Bad err) =
296
  logWarning $ "Failed to execute request " ++ hInputLogLong handler req ++ ": "
297
               ++ show err
298
logMsg handler req (Ok result) = do
299
  -- only log the first 2,000 chars of the result
300
  logDebug $ "Result (truncated): " ++ take 2000 (J.encode result)
301
  logInfo $ "Successfully handled " ++ hInputLogShort handler req
302

    
303
-- | Prepares an outgoing message.
304
prepareMsg
305
    :: (J.JSON e)
306
    => GenericResult e J.JSValue  -- ^ A message to be sent
307
    -> (Bool, J.JSValue)
308
prepareMsg (Bad err)   = (False, J.showJSON err)
309
prepareMsg (Ok result) = (True, result)
310

    
311

    
312
-- * Processing client requests
313

    
314
type HandlerResult m o = m (Bool, GenericResult GanetiException o)
315

    
316
data Handler i m o = Handler
317
  { hParse         :: J.JSValue -> J.JSValue -> Result i
318
    -- ^ parses method and its arguments into the input type
319
  , hInputLogShort :: i -> String
320
    -- ^ short description of an input, for the INFO logging level
321
  , hInputLogLong  :: i -> String
322
    -- ^ long description of an input, for the DEBUG logging level
323
  , hExec          :: i -> HandlerResult m o
324
    -- ^ executes the handler on an input
325
  }
326

    
327

    
328
handleJsonMessage
329
    :: (J.JSON o, Monad m)
330
    => Handler i m o            -- ^ handler
331
    -> i                        -- ^ parsed input
332
    -> HandlerResult m J.JSValue
333
handleJsonMessage handler req = do
334
  (close, call_result) <- hExec handler req
335
  return (close, fmap J.showJSON call_result)
336

    
337
-- | Takes a request as a 'String', parses it, passes it to a handler and
338
-- formats its response.
339
handleRawMessage
340
    :: (J.JSON o, MonadLog m)
341
    => Handler i m o            -- ^ handler
342
    -> String                   -- ^ raw unparsed input
343
    -> m (Bool, String)
344
handleRawMessage handler payload =
345
  case parseCall payload >>= uncurry (hParse handler) of
346
    Bad err -> do
347
         let errmsg = "Failed to parse request: " ++ err
348
         logWarning errmsg
349
         return (False, buildResponse False (J.showJSON errmsg))
350
    Ok req -> do
351
        logDebug $ "Request: " ++ hInputLogLong handler req
352
        (close, call_result_json) <- handleJsonMessage handler req
353
        logMsg handler req call_result_json
354
        let (status, response) = prepareMsg call_result_json
355
        return (close, buildResponse status response)
356

    
357
isRisky :: RecvResult -> Bool
358
isRisky msg = case msg of
359
  RecvOk payload -> any (`isInfixOf` payload) privateParametersBlacklist
360
  _ -> False
361

    
362
-- | Reads a request, passes it to a handler and sends a response back to the
363
-- client.
364
handleClient
365
    :: (J.JSON o, MonadBase IO m, MonadLog m)
366
    => Handler i m o
367
    -> Client
368
    -> m Bool
369
handleClient handler client = do
370
  msg <- liftBase $ recvMsgExt client
371

    
372
  debugMode <- liftBase isDebugMode
373
  when (debugMode && isRisky msg) $
374
    logAlert "POSSIBLE LEAKING OF CONFIDENTIAL PARAMETERS. \
375
             \Daemon is running in debug mode. \
376
             \The text of the request has been logged."
377
  logDebug $ "Received message: " ++ show msg
378

    
379
  case msg of
380
    RecvConnClosed -> logDebug "Connection closed" >>
381
                      return False
382
    RecvError err -> logWarning ("Error during message receiving: " ++ err) >>
383
                     return False
384
    RecvOk payload -> do
385
      (close, outMsg) <- handleRawMessage handler payload
386
      liftBase $ sendMsg client outMsg
387
      return close
388

    
389

    
390
-- | Main client loop: runs one loop of 'handleClient', and if that
391
-- doesn't report a finished (closed) connection, restarts itself.
392
clientLoop
393
    :: (J.JSON o, MonadBase IO m, MonadLog m)
394
    => Handler i m o
395
    -> Client
396
    -> m ()
397
clientLoop handler client = do
398
  result <- handleClient handler client
399
  if result
400
    then clientLoop handler client
401
    else liftBase $ closeClient client
402

    
403
-- | Main listener loop: accepts clients, forks an I/O thread to handle
404
-- that client.
405
listener
406
    :: (J.JSON o, MonadBaseControl IO m, MonadLog m)
407
    => Handler i m o
408
    -> Server
409
    -> m ()
410
listener handler server = do
411
  client <- liftBase $ acceptClient server
412
  _ <- fork $ clientLoop handler client
413
  return ()