Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / UDSServer.hs @ 6e47412f

History | View | Annotate | Download (7.5 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
  ) where
46

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

    
65
import Ganeti.BasicTypes
66
import Ganeti.JSON
67
import Ganeti.Runtime (GanetiDaemon(..), MiscGroup(..), GanetiGroup(..))
68
import Ganeti.THH
69
import Ganeti.Utils
70

    
71

    
72
-- * Utility functions
73

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

    
82

    
83
-- * Generic protocol functionality
84

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

    
91

    
92
-- | The end-of-message separator.
93
eOM :: Word8
94
eOM = 3
95

    
96
-- | The end-of-message encoded as a ByteString.
97
bEOM :: B.ByteString
98
bEOM = B.singleton eOM
99

    
100
-- | Valid keys in the requests and responses.
101
data MsgKeys = Method
102
             | Args
103
             | Success
104
             | Result
105

    
106
-- | The serialisation of MsgKeys into strings in messages.
107
$(genStrOfKey ''MsgKeys "strOfKey")
108

    
109

    
110
data ConnectConfig = ConnectConfig
111
                     { connDaemon :: GanetiDaemon
112
                     , recvTmo :: Int
113
                     , sendTmo :: Int
114
                     }
115

    
116
-- | A client encapsulation.
117
data Client = Client { socket :: Handle           -- ^ The socket of the client
118
                     , rbuf :: IORef B.ByteString -- ^ Already received buffer
119
                     , clientConfig :: ConnectConfig
120
                     }
121

    
122
-- | A server encapsulation.
123
data Server = Server { sSocket :: S.Socket        -- ^ The bound server socket
124
                     , sPath :: FilePath          -- ^ The scoket's path
125
                     , serverConfig :: ConnectConfig
126
                     }
127

    
128

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

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

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

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

    
172
-- | Closes the client socket.
173
closeClient :: Client -> IO ()
174
closeClient = hClose . socket
175

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

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

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

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

    
221

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

    
231

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