Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / UDSServer.hs @ d79a6502

History | View | Annotate | Download (8.1 kB)

1
{-# LANGUAGE TemplateHaskell #-}
2

    
3
{-| Implementation of the Ganeti Unix Domain Socket JSON server interface.
4

    
5
-}
6

    
7
{-
8

    
9
Copyright (C) 2013 Google Inc.
10

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

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

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

    
26
-}
27

    
28
module Ganeti.UDSServer
29
  ( ConnectConfig(..)
30
  , Client
31
  , Server
32
  , RecvResult(..)
33
  , MsgKeys(..)
34
  , strOfKey
35
  , connectClient
36
  , connectServer
37
  , acceptClient
38
  , closeClient
39
  , closeServer
40
  , buildResponse
41
  , parseCall
42
  , recvMsg
43
  , recvMsgExt
44
  , sendMsg
45
  -- * Client handler
46
  , Handler(..)
47
  , HandlerResult
48
  ) where
49

    
50
import Control.Applicative
51
import Control.Exception (catch)
52
import Data.IORef
53
import qualified Data.ByteString as B
54
import qualified Data.ByteString.Lazy as BL
55
import qualified Data.ByteString.UTF8 as UTF8
56
import qualified Data.ByteString.Lazy.UTF8 as UTF8L
57
import Data.Word (Word8)
58
import Control.Monad
59
import qualified Network.Socket as S
60
import System.Directory (removeFile)
61
import System.IO (hClose, hFlush, hWaitForInput, Handle, IOMode(..))
62
import System.IO.Error (isEOFError)
63
import System.Timeout
64
import Text.JSON (encodeStrict, decodeStrict)
65
import qualified Text.JSON as J
66
import Text.JSON.Types
67

    
68
import Ganeti.BasicTypes
69
import Ganeti.Errors (GanetiException)
70
import Ganeti.JSON
71
import Ganeti.Runtime (GanetiDaemon(..), MiscGroup(..), GanetiGroup(..))
72
import Ganeti.THH
73
import Ganeti.Utils
74

    
75

    
76
-- * Utility functions
77

    
78
-- | Wrapper over System.Timeout.timeout that fails in the IO monad.
79
withTimeout :: Int -> String -> IO a -> IO a
80
withTimeout secs descr action = do
81
  result <- timeout (secs * 1000000) action
82
  case result of
83
    Nothing -> fail $ "Timeout in " ++ descr
84
    Just v -> return v
85

    
86

    
87
-- * Generic protocol functionality
88

    
89
-- | Result of receiving a message from the socket.
90
data RecvResult = RecvConnClosed    -- ^ Connection closed
91
                | RecvError String  -- ^ Any other error
92
                | RecvOk String     -- ^ Successfull receive
93
                  deriving (Show, Eq)
94

    
95

    
96
-- | The end-of-message separator.
97
eOM :: Word8
98
eOM = 3
99

    
100
-- | The end-of-message encoded as a ByteString.
101
bEOM :: B.ByteString
102
bEOM = B.singleton eOM
103

    
104
-- | Valid keys in the requests and responses.
105
data MsgKeys = Method
106
             | Args
107
             | Success
108
             | Result
109

    
110
-- | The serialisation of MsgKeys into strings in messages.
111
$(genStrOfKey ''MsgKeys "strOfKey")
112

    
113

    
114
data ConnectConfig = ConnectConfig
115
                     { connDaemon :: GanetiDaemon
116
                     , recvTmo :: Int
117
                     , sendTmo :: Int
118
                     }
119

    
120
-- | A client encapsulation.
121
data Client = Client { socket :: Handle           -- ^ The socket of the client
122
                     , rbuf :: IORef B.ByteString -- ^ Already received buffer
123
                     , clientConfig :: ConnectConfig
124
                     }
125

    
126
-- | A server encapsulation.
127
data Server = Server { sSocket :: S.Socket        -- ^ The bound server socket
128
                     , sPath :: FilePath          -- ^ The scoket's path
129
                     , serverConfig :: ConnectConfig
130
                     }
131

    
132

    
133
-- | Connects to the master daemon and returns a Client.
134
connectClient
135
  :: ConnectConfig    -- ^ configuration for the client
136
  -> Int              -- ^ connection timeout
137
  -> FilePath         -- ^ socket path
138
  -> IO Client
139
connectClient conf tmo path = do
140
  s <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
141
  withTimeout tmo "creating a connection" $
142
              S.connect s (S.SockAddrUnix path)
143
  rf <- newIORef B.empty
144
  h <- S.socketToHandle s ReadWriteMode
145
  return Client { socket=h, rbuf=rf, clientConfig=conf }
146

    
147
-- | Creates and returns a server endpoint.
148
connectServer :: ConnectConfig -> Bool -> FilePath -> IO Server
149
connectServer conf setOwner path = do
150
  s <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
151
  S.bindSocket s (S.SockAddrUnix path)
152
  when setOwner . setOwnerAndGroupFromNames path (connDaemon conf) $
153
    ExtraGroup DaemonsGroup
154
  S.listen s 5 -- 5 is the max backlog
155
  return Server { sSocket=s, sPath=path, serverConfig=conf }
156

    
157
-- | Closes a server endpoint.
158
-- FIXME: this should be encapsulated into a nicer type.
159
closeServer :: Server -> IO ()
160
closeServer server = do
161
  S.sClose (sSocket server)
162
  removeFile (sPath server)
163

    
164
-- | Accepts a client
165
acceptClient :: Server -> IO Client
166
acceptClient s = do
167
  -- second return is the address of the client, which we ignore here
168
  (client_socket, _) <- S.accept (sSocket s)
169
  new_buffer <- newIORef B.empty
170
  handle <- S.socketToHandle client_socket ReadWriteMode
171
  return Client { socket=handle
172
                , rbuf=new_buffer
173
                , clientConfig=serverConfig s
174
                }
175

    
176
-- | Closes the client socket.
177
closeClient :: Client -> IO ()
178
closeClient = hClose . socket
179

    
180
-- | Sends a message over a transport.
181
sendMsg :: Client -> String -> IO ()
182
sendMsg s buf = withTimeout (sendTmo $ clientConfig s) "sending a message" $ do
183
  let encoded = UTF8L.fromString buf
184
      handle = socket s
185
  BL.hPut handle encoded
186
  B.hPut handle bEOM
187
  hFlush handle
188

    
189
-- | Given a current buffer and the handle, it will read from the
190
-- network until we get a full message, and it will return that
191
-- message and the leftover buffer contents.
192
recvUpdate :: ConnectConfig -> Handle -> B.ByteString
193
           -> IO (B.ByteString, B.ByteString)
194
recvUpdate conf handle obuf = do
195
  nbuf <- withTimeout (recvTmo conf) "reading a response" $ do
196
            _ <- hWaitForInput handle (-1)
197
            B.hGetNonBlocking handle 4096
198
  let (msg, remaining) = B.break (eOM ==) nbuf
199
      newbuf = B.append obuf msg
200
  if B.null remaining
201
    then recvUpdate conf handle newbuf
202
    else return (newbuf, B.tail remaining)
203

    
204
-- | Waits for a message over a transport.
205
recvMsg :: Client -> IO String
206
recvMsg s = do
207
  cbuf <- readIORef $ rbuf s
208
  let (imsg, ibuf) = B.break (eOM ==) cbuf
209
  (msg, nbuf) <-
210
    if B.null ibuf      -- if old buffer didn't contain a full message
211
                        -- then we read from network:
212
      then recvUpdate (clientConfig s) (socket s) cbuf
213
      else return (imsg, B.tail ibuf)   -- else we return data from our buffer
214
  writeIORef (rbuf s) nbuf
215
  return $ UTF8.toString msg
216

    
217
-- | Extended wrapper over recvMsg.
218
recvMsgExt :: Client -> IO RecvResult
219
recvMsgExt s =
220
  Control.Exception.catch (liftM RecvOk (recvMsg s)) $ \e ->
221
    return $ if isEOFError e
222
               then RecvConnClosed
223
               else RecvError (show e)
224

    
225

    
226
-- | Parse the required keys out of a call.
227
parseCall :: (J.JSON mth, J.JSON args) => String -> Result (mth, args)
228
parseCall s = do
229
  arr <- fromJResult "parsing top-level JSON message" $
230
           decodeStrict s :: Result (JSObject JSValue)
231
  let keyFromObj :: (J.JSON a) => MsgKeys -> Result a
232
      keyFromObj = fromObj (fromJSObject arr) . strOfKey
233
  (,) <$> keyFromObj Method <*> keyFromObj Args
234

    
235

    
236
-- | Serialize the response to String.
237
buildResponse :: Bool    -- ^ Success
238
              -> JSValue -- ^ The arguments
239
              -> String  -- ^ The serialized form
240
buildResponse success args =
241
  let ja = [ (strOfKey Success, JSBool success)
242
           , (strOfKey Result, args)]
243
      jo = toJSObject ja
244
  in encodeStrict jo
245

    
246

    
247

    
248
-- * Processing client requests
249

    
250
type HandlerResult o = IO (Bool, GenericResult GanetiException o)
251

    
252
data Handler i o = Handler
253
  { hParse         :: J.JSValue -> J.JSValue -> Result i
254
    -- ^ parses method and its arguments into the input type
255
  , hInputLogShort :: i -> String
256
    -- ^ short description of an input, for the INFO logging level
257
  , hInputLogLong  :: i -> String
258
    -- ^ long description of an input, for the DEBUG logging level
259
  , hExec          :: i -> HandlerResult o
260
    -- ^ executes the handler on an input
261
  }