Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Confd / Server.hs @ 1f005f16

History | View | Annotate | Download (10.9 kB)

1 358a0a8f Iustin Pop
{-| Implementation of the Ganeti confd server functionality.
2 358a0a8f Iustin Pop
3 358a0a8f Iustin Pop
-}
4 358a0a8f Iustin Pop
5 358a0a8f Iustin Pop
{-
6 358a0a8f Iustin Pop
7 3190ad64 Iustin Pop
Copyright (C) 2011, 2012, 2013 Google Inc.
8 358a0a8f Iustin Pop
9 358a0a8f Iustin Pop
This program is free software; you can redistribute it and/or modify
10 358a0a8f Iustin Pop
it under the terms of the GNU General Public License as published by
11 358a0a8f Iustin Pop
the Free Software Foundation; either version 2 of the License, or
12 358a0a8f Iustin Pop
(at your option) any later version.
13 358a0a8f Iustin Pop
14 358a0a8f Iustin Pop
This program is distributed in the hope that it will be useful, but
15 358a0a8f Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
16 358a0a8f Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 358a0a8f Iustin Pop
General Public License for more details.
18 358a0a8f Iustin Pop
19 358a0a8f Iustin Pop
You should have received a copy of the GNU General Public License
20 358a0a8f Iustin Pop
along with this program; if not, write to the Free Software
21 358a0a8f Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 358a0a8f Iustin Pop
02110-1301, USA.
23 358a0a8f Iustin Pop
24 358a0a8f Iustin Pop
-}
25 358a0a8f Iustin Pop
26 358a0a8f Iustin Pop
module Ganeti.Confd.Server
27 358a0a8f Iustin Pop
  ( main
28 2ac2e420 Iustin Pop
  , checkMain
29 2ac2e420 Iustin Pop
  , prepMain
30 358a0a8f Iustin Pop
  ) where
