module Ganeti.UDSServer
( ConnectConfig(..)
, ServerConfig(..)
, Client
, Server
, RecvResult(..)
, MsgKeys(..)
, strOfKey
, openClientSocket
, closeClientSocket
, openServerSocket
, closeServerSocket
, acceptSocket
, connectClient
, connectServer
, pipeClient
, acceptClient
, closeClient
, clientToFd
, closeServer
, buildResponse
, parseResponse
, buildCall
, parseCall
, recvMsg
, recvMsgExt
, sendMsg
, Handler(..)
, HandlerResult
, listener
) where
import Prelude ()
import Ganeti.Prelude
import Control.Concurrent.Lifted (fork, yield)
import Control.Monad.Base
import Control.Monad.Trans.Control
import Control.Exception (catch)
import Control.Monad
import qualified Data.ByteString as B
import qualified Data.ByteString.UTF8 as UTF8
import Data.IORef
import Data.List (isInfixOf)
import Data.Word (Word8)
import qualified Network.Socket as S
import System.Directory (removeFile)
import System.IO ( hClose, hFlush, hPutStr, hWaitForInput, Handle, IOMode(..)
, hSetBuffering, BufferMode(..))
import System.IO.Error (isEOFError)
import System.Posix.Types (Fd)
import System.Posix.IO (createPipe, fdToHandle, handleToFd)
import System.Timeout
import Text.JSON (encodeStrict, decodeStrict)
import qualified Text.JSON as J
import Text.JSON.Types
import Ganeti.BasicTypes
import Ganeti.Errors (GanetiException(..), ErrorResult)
import Ganeti.JSON
import Ganeti.Logging
import Ganeti.THH
import Ganeti.Utils
import Ganeti.Constants (privateParametersBlacklist)
withTimeout :: Int -> String -> IO a -> IO a
withTimeout secs descr action = do
result <- timeout (secs * 1000000) action
case result of
Nothing -> fail $ "Timeout in " ++ descr
Just v -> return v
data RecvResult = RecvConnClosed
| RecvError String
| RecvOk String
deriving (Show, Eq)
eOM :: Word8
eOM = 3
bEOM :: B.ByteString
bEOM = B.singleton eOM
data MsgKeys = Method
| Args
| Success
| Result
$(genStrOfKey ''MsgKeys "strOfKey")
data ServerConfig = ServerConfig
{ connPermissions :: FilePermissions
, connConfig :: ConnectConfig
}
data ConnectConfig = ConnectConfig
{ recvTmo :: Int
, sendTmo :: Int
}
data Client = Client { rsocket :: Handle
, wsocket :: Handle
, rbuf :: IORef B.ByteString
, clientConfig :: ConnectConfig
}
data Server = Server { sSocket :: S.Socket
, sPath :: FilePath
, serverConfig :: ConnectConfig
}
openClientSocket
:: Int
-> FilePath
-> IO Handle
openClientSocket tmo path = do
sock <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
withTimeout tmo "creating a connection" $
S.connect sock (S.SockAddrUnix path)
S.socketToHandle sock ReadWriteMode
closeClientSocket :: Handle -> IO ()
closeClientSocket = hClose
openServerSocket :: FilePath -> IO S.Socket
openServerSocket path = do
sock <- S.socket S.AF_UNIX S.Stream S.defaultProtocol
S.bindSocket sock (S.SockAddrUnix path)
return sock
closeServerSocket :: S.Socket -> FilePath -> IO ()
closeServerSocket sock path = do
S.sClose sock
removeFile path
acceptSocket :: S.Socket -> IO Handle
acceptSocket sock = do
(clientSock, _) <- S.accept sock
S.socketToHandle clientSock ReadWriteMode
connectClient
:: ConnectConfig
-> Int
-> FilePath
-> IO Client
connectClient conf tmo path = do
h <- openClientSocket tmo path
rf <- newIORef B.empty
return Client { rsocket=h, wsocket=h, rbuf=rf, clientConfig=conf }
connectServer :: ServerConfig -> Bool -> FilePath -> IO Server
connectServer sconf setOwner path = do
s <- openServerSocket path
when setOwner $ do
res <- ensurePermissions path (connPermissions sconf)
exitIfBad "Error - could not set socket properties" res
S.listen s 5
return Server { sSocket = s, sPath = path, serverConfig = connConfig sconf }
pipeClient :: ConnectConfig -> IO (Client, Client)
pipeClient conf =
let newClient r w = do
rf <- newIORef B.empty
rh <- fdToHandle r
wh <- fdToHandle w
return Client { rsocket = rh, wsocket = wh
, rbuf = rf, clientConfig = conf }
in do
(r1, w1) <- createPipe
(r2, w2) <- createPipe
(,) <$> newClient r1 w2 <*> newClient r2 w1
closeServer :: (MonadBase IO m) => Server -> m ()
closeServer server =
liftBase $ closeServerSocket (sSocket server) (sPath server)
acceptClient :: Server -> IO Client
acceptClient s = do
handle <- acceptSocket (sSocket s)
new_buffer <- newIORef B.empty
return Client { rsocket=handle
, wsocket=handle
, rbuf=new_buffer
, clientConfig=serverConfig s
}
closeClient :: Client -> IO ()
closeClient client = do
closeClientSocket . wsocket $ client
closeClientSocket . rsocket $ client
clientToFd :: Client -> IO (Fd, Fd)
clientToFd client | rh == wh = join (,) <$> handleToFd rh
| otherwise = (,) <$> handleToFd rh <*> handleToFd wh
where
rh = rsocket client
wh = wsocket client
sendMsg :: Client -> String -> IO ()
sendMsg s buf = withTimeout (sendTmo $ clientConfig s) "sending a message" $ do
t1 <- getCurrentTimeUSec
let handle = wsocket s
hSetBuffering handle (BlockBuffering . Just $ 1024 * 1024)
hPutStr handle buf
B.hPut handle bEOM
hFlush handle
t2 <- getCurrentTimeUSec
logDebug $ "sendMsg: " ++ (show ((t2 t1) `div` 1000)) ++ "ms"
recvUpdate :: ConnectConfig -> Handle -> B.ByteString
-> IO (B.ByteString, B.ByteString)
recvUpdate conf handle obuf = do
nbuf <- withTimeout (recvTmo conf) "reading a response" $ do
_ <- hWaitForInput handle (1)
B.hGetNonBlocking handle 4096
let (msg, remaining) = B.break (eOM ==) nbuf
newbuf = B.append obuf msg
if B.null remaining
then recvUpdate conf handle newbuf
else return (newbuf, B.copy (B.tail remaining))
recvMsg :: Client -> IO String
recvMsg s = do
cbuf <- readIORef $ rbuf s
let (imsg, ibuf) = B.break (eOM ==) cbuf
(msg, nbuf) <-
if B.null ibuf
then recvUpdate (clientConfig s) (rsocket s) cbuf
else return (imsg, B.copy (B.tail ibuf))
writeIORef (rbuf s) nbuf
return $ UTF8.toString msg
recvMsgExt :: Client -> IO RecvResult
recvMsgExt s =
Control.Exception.catch (liftM RecvOk (recvMsg s)) $ \e ->
return $ if isEOFError e
then RecvConnClosed
else RecvError (show e)
buildCall :: (J.JSON mth, J.JSON args)
=> mth
-> args
-> String
buildCall mth args =
let keyToObj :: (J.JSON a) => MsgKeys -> a -> (String, J.JSValue)
keyToObj k v = (strOfKey k, J.showJSON v)
in encodeStrict $ toJSObject [ keyToObj Method mth, keyToObj Args args ]
parseCall :: (J.JSON mth, J.JSON args) => String -> Result (mth, args)
parseCall s = do
arr <- fromJResult "parsing top-level JSON message" $
decodeStrict s :: Result (JSObject JSValue)
let keyFromObj :: (J.JSON a) => MsgKeys -> Result a
keyFromObj = fromObj (fromJSObject arr) . strOfKey
(,) <$> keyFromObj Method <*> keyFromObj Args
buildResponse :: Bool
-> JSValue
-> String
buildResponse success args =
let ja = [ (strOfKey Success, JSBool success)
, (strOfKey Result, args)]
jo = toJSObject ja
in encodeStrict jo
decodeError :: JSValue -> ErrorResult JSValue
decodeError val =
case fromJVal val of
Ok e -> Bad e
Bad msg -> Bad $ GenericError msg
parseResponse :: String -> ErrorResult JSValue
parseResponse s = do
when (UTF8.replacement_char `elem` s) $
failError "Failed to decode UTF-8,\
\ detected replacement char after decoding"
oarr <- fromJResultE "Parsing LUXI response" (decodeStrict s)
let arr = J.fromJSObject oarr
status <- fromObj arr (strOfKey Success)
result <- fromObj arr (strOfKey Result)
if status
then return result
else decodeError result
logMsg
:: (Show e, J.JSON e, MonadLog m)
=> Handler i m o
-> i
-> GenericResult e J.JSValue
-> m ()
logMsg handler req (Bad err) =
logWarning $ "Failed to execute request " ++ hInputLogLong handler req ++ ": "
++ show err
logMsg handler req (Ok result) = do
logDebug $ "Result (truncated): " ++ take 2000 (J.encode result)
logDebug $ "Successfully handled " ++ hInputLogShort handler req
prepareMsg
:: (J.JSON e)
=> GenericResult e J.JSValue
-> (Bool, J.JSValue)
prepareMsg (Bad err) = (False, J.showJSON err)
prepareMsg (Ok result) = (True, result)
type HandlerResult m o = m (Bool, GenericResult GanetiException o)
data Handler i m o = Handler
{ hParse :: J.JSValue -> J.JSValue -> Result i
, hInputLogShort :: i -> String
, hInputLogLong :: i -> String
, hExec :: i -> HandlerResult m o
}
handleJsonMessage
:: (J.JSON o, Monad m)
=> Handler i m o
-> i
-> HandlerResult m J.JSValue
handleJsonMessage handler req = do
(close, call_result) <- hExec handler req
return (close, fmap J.showJSON call_result)
handleRawMessage
:: (J.JSON o, MonadLog m)
=> Handler i m o
-> String
-> m (Bool, String)
handleRawMessage handler payload =
case parseCall payload >>= uncurry (hParse handler) of
Bad err -> do
let errmsg = "Failed to parse request: " ++ err
logWarning errmsg
return (False, buildResponse False (J.showJSON errmsg))
Ok req -> do
logDebug $ "Request: " ++ hInputLogLong handler req
(close, call_result_json) <- handleJsonMessage handler req
logMsg handler req call_result_json
let (status, response) = prepareMsg call_result_json
return (close, buildResponse status response)
isRisky :: RecvResult -> Bool
isRisky msg = case msg of
RecvOk payload -> any (`isInfixOf` payload) privateParametersBlacklist
_ -> False
handleClient
:: (J.JSON o, MonadBase IO m, MonadLog m)
=> Handler i m o
-> Client
-> m Bool
handleClient handler client = do
msg <- liftBase $ recvMsgExt client
debugMode <- liftBase isDebugMode
when (debugMode && isRisky msg) $
logAlert "POSSIBLE LEAKING OF CONFIDENTIAL PARAMETERS. \
\Daemon is running in debug mode. \
\The text of the request has been logged."
logDebug $ "Received message (truncated): " ++ take 500 (show msg)
case msg of
RecvConnClosed -> logDebug "Connection closed" >>
return False
RecvError err -> logWarning ("Error during message receiving: " ++ err) >>
return False
RecvOk payload -> do
(close, outMsg) <- handleRawMessage handler payload
liftBase $ sendMsg client outMsg
return close
clientLoop
:: (J.JSON o, MonadBase IO m, MonadLog m)
=> Handler i m o
-> Client
-> m ()
clientLoop handler client = do
result <- handleClient handler client
if result
then yield >> clientLoop handler client
else liftBase $ closeClient client
listener
:: (J.JSON o, MonadBaseControl IO m, MonadLog m)
=> Handler i m o
-> Server
-> m ()
listener handler server = do
client <- liftBase $ acceptClient server
_ <- fork $ clientLoop handler client
return ()