Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / UDSServer.hs @ 5e671e0e

History | View | Annotate | Download (7 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
  , recvMsg
42
  , recvMsgExt
43
  , sendMsg
44
  ) where
45

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

    
62
import Ganeti.Runtime (GanetiDaemon(..), MiscGroup(..), GanetiGroup(..))
63
import Ganeti.THH
64
import Ganeti.Utils
65

    
66

    
67
-- * Utility functions
68

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

    
77

    
78
-- * Generic protocol functionality
79

    
80
-- | Result of receiving a message from the socket.
81
data RecvResult = RecvConnClosed    -- ^ Connection closed
82
                | RecvError String  -- ^ Any other error
83
                | RecvOk String     -- ^ Successfull receive
84
                  deriving (Show, Eq)
85

    
86

    
87
-- | The end-of-message separator.
88
eOM :: Word8
89
eOM = 3
90

    
91
-- | The end-of-message encoded as a ByteString.
92
bEOM :: B.ByteString
93
bEOM = B.singleton eOM
94

    
95
-- | Valid keys in the requests and responses.
96
data MsgKeys = Method
97
             | Args
98
             | Success
99
             | Result
100

    
101
-- | The serialisation of MsgKeys into strings in messages.
102
$(genStrOfKey ''MsgKeys "strOfKey")
103

    
104

    
105
data ConnectConfig = ConnectConfig
106
                     { connDaemon :: GanetiDaemon
107
                     , recvTmo :: Int
108
                     , sendTmo :: Int
109
                     }
110

    
111
-- | A client encapsulation.
112
data Client = Client { socket :: Handle           -- ^ The socket of the client
113
                     , rbuf :: IORef B.ByteString -- ^ Already received buffer
114
                     , clientConfig :: ConnectConfig
115
                     }
116

    
117
-- | A server encapsulation.
118
data Server = Server { sSocket :: S.Socket        -- ^ The bound server socket
119
                     , sPath :: FilePath          -- ^ The scoket's path
120
                     , serverConfig :: ConnectConfig
121
                     }
122

    
123

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

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

    
148
-- | Closes a server endpoint.
149
-- FIXME: this should be encapsulated into a nicer type.
150
closeServer :: Server -> IO ()
151
closeServer server = do
152
  S.sClose (sSocket server)
153
  removeFile (sPath server)
154

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

    
167
-- | Closes the client socket.
168
closeClient :: Client -> IO ()
169
closeClient = hClose . socket
170

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

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

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

    
208
-- | Extended wrapper over recvMsg.
209
recvMsgExt :: Client -> IO RecvResult
210
recvMsgExt s =
211
  Control.Exception.catch (liftM RecvOk (recvMsg s)) $ \e ->
212
    return $ if isEOFError e
213
               then RecvConnClosed
214
               else RecvError (show e)
215

    
216

    
217
-- | Serialize the response to String.
218
buildResponse :: Bool    -- ^ Success
219
              -> JSValue -- ^ The arguments
220
              -> String  -- ^ The serialized form
221
buildResponse success args =
222
  let ja = [ (strOfKey Success, JSBool success)
223
           , (strOfKey Result, args)]
224
      jo = toJSObject ja
225
  in encodeStrict jo