31 358a0a8f Iustin Pop
32 358a0a8f Iustin Pop
import Control.Concurrent
33 218e3b0f Thomas Thrainer
import Control.Monad (forever, liftM)
34 358a0a8f Iustin Pop
import Data.IORef
35 358a0a8f Iustin Pop
import Data.List
36 358a0a8f Iustin Pop
import qualified Data.Map as M
37 2cdaf225 Iustin Pop
import Data.Maybe (fromMaybe)
38 358a0a8f Iustin Pop
import qualified Network.Socket as S
39 ef3de7b0 Iustin Pop
import System.Exit
40 ef3de7b0 Iustin Pop
import System.IO
41 358a0a8f Iustin Pop
import qualified Text.JSON as J
42 358a0a8f Iustin Pop
43 4cd79ca8 Iustin Pop
import Ganeti.BasicTypes
44 5183e8be Iustin Pop
import Ganeti.Errors
45 358a0a8f Iustin Pop
import Ganeti.Daemon
46 f3baf5ef Iustin Pop
import Ganeti.JSON
47 358a0a8f Iustin Pop
import Ganeti.Objects
48 cdc2392b Iustin Pop
import Ganeti.Confd.Types
49 62377cf5 Iustin Pop
import Ganeti.Confd.Utils
50 358a0a8f Iustin Pop
import Ganeti.Config
51 218e3b0f Thomas Thrainer
import Ganeti.ConfigReader
52 358a0a8f Iustin Pop
import Ganeti.Hash
53 358a0a8f Iustin Pop
import Ganeti.Logging
54 358a0a8f Iustin Pop
import qualified Ganeti.Constants as C
55 1c3231aa Thomas Thrainer
import qualified Ganeti.Query.Cluster as QCluster
56 ea626b33 Iustin Pop
import Ganeti.Utils
57 358a0a8f Iustin Pop
58 358a0a8f Iustin Pop
-- * Types and constants definitions
59 358a0a8f Iustin Pop
60 358a0a8f Iustin Pop
-- | What we store as configuration.
61 358a0a8f Iustin Pop
type CRef = IORef (Result (ConfigData, LinkIpMap))
62 358a0a8f Iustin Pop
63 358a0a8f Iustin Pop
-- | A small type alias for readability.
64 358a0a8f Iustin Pop
type StatusAnswer = (ConfdReplyStatus, J.JSValue)
65 358a0a8f Iustin Pop
66 358a0a8f Iustin Pop
-- | Unknown entry standard response.
67 358a0a8f Iustin Pop
queryUnknownEntry :: StatusAnswer
68 358a0a8f Iustin Pop
queryUnknownEntry = (ReplyStatusError, J.showJSON ConfdErrorUnknownEntry)
69 358a0a8f Iustin Pop
70 358a0a8f Iustin Pop
{- not used yet
71 358a0a8f Iustin Pop
-- | Internal error standard response.
72 358a0a8f Iustin Pop
queryInternalError :: StatusAnswer
73 358a0a8f Iustin Pop
queryInternalError = (ReplyStatusError, J.showJSON ConfdErrorInternal)
74 358a0a8f Iustin Pop
-}
75 358a0a8f Iustin Pop
76 358a0a8f Iustin Pop
-- | Argument error standard response.
77 358a0a8f Iustin Pop
queryArgumentError :: StatusAnswer
78 358a0a8f Iustin Pop
queryArgumentError = (ReplyStatusError, J.showJSON ConfdErrorArgument)
79 358a0a8f Iustin Pop
80 5183e8be Iustin Pop
-- | Converter from specific error to a string format.
81 5183e8be Iustin Pop
gntErrorToResult :: ErrorResult a -> Result a
82 5183e8be Iustin Pop
gntErrorToResult (Bad err) = Bad (show err)
83 5183e8be Iustin Pop
gntErrorToResult (Ok x) = Ok x
84 5183e8be Iustin Pop
85 358a0a8f Iustin Pop
-- * Confd base functionality
86 358a0a8f Iustin Pop
87 358a0a8f Iustin Pop
-- | Computes the node role.
88 358a0a8f Iustin Pop
nodeRole :: ConfigData -> String -> Result ConfdNodeRole
89 1c3231aa Thomas Thrainer
nodeRole cfg name = do
90 1c3231aa Thomas Thrainer
  cmaster <- errToResult $ QCluster.clusterMasterNodeName cfg
91 1c3231aa Thomas Thrainer
  mnode <- errToResult $ getNode cfg name
92 1c3231aa Thomas Thrainer
  let role = case mnode of
93 1c3231aa Thomas Thrainer
               node | cmaster == name -> NodeRoleMaster
94 1c3231aa Thomas Thrainer
                    | nodeDrained node -> NodeRoleDrained
95 1c3231aa Thomas Thrainer
                    | nodeOffline node -> NodeRoleOffline
96 1c3231aa Thomas Thrainer
                    | nodeMasterCandidate node -> NodeRoleCandidate
97 1c3231aa Thomas Thrainer
               _ -> NodeRoleRegular
98 1c3231aa Thomas Thrainer
  return role
99 358a0a8f Iustin Pop
100 358a0a8f Iustin Pop
-- | Does an instance ip -> instance -> primary node -> primary ip
101 358a0a8f Iustin Pop
-- transformation.
102 358a0a8f Iustin Pop
getNodePipByInstanceIp :: ConfigData
103 358a0a8f Iustin Pop
                       -> LinkIpMap
104 358a0a8f Iustin Pop
                       -> String
105 358a0a8f Iustin Pop
                       -> String
106 358a0a8f Iustin Pop
                       -> StatusAnswer
107 358a0a8f Iustin Pop
getNodePipByInstanceIp cfg linkipmap link instip =
108 358a0a8f Iustin Pop
  case M.lookup instip (M.findWithDefault M.empty link linkipmap) of
109 358a0a8f Iustin Pop
    Nothing -> queryUnknownEntry
110 358a0a8f Iustin Pop
    Just instname ->
