Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Confd / Server.hs @ 218e3b0f

History | View | Annotate | Download (10.9 kB)

1
{-| Implementation of the Ganeti confd server functionality.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 2011, 2012, 2013 Google Inc.
8

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

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

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

    
24
-}
25

    
26
module Ganeti.Confd.Server
27
  ( main
28
  , checkMain
29
  , prepMain
30
  ) where
31

    
32
import Control.Concurrent
33
import Control.Monad (forever, liftM)
34
import Data.IORef
35
import Data.List
36
import qualified Data.Map as M
37
import Data.Maybe (fromMaybe)
38
import qualified Network.Socket as S
39
import System.Exit
40
import System.IO
41
import qualified Text.JSON as J
42

    
43
import Ganeti.BasicTypes
44
import Ganeti.Errors
45
import Ganeti.Daemon
46
import Ganeti.JSON
47
import Ganeti.Objects
48
import Ganeti.Confd.Types
49
import Ganeti.Confd.Utils
50
import Ganeti.Config
51
import Ganeti.ConfigReader
52
import Ganeti.Hash
53
import Ganeti.Logging
54
import qualified Ganeti.Constants as C
55
import Ganeti.Query.Server (prepQueryD, runQueryD)
56
import Ganeti.Utils
57

    
58
-- * Types and constants definitions
59

    
60
-- | What we store as configuration.
61
type CRef = IORef (Result (ConfigData, LinkIpMap))
62

    
63
-- | A small type alias for readability.
64
type StatusAnswer = (ConfdReplyStatus, J.JSValue)
65

    
66
-- | Unknown entry standard response.
67
queryUnknownEntry :: StatusAnswer
68
queryUnknownEntry = (ReplyStatusError, J.showJSON ConfdErrorUnknownEntry)
69

    
70
{- not used yet
71
-- | Internal error standard response.
72
queryInternalError :: StatusAnswer
73
queryInternalError = (ReplyStatusError, J.showJSON ConfdErrorInternal)
74
-}
75

    
76
-- | Argument error standard response.
77
queryArgumentError :: StatusAnswer
78
queryArgumentError = (ReplyStatusError, J.showJSON ConfdErrorArgument)
79

    
80
-- | Converter from specific error to a string format.
81
gntErrorToResult :: ErrorResult a -> Result a
82
gntErrorToResult (Bad err) = Bad (show err)
83
gntErrorToResult (Ok x) = Ok x
84

    
85
-- * Confd base functionality
86

    
87
-- | Computes the node role.
88
nodeRole :: ConfigData -> String -> Result ConfdNodeRole
89
nodeRole cfg name =
90
  let cmaster = clusterMasterNode . configCluster $ cfg
91
      mnode = M.lookup name . fromContainer . configNodes $ cfg
92
  in case mnode of
93
       Nothing -> Bad "Node not found"
94
       Just node | cmaster == name -> Ok NodeRoleMaster
95
                 | nodeDrained node -> Ok NodeRoleDrained
96
                 | nodeOffline node -> Ok NodeRoleOffline
97
                 | nodeMasterCandidate node -> Ok NodeRoleCandidate
98
       _ -> Ok NodeRoleRegular
99

    
100
-- | Does an instance ip -> instance -> primary node -> primary ip
101
-- transformation.
102
getNodePipByInstanceIp :: ConfigData
103
                       -> LinkIpMap
104
                       -> String
105
                       -> String
106
                       -> StatusAnswer
107
getNodePipByInstanceIp cfg linkipmap link instip =
108
  case M.lookup instip (M.findWithDefault M.empty link linkipmap) of
109
    Nothing -> queryUnknownEntry
110
    Just instname ->
111
      case getInstPrimaryNode cfg instname of
112
        Bad _ -> queryUnknownEntry -- either instance or node not found
113
        Ok node -> (ReplyStatusOk, J.showJSON (nodePrimaryIp node))
114

    
115
-- | Builds the response to a given query.
116
buildResponse :: (ConfigData, LinkIpMap) -> ConfdRequest -> Result StatusAnswer
117
buildResponse (cfg, _) (ConfdRequest { confdRqType = ReqPing }) =
118
  return (ReplyStatusOk, J.showJSON (configVersion cfg))
