Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / InstStatus.hs @ 17ae9cdb

History | View | Annotate | Download (5.5 kB)

1 d7e9323b Michele Tartara
{-| Instance status data collector.
2 d7e9323b Michele Tartara
3 d7e9323b Michele Tartara
-}
4 d7e9323b Michele Tartara
5 d7e9323b Michele Tartara
{-
6 d7e9323b Michele Tartara
7 d7e9323b Michele Tartara
Copyright (C) 2013 Google Inc.
8 d7e9323b Michele Tartara
9 d7e9323b Michele Tartara
This program is free software; you can redistribute it and/or modify
10 d7e9323b Michele Tartara
it under the terms of the GNU General Public License as published by
11 d7e9323b Michele Tartara
the Free Software Foundation; either version 2 of the License, or
12 d7e9323b Michele Tartara
(at your option) any later version.
13 d7e9323b Michele Tartara
14 d7e9323b Michele Tartara
This program is distributed in the hope that it will be useful, but
15 d7e9323b Michele Tartara
WITHOUT ANY WARRANTY; without even the implied warranty of
16 d7e9323b Michele Tartara
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 d7e9323b Michele Tartara
General Public License for more details.
18 d7e9323b Michele Tartara
19 d7e9323b Michele Tartara
You should have received a copy of the GNU General Public License
20 d7e9323b Michele Tartara
along with this program; if not, write to the Free Software
21 d7e9323b Michele Tartara
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 d7e9323b Michele Tartara
02110-1301, USA.
23 d7e9323b Michele Tartara
24 d7e9323b Michele Tartara
-}
25 d7e9323b Michele Tartara
26 d7e9323b Michele Tartara
module Ganeti.DataCollectors.InstStatus
27 d7e9323b Michele Tartara
  ( main
28 d7e9323b Michele Tartara
  , options
29 d7e9323b Michele Tartara
  , arguments
30 d7e9323b Michele Tartara
  ) where
31 d7e9323b Michele Tartara
32 d7e9323b Michele Tartara
33 17ae9cdb Michele Tartara
import Control.Exception.Base
34 d7e9323b Michele Tartara
import Data.Maybe
35 d7e9323b Michele Tartara
import qualified Data.Map as Map
36 d7e9323b Michele Tartara
import Network.BSD (getHostName)
37 d7e9323b Michele Tartara
import qualified Text.JSON as J
38 d7e9323b Michele Tartara
39 d7e9323b Michele Tartara
import qualified Ganeti.BasicTypes as BT
40 d7e9323b Michele Tartara
import Ganeti.Confd.Client
41 d7e9323b Michele Tartara
import Ganeti.Confd.Types
42 d7e9323b Michele Tartara
import Ganeti.Common
43 d7e9323b Michele Tartara
import Ganeti.DataCollectors.CLI
44 d7e9323b Michele Tartara
import Ganeti.DataCollectors.InstStatusTypes
45 fc4be2bf Michele Tartara
import Ganeti.DataCollectors.Types
46 d7e9323b Michele Tartara
import Ganeti.Hypervisor.Xen
47 d4de2ea8 Michele Tartara
import Ganeti.Hypervisor.Xen.Types
48 17ae9cdb Michele Tartara
import Ganeti.Logging
49 d7e9323b Michele Tartara
import Ganeti.Objects
50 17ae9cdb Michele Tartara
import Ganeti.Path
51 17ae9cdb Michele Tartara
import Ganeti.Types
52 d7e9323b Michele Tartara
import Ganeti.Utils
53 d7e9323b Michele Tartara
54 d7e9323b Michele Tartara
-- * Command line options
55 d7e9323b Michele Tartara
56 d7e9323b Michele Tartara
options :: IO [OptType]
57 d7e9323b Michele Tartara
options = return
58 d7e9323b Michele Tartara
  [ oConfdAddr
59 d7e9323b Michele Tartara
  , oConfdPort
60 d7e9323b Michele Tartara
  ]