111 358a0a8f Iustin Pop
      case getInstPrimaryNode cfg instname of
112 358a0a8f Iustin Pop
        Bad _ -> queryUnknownEntry -- either instance or node not found
113 358a0a8f Iustin Pop
        Ok node -> (ReplyStatusOk, J.showJSON (nodePrimaryIp node))
114 358a0a8f Iustin Pop
115 358a0a8f Iustin Pop
-- | Builds the response to a given query.
116 358a0a8f Iustin Pop
buildResponse :: (ConfigData, LinkIpMap) -> ConfdRequest -> Result StatusAnswer
117 358a0a8f Iustin Pop
buildResponse (cfg, _) (ConfdRequest { confdRqType = ReqPing }) =
118 358a0a8f Iustin Pop
  return (ReplyStatusOk, J.showJSON (configVersion cfg))
119 358a0a8f Iustin Pop
120 358a0a8f Iustin Pop
buildResponse cdata req@(ConfdRequest { confdRqType = ReqClusterMaster }) =
121 358a0a8f Iustin Pop
  case confdRqQuery req of
122 1c3231aa Thomas Thrainer
    EmptyQuery -> liftM ((,) ReplyStatusOk . J.showJSON) master_name
123 358a0a8f Iustin Pop
    PlainQuery _ -> return queryArgumentError
124 358a0a8f Iustin Pop
    DictQuery reqq -> do
125 1c3231aa Thomas Thrainer
      mnode <- gntErrorToResult $ getNode cfg master_uuid
126 1c3231aa Thomas Thrainer
      mname <- master_name
127 5183e8be Iustin Pop
      let fvals = map (\field -> case field of
128 1c3231aa Thomas Thrainer
                                   ReqFieldName -> mname
129 5183e8be Iustin Pop
                                   ReqFieldIp -> clusterMasterIp cluster
130 5183e8be Iustin Pop
                                   ReqFieldMNodePip -> nodePrimaryIp mnode
131 5183e8be Iustin Pop
                      ) (confdReqQFields reqq)
132 358a0a8f Iustin Pop
      return (ReplyStatusOk, J.showJSON fvals)
133 1c3231aa Thomas Thrainer
    where master_uuid = clusterMasterNode cluster
134 1c3231aa Thomas Thrainer
          master_name = errToResult $ QCluster.clusterMasterNodeName cfg
135 358a0a8f Iustin Pop
          cluster = configCluster cfg
136 358a0a8f Iustin Pop
          cfg = fst cdata
137 358a0a8f Iustin Pop
138 358a0a8f Iustin Pop
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeRoleByName }) = do
139 358a0a8f Iustin Pop
  node_name <- case confdRqQuery req of
140 358a0a8f Iustin Pop
                 PlainQuery str -> return str
141 358a0a8f Iustin Pop
                 _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
142 358a0a8f Iustin Pop
  role <- nodeRole (fst cdata) node_name
143 358a0a8f Iustin Pop
  return (ReplyStatusOk, J.showJSON role)
144 358a0a8f Iustin Pop
145 358a0a8f Iustin Pop
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipList }) =
146 358a0a8f Iustin Pop
  -- note: we use foldlWithKey because that's present accross more
147 358a0a8f Iustin Pop
  -- versions of the library
148 358a0a8f Iustin Pop
  return (ReplyStatusOk, J.showJSON $
149 358a0a8f Iustin Pop
          M.foldlWithKey (\accu _ n -> nodePrimaryIp n:accu) []
150 84835174 Iustin Pop
          (fromContainer . configNodes . fst $ cdata))
151 358a0a8f Iustin Pop
152 358a0a8f Iustin Pop
buildResponse cdata (ConfdRequest { confdRqType = ReqMcPipList }) =
153 358a0a8f Iustin Pop
  -- note: we use foldlWithKey because that's present accross more
154 358a0a8f Iustin Pop
  -- versions of the library