119

    
120
buildResponse cdata req@(ConfdRequest { confdRqType = ReqClusterMaster }) =
121
  case confdRqQuery req of
122
    EmptyQuery -> return (ReplyStatusOk, J.showJSON master_name)
123
    PlainQuery _ -> return queryArgumentError
124
    DictQuery reqq -> do
125
      mnode <- gntErrorToResult $ getNode cfg master_name
126
      let fvals = map (\field -> case field of
127
                                   ReqFieldName -> master_name
128
                                   ReqFieldIp -> clusterMasterIp cluster
129
                                   ReqFieldMNodePip -> nodePrimaryIp mnode
130
                      ) (confdReqQFields reqq)
131
      return (ReplyStatusOk, J.showJSON fvals)
132
    where master_name = clusterMasterNode cluster
133
          cluster = configCluster cfg
134
          cfg = fst cdata
135

    
136
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeRoleByName }) = do
137
  node_name <- case confdRqQuery req of
138
                 PlainQuery str -> return str
139
                 _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
140
  role <- nodeRole (fst cdata) node_name
141
  return (ReplyStatusOk, J.showJSON role)
142

    
143
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipList }) =
144
  -- note: we use foldlWithKey because that's present accross more
145
  -- versions of the library
146
  return (ReplyStatusOk, J.showJSON $
147
          M.foldlWithKey (\accu _ n -> nodePrimaryIp n:accu) []
148
          (fromContainer . configNodes . fst $ cdata))
149

    
150
buildResponse cdata (ConfdRequest { confdRqType = ReqMcPipList }) =
151
  -- note: we use foldlWithKey because that's present accross more
152
  -- versions of the library
153
  return (ReplyStatusOk, J.showJSON $
154
          M.foldlWithKey (\accu _ n -> if nodeMasterCandidate n
155
                                         then nodePrimaryIp n:accu
156
                                         else accu) []
157
          (fromContainer . configNodes . fst $ cdata))
158

    
159
buildResponse (cfg, linkipmap)
160
              req@(ConfdRequest { confdRqType = ReqInstIpsList }) = do
161
  link <- case confdRqQuery req of
162
            PlainQuery str -> return str
163
            EmptyQuery -> return (getDefaultNicLink cfg)
164
            _ -> fail "Invalid query type"
165
  return (ReplyStatusOk, J.showJSON $ getInstancesIpByLink linkipmap link)
166

    
167
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipByInstPip
168
                                  , confdRqQuery = DictQuery query}) =
169
  let (cfg, linkipmap) = cdata
170
      link = fromMaybe (getDefaultNicLink cfg) (confdReqQLink query)
171
  in case confdReqQIp query of
172
       Just ip -> return $ getNodePipByInstanceIp cfg linkipmap link ip
173
       Nothing -> return (ReplyStatusOk,
174
                          J.showJSON $
175
                           map (getNodePipByInstanceIp cfg linkipmap link)
176
                           (confdReqQIpList query))
177

    
178
buildResponse _ (ConfdRequest { confdRqType = ReqNodePipByInstPip }) =
179
  return queryArgumentError
180

    
181
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeDrbd }) = do
182
  let cfg = fst cdata
183
  node_name <- case confdRqQuery req of
184
                 PlainQuery str -> return str
185
                 _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
186
  node <- gntErrorToResult $ getNode cfg node_name
187
  let minors = concatMap (getInstMinorsForNode (nodeName node)) .
188
               M.elems . fromContainer . configInstances $ cfg
189
      encoded = [J.JSArray [J.showJSON a, J.showJSON b, J.showJSON c,
190
                             J.showJSON d, J.showJSON e, J.showJSON f] |
191
                 (a, b, c, d, e, f) <- minors]
192
  return (ReplyStatusOk, J.showJSON encoded)
193

    
194
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeInstances }) = do
195
  let cfg = fst cdata
196
  node_name <- case confdRqQuery req of
197
                PlainQuery str -> return str
198
                _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
199
  let instances = getNodeInstances cfg node_name
200
  return (ReplyStatusOk, J.showJSON instances)
201

    
202
-- | Creates a ConfdReply from a given answer.
203
serializeResponse :: Result StatusAnswer -> ConfdReply
204
serializeResponse r =
205
    let (status, result) = case r of