61 d7e9323b Michele Tartara
62 d7e9323b Michele Tartara
-- | The list of arguments supported by the program.
63 d7e9323b Michele Tartara
arguments :: [ArgCompletion]
64 d7e9323b Michele Tartara
arguments = []
65 d7e9323b Michele Tartara
66 d7e9323b Michele Tartara
-- | Get the list of instances ([primary], [secondary]) on the given node.
67 d7e9323b Michele Tartara
-- Implemented as a function, even if used a single time, to specify in a
68 d7e9323b Michele Tartara
-- convenient and elegant way the return data type, required in order to
69 d7e9323b Michele Tartara
-- prevent incurring in the monomorphism restriction.
70 d7e9323b Michele Tartara
-- The server address and the server port parameters are mainly intended
71 d7e9323b Michele Tartara
-- for testing purposes. If they are Nothing, the default values will be used.
72 d7e9323b Michele Tartara
getInstances
73 d7e9323b Michele Tartara
  :: String
74 d7e9323b Michele Tartara
  -> Maybe String
75 d7e9323b Michele Tartara
  -> Maybe Int
76 d7e9323b Michele Tartara
  -> IO (BT.Result ([Ganeti.Objects.Instance], [Ganeti.Objects.Instance]))
77 d7e9323b Michele Tartara
getInstances node srvAddr srvPort = do
78 d7e9323b Michele Tartara
  client <- getConfdClient srvAddr srvPort
79 d7e9323b Michele Tartara
  reply <- query client ReqNodeInstances $ PlainQuery node
80 d7e9323b Michele Tartara
  return $
81 d7e9323b Michele Tartara
    case fmap (J.readJSON . confdReplyAnswer) reply of
82 d7e9323b Michele Tartara
      Just (J.Ok instances) -> BT.Ok instances
83 d7e9323b Michele Tartara
      Just (J.Error msg) -> BT.Bad msg
84 d7e9323b Michele Tartara
      Nothing -> BT.Bad "No answer from the Confd server"
85 d7e9323b Michele Tartara
86 17ae9cdb Michele Tartara
-- | Try to get the reason trail for an instance. In case it is not possible,
87 17ae9cdb Michele Tartara
-- log the failure and return an empty list instead.
88 17ae9cdb Michele Tartara
getReasonTrail :: String -> IO ReasonTrail
89 17ae9cdb Michele Tartara
getReasonTrail instanceName = do
90 17ae9cdb Michele Tartara
  fileName <- getInstReasonFilename instanceName
91 17ae9cdb Michele Tartara
  content <- try $ readFile fileName
92 17ae9cdb Michele Tartara
  case content of
93 17ae9cdb Michele Tartara
    Left e -> do
94 17ae9cdb Michele Tartara
      logWarning $
95 17ae9cdb Michele Tartara
        "Unable to open the reason trail for instance " ++ instanceName ++
96 17ae9cdb Michele Tartara
        " expected at " ++ fileName ++ ": " ++ show (e :: IOException)
97 17ae9cdb Michele Tartara
      return []
98 17ae9cdb Michele Tartara
    Right trailString ->
99 17ae9cdb Michele Tartara
      case J.decode trailString of
100 17ae9cdb Michele Tartara
        J.Ok t -> return t
101 17ae9cdb Michele Tartara
        J.Error msg -> do
102 17ae9cdb Michele Tartara
          logWarning $ "Unable to parse the reason trail: " ++ msg
103 17ae9cdb Michele Tartara
          return []
104 17ae9cdb Michele Tartara
105 fc4be2bf Michele Tartara
-- | Determine the value of the status field for the report of one instance
106 fc4be2bf Michele Tartara
computeStatusField :: AdminState -> ActualState -> DCStatus
107 fc4be2bf Michele Tartara
computeStatusField AdminDown actualState =
108 fc4be2bf Michele Tartara
  if actualState `notElem` [ActualShutdown, ActualDying]
109 fc4be2bf Michele Tartara
    then DCStatus DCSCBad "The instance is not stopped as it should be"
110 fc4be2bf Michele Tartara
    else DCStatus DCSCOk ""
111 fc4be2bf Michele Tartara
computeStatusField AdminUp ActualHung =
112 fc4be2bf Michele Tartara
  DCStatus DCSCUnknown "Instance marked as running, but it appears to be hung"
113 fc4be2bf Michele Tartara
computeStatusField AdminUp actualState =
114 fc4be2bf Michele Tartara
  if actualState `notElem` [ActualRunning, ActualBlocked]