155 358a0a8f Iustin Pop
  return (ReplyStatusOk, J.showJSON $
156 358a0a8f Iustin Pop
          M.foldlWithKey (\accu _ n -> if nodeMasterCandidate n
157 358a0a8f Iustin Pop
                                         then nodePrimaryIp n:accu
158 358a0a8f Iustin Pop
                                         else accu) []
159 84835174 Iustin Pop
          (fromContainer . configNodes . fst $ cdata))
160 358a0a8f Iustin Pop
161 358a0a8f Iustin Pop
buildResponse (cfg, linkipmap)
162 358a0a8f Iustin Pop
              req@(ConfdRequest { confdRqType = ReqInstIpsList }) = do
163 358a0a8f Iustin Pop
  link <- case confdRqQuery req of
164 358a0a8f Iustin Pop
            PlainQuery str -> return str
165 358a0a8f Iustin Pop
            EmptyQuery -> return (getDefaultNicLink cfg)
166 358a0a8f Iustin Pop
            _ -> fail "Invalid query type"
167 358a0a8f Iustin Pop
  return (ReplyStatusOk, J.showJSON $ getInstancesIpByLink linkipmap link)
168 358a0a8f Iustin Pop
169 358a0a8f Iustin Pop
buildResponse cdata (ConfdRequest { confdRqType = ReqNodePipByInstPip
170 358a0a8f Iustin Pop
                                  , confdRqQuery = DictQuery query}) =
171 358a0a8f Iustin Pop
  let (cfg, linkipmap) = cdata
172 2cdaf225 Iustin Pop
      link = fromMaybe (getDefaultNicLink cfg) (confdReqQLink query)
173 358a0a8f Iustin Pop
  in case confdReqQIp query of
174 358a0a8f Iustin Pop
       Just ip -> return $ getNodePipByInstanceIp cfg linkipmap link ip
175 358a0a8f Iustin Pop
       Nothing -> return (ReplyStatusOk,
176 358a0a8f Iustin Pop
                          J.showJSON $
177 358a0a8f Iustin Pop
                           map (getNodePipByInstanceIp cfg linkipmap link)
178 358a0a8f Iustin Pop
                           (confdReqQIpList query))
179 358a0a8f Iustin Pop
180 358a0a8f Iustin Pop
buildResponse _ (ConfdRequest { confdRqType = ReqNodePipByInstPip }) =
181 358a0a8f Iustin Pop
  return queryArgumentError
182 358a0a8f Iustin Pop
183 d81ec8b7 Iustin Pop
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeDrbd }) = do
184 d81ec8b7 Iustin Pop
  let cfg = fst cdata
185 d81ec8b7 Iustin Pop
  node_name <- case confdRqQuery req of
186 d81ec8b7 Iustin Pop
                 PlainQuery str -> return str
187 d81ec8b7 Iustin Pop
                 _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
188 5183e8be Iustin Pop
  node <- gntErrorToResult $ getNode cfg node_name
189 d81ec8b7 Iustin Pop
  let minors = concatMap (getInstMinorsForNode (nodeName node)) .
190 84835174 Iustin Pop
               M.elems . fromContainer . configInstances $ cfg
191 d81ec8b7 Iustin Pop
      encoded = [J.JSArray [J.showJSON a, J.showJSON b, J.showJSON c,
192 d81ec8b7 Iustin Pop
                             J.showJSON d, J.showJSON e, J.showJSON f] |
193 d81ec8b7 Iustin Pop
                 (a, b, c, d, e, f) <- minors]
194 d81ec8b7 Iustin Pop
  return (ReplyStatusOk, J.showJSON encoded)
195 d81ec8b7 Iustin Pop
196 1f005f16 Michele Tartara
-- | Return the list of instances for a node (as ([primary], [secondary])) given
197 1f005f16 Michele Tartara
-- the node name.
198 332a83ca Michele Tartara
buildResponse cdata req@(ConfdRequest { confdRqType = ReqNodeInstances }) = do
199 332a83ca Michele Tartara
  let cfg = fst cdata
