Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / UDSServer.hs @ 0fbc8447

History | View | Annotate | Download (6.9 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
                     , serverConfig :: ConnectConfig
120
                     }
121

    
122

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

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

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

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

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

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

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

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

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

    
215

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