115 fc4be2bf Michele Tartara
    then DCStatus DCSCBad "The instance is not running as it should be"
116 fc4be2bf Michele Tartara
    else DCStatus DCSCOk ""
117 fc4be2bf Michele Tartara
computeStatusField AdminOffline _ =
118 fc4be2bf Michele Tartara
  -- FIXME: The "offline" status seems not to be used anywhere in the source
119 fc4be2bf Michele Tartara
  -- code, but it is defined, so we have to consider it anyway here.
120 fc4be2bf Michele Tartara
  DCStatus DCSCUnknown "The instance is marked as offline"
121 fc4be2bf Michele Tartara
122 d7e9323b Michele Tartara
-- Builds the status of an instance using runtime information about the Xen
123 d7e9323b Michele Tartara
-- Domains, their uptime information and the static information provided by
124 d7e9323b Michele Tartara
-- the ConfD server.
125 d7e9323b Michele Tartara
buildStatus :: Map.Map String Domain -> Map.Map Int UptimeInfo -> Instance
126 d7e9323b Michele Tartara
  -> IO InstStatus
127 d7e9323b Michele Tartara
buildStatus domains uptimes inst = do
128 d7e9323b Michele Tartara
  let name = instName inst
129 d7e9323b Michele Tartara
      currDomain = Map.lookup name domains
130 d7e9323b Michele Tartara
      idNum = fmap domId currDomain
131 d7e9323b Michele Tartara
      currUInfo = idNum >>= (`Map.lookup` uptimes)
132 d7e9323b Michele Tartara
      uptime = fmap uInfoUptime currUInfo
133 d7e9323b Michele Tartara
      adminState = instAdminState inst
134 d4de2ea8 Michele Tartara
      actualState =
135 d4de2ea8 Michele Tartara
        if adminState == AdminDown && isNothing currDomain
136 d4de2ea8 Michele Tartara
          then ActualShutdown
137 d4de2ea8 Michele Tartara
          else case currDomain of
138 d4de2ea8 Michele Tartara
            (Just dom@(Domain _ _ _ _ (Just isHung))) ->
139 d4de2ea8 Michele Tartara
              if isHung
140 d4de2ea8 Michele Tartara
                then ActualHung
141 d4de2ea8 Michele Tartara
                else domState dom
142 d4de2ea8 Michele Tartara
            _ -> ActualUnknown
143 fc4be2bf Michele Tartara
      status = computeStatusField adminState actualState
144 17ae9cdb Michele Tartara
  trail <- getReasonTrail name
145 d7e9323b Michele Tartara
  return $
146 d7e9323b Michele Tartara
    InstStatus
147 d7e9323b Michele Tartara
      name
148 d7e9323b Michele Tartara
      (instUuid inst)
149 d7e9323b Michele Tartara
      adminState
150 d4de2ea8 Michele Tartara
      actualState
151 d7e9323b Michele Tartara
      uptime
152 d7e9323b Michele Tartara
      (instMtime inst)
153 17ae9cdb Michele Tartara
      trail
154 fc4be2bf Michele Tartara
      status
155 d7e9323b Michele Tartara
156 d7e9323b Michele Tartara
-- | Main function.
157 d7e9323b Michele Tartara
main :: Options -> [String] -> IO ()
158 d7e9323b Michele Tartara
main opts _ = do
159 d7e9323b Michele Tartara
  curNode <- getHostName
160 d7e9323b Michele Tartara
  let node = fromMaybe curNode $ optNode opts
161 d7e9323b Michele Tartara
  answer <- getInstances node (optConfdAddr opts) (optConfdPort opts)
162 d7e9323b Michele Tartara
  inst <- exitIfBad "Can't get instance info from ConfD" answer
163 d7e9323b Michele Tartara
  domains <- getInferredDomInfo
164 d7e9323b Michele Tartara
  uptimes <- getUptimeInfo
165 d7e9323b Michele Tartara
  let primaryInst =  fst inst
166 d7e9323b Michele Tartara
  iStatus <- mapM (buildStatus domains uptimes) primaryInst
167 d7e9323b Michele Tartara
  putStrLn $ J.encode iStatus