200 332a83ca Michele Tartara
  node_name <- case confdRqQuery req of
201 332a83ca Michele Tartara
                PlainQuery str -> return str
202 332a83ca Michele Tartara
                _ -> fail $ "Invalid query type " ++ show (confdRqQuery req)
203 1f005f16 Michele Tartara
  node <-
204 1f005f16 Michele Tartara
    case getNode cfg node_name of
205 1f005f16 Michele Tartara
      Ok n -> return n
206 1f005f16 Michele Tartara
      Bad e -> fail $ "Node not found in the configuration: " ++ show e
207 1f005f16 Michele Tartara
  let node_uuid = nodeUuid node
208 1f005f16 Michele Tartara
      instances = getNodeInstances cfg node_uuid
209 332a83ca Michele Tartara
  return (ReplyStatusOk, J.showJSON instances)
210 332a83ca Michele Tartara
211 358a0a8f Iustin Pop
-- | Creates a ConfdReply from a given answer.
212 358a0a8f Iustin Pop
serializeResponse :: Result StatusAnswer -> ConfdReply
213 358a0a8f Iustin Pop
serializeResponse r =
214 358a0a8f Iustin Pop
    let (status, result) = case r of
215 358a0a8f Iustin Pop
                    Bad err -> (ReplyStatusError, J.showJSON err)
216 358a0a8f Iustin Pop
                    Ok (code, val) -> (code, val)
217 358a0a8f Iustin Pop
    in ConfdReply { confdReplyProtocol = 1
218 358a0a8f Iustin Pop
                  , confdReplyStatus   = status
219 358a0a8f Iustin Pop
                  , confdReplyAnswer   = result
220 358a0a8f Iustin Pop
                  , confdReplySerial   = 0 }
221 358a0a8f Iustin Pop
222 358a0a8f Iustin Pop
-- ** Client input/output handlers
223 358a0a8f Iustin Pop
224 358a0a8f Iustin Pop
-- | Main loop for a given client.
225 358a0a8f Iustin Pop
responder :: CRef -> S.Socket -> HashKey -> String -> S.SockAddr -> IO ()
226 358a0a8f Iustin Pop
responder cfgref socket hmac msg peer = do
227 358a0a8f Iustin Pop
  ctime <- getCurrentTime
228 497f5cbf Michele Tartara
  case parseRequest hmac msg ctime of
229 358a0a8f Iustin Pop
    Ok (origmsg, rq) -> do
230 ea626b33 Iustin Pop
              logDebug $ "Processing request: " ++ rStripSpace origmsg
231 358a0a8f Iustin Pop
              mcfg <- readIORef cfgref
232 358a0a8f Iustin Pop
              let response = respondInner mcfg hmac rq
233 358a0a8f Iustin Pop
              _ <- S.sendTo socket response peer
234 e2625797 Michele Tartara
              logDebug $ "Response sent: " ++ response
235 358a0a8f Iustin Pop
              return ()
236 358a0a8f Iustin Pop
    Bad err -> logInfo $ "Failed to parse incoming message: " ++ err
237 358a0a8f Iustin Pop
  return ()
238 358a0a8f Iustin Pop
239 358a0a8f Iustin Pop
-- | Inner helper function for a given client. This generates the
240 358a0a8f Iustin Pop
-- final encoded message (as a string), ready to be sent out to the
241 358a0a8f Iustin Pop
-- client.
242 358a0a8f Iustin Pop
respondInner :: Result (ConfigData, LinkIpMap) -> HashKey
243 358a0a8f Iustin Pop
             -> ConfdRequest -> String
244 358a0a8f Iustin Pop
respondInner cfg hmac rq =
245 358a0a8f Iustin Pop
  let rsalt = confdRqRsalt rq
246 358a0a8f Iustin Pop
      innermsg = serializeResponse (cfg >>= flip buildResponse rq)