206
                    Bad err -> (ReplyStatusError, J.showJSON err)
207
                    Ok (code, val) -> (code, val)
208
    in ConfdReply { confdReplyProtocol = 1
209
                  , confdReplyStatus   = status
210
                  , confdReplyAnswer   = result
211
                  , confdReplySerial   = 0 }
212

    
213
-- ** Client input/output handlers
214

    
215
-- | Main loop for a given client.
216
responder :: CRef -> S.Socket -> HashKey -> String -> S.SockAddr -> IO ()
217
responder cfgref socket hmac msg peer = do
218
  ctime <- getCurrentTime
219
  case parseRequest hmac msg ctime of
220
    Ok (origmsg, rq) -> do
221
              logDebug $ "Processing request: " ++ rStripSpace origmsg
222
              mcfg <- readIORef cfgref
223
              let response = respondInner mcfg hmac rq
224
              _ <- S.sendTo socket response peer
225
              return ()
226
    Bad err -> logInfo $ "Failed to parse incoming message: " ++ err
227
  return ()
228

    
229
-- | Inner helper function for a given client. This generates the
230
-- final encoded message (as a string), ready to be sent out to the
231
-- client.
232
respondInner :: Result (ConfigData, LinkIpMap) -> HashKey
233
             -> ConfdRequest -> String
234
respondInner cfg hmac rq =
235
  let rsalt = confdRqRsalt rq
236
      innermsg = serializeResponse (cfg >>= flip buildResponse rq)
237
      innerserialised = J.encodeStrict innermsg
238
      outermsg = signMessage hmac rsalt innerserialised
239
      outerserialised = confdMagicFourcc ++ J.encodeStrict outermsg
240
  in outerserialised
241

    
242
-- | Main listener loop.
243
listener :: S.Socket -> HashKey
244
         -> (S.Socket -> HashKey -> String -> S.SockAddr -> IO ())
245
         -> IO ()
246
listener s hmac resp = do
247
  (msg, _, peer) <- S.recvFrom s 4096
248
  if confdMagicFourcc `isPrefixOf` msg
249
    then forkIO (resp s hmac (drop 4 msg) peer) >> return ()
250
    else logDebug "Invalid magic code!" >> return ()
251
  return ()
252

    
253
-- | Extract the configuration from our IORef.
254
configReader :: CRef -> ConfigReader
255
configReader cref = do
256
  cdata <- readIORef cref
257
  return $ liftM fst cdata
258

    
259
-- | Type alias for prepMain results
260
type PrepResult = (S.Socket, (FilePath, S.Socket),
261
                   IORef (Result (ConfigData, LinkIpMap)))
262

    
263
-- | Check function for confd.
264
checkMain :: CheckFn (S.Family, S.SockAddr)
265
checkMain opts = do
266
  parseresult <- parseAddress opts C.defaultConfdPort
267
  case parseresult of
268
    Bad msg -> do
269
      hPutStrLn stderr $ "parsing bind address: " ++ msg
270
      return . Left $ ExitFailure 1
271
    Ok v -> return $ Right v
272

    
273
-- | Prepare function for confd.
274
prepMain :: PrepFn (S.Family, S.SockAddr) PrepResult
275
prepMain _ (af_family, bindaddr) = do
276
  s <- S.socket af_family S.Datagram S.defaultProtocol
277
  S.bindSocket s bindaddr
278
  -- prepare the queryd listener
279
  query_data <- prepQueryD Nothing
280
  cref <- newIORef (Bad "Configuration not yet loaded")
281
  return (s, query_data, cref)
282

    
283
-- | Main function.
284
main :: MainFn (S.Family, S.SockAddr) PrepResult
285
main _ _ (s, query_data, cref) = do
286
  let cfg_transform :: Result ConfigData -> Result (ConfigData, LinkIpMap)
287
      cfg_transform = liftM (\cfg -> (cfg, buildLinkIpInstnameMap cfg))
288
  initConfigReader cfg_transform cref
289

    
290
  hmac <- getClusterHmac
291
  -- launch the queryd listener
292
  _ <- forkIO $ runQueryD query_data (configReader cref)
293
  -- and finally enter the responder loop
294
  forever $ listener s hmac (responder cref)