247 358a0a8f Iustin Pop
      innerserialised = J.encodeStrict innermsg
248 358a0a8f Iustin Pop
      outermsg = signMessage hmac rsalt innerserialised
249 358a0a8f Iustin Pop
      outerserialised = confdMagicFourcc ++ J.encodeStrict outermsg
250 358a0a8f Iustin Pop
  in outerserialised
251 358a0a8f Iustin Pop
252 358a0a8f Iustin Pop
-- | Main listener loop.
253 358a0a8f Iustin Pop
listener :: S.Socket -> HashKey
254 358a0a8f Iustin Pop
         -> (S.Socket -> HashKey -> String -> S.SockAddr -> IO ())
255 358a0a8f Iustin Pop
         -> IO ()
256 358a0a8f Iustin Pop
listener s hmac resp = do
257 358a0a8f Iustin Pop
  (msg, _, peer) <- S.recvFrom s 4096
258 358a0a8f Iustin Pop
  if confdMagicFourcc `isPrefixOf` msg
259 5b11f8db Iustin Pop
    then forkIO (resp s hmac (drop 4 msg) peer) >> return ()
260 358a0a8f Iustin Pop
    else logDebug "Invalid magic code!" >> return ()
261 358a0a8f Iustin Pop
  return ()
262 358a0a8f Iustin Pop
263 ef3de7b0 Iustin Pop
-- | Type alias for prepMain results
264 670e954a Thomas Thrainer
type PrepResult = (S.Socket, IORef (Result (ConfigData, LinkIpMap)))
265 ef3de7b0 Iustin Pop
266 2ac2e420 Iustin Pop
-- | Check function for confd.
267 ef3de7b0 Iustin Pop
checkMain :: CheckFn (S.Family, S.SockAddr)
268 ef3de7b0 Iustin Pop
checkMain opts = do
269 ef3de7b0 Iustin Pop
  parseresult <- parseAddress opts C.defaultConfdPort
270 ef3de7b0 Iustin Pop
  case parseresult of
271 ef3de7b0 Iustin Pop
    Bad msg -> do
272 ef3de7b0 Iustin Pop
      hPutStrLn stderr $ "parsing bind address: " ++ msg
273 ef3de7b0 Iustin Pop
      return . Left $ ExitFailure 1
274 ef3de7b0 Iustin Pop
    Ok v -> return $ Right v
275 2ac2e420 Iustin Pop
276 2ac2e420 Iustin Pop
-- | Prepare function for confd.
277 ef3de7b0 Iustin Pop
prepMain :: PrepFn (S.Family, S.SockAddr) PrepResult
278 ef3de7b0 Iustin Pop
prepMain _ (af_family, bindaddr) = do
279 19cff311 Iustin Pop
  s <- S.socket af_family S.Datagram S.defaultProtocol
280 19cff311 Iustin Pop
  S.bindSocket s bindaddr
281 358a0a8f Iustin Pop
  cref <- newIORef (Bad "Configuration not yet loaded")
282 670e954a Thomas Thrainer
  return (s, cref)
283 ef3de7b0 Iustin Pop
284 ef3de7b0 Iustin Pop
-- | Main function.
285 ef3de7b0 Iustin Pop
main :: MainFn (S.Family, S.SockAddr) PrepResult
286 670e954a Thomas Thrainer
main _ _ (s, cref) = do
287 218e3b0f Thomas Thrainer
  let cfg_transform :: Result ConfigData -> Result (ConfigData, LinkIpMap)
288 218e3b0f Thomas Thrainer
      cfg_transform = liftM (\cfg -> (cfg, buildLinkIpInstnameMap cfg))
289 218e3b0f Thomas Thrainer
  initConfigReader cfg_transform cref
290 218e3b0f Thomas Thrainer
291 c62df702 Iustin Pop
  hmac <- getClusterHmac
292 670e954a Thomas Thrainer
  -- enter the responder loop
293 358a0a8f Iustin Pop
  forever $ listener s hmac (responder cref)