Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / InstStatus.hs @ b54ecf12

History | View | Annotate | Download (7.2 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 7660aaf3 Michele Tartara
  , dcName
31 7660aaf3 Michele Tartara
  , dcVersion
32 7660aaf3 Michele Tartara
  , dcFormatVersion
33 7660aaf3 Michele Tartara
  , dcCategory
34 7660aaf3 Michele Tartara
  , dcKind
35 e8b46463 Michele Tartara
  , dcReport
36 d7e9323b Michele Tartara
  ) where
37 d7e9323b Michele Tartara
38 d7e9323b Michele Tartara
39 17ae9cdb Michele Tartara
import Control.Exception.Base
40 79731e21 Michele Tartara
import Data.List
41 d7e9323b Michele Tartara
import Data.Maybe
42 d7e9323b Michele Tartara
import qualified Data.Map as Map
43 d7e9323b Michele Tartara
import Network.BSD (getHostName)
44 d7e9323b Michele Tartara
import qualified Text.JSON as J
45 d7e9323b Michele Tartara
46 d7e9323b Michele Tartara
import qualified Ganeti.BasicTypes as BT
47 d7e9323b Michele Tartara
import Ganeti.Confd.Client
48 d7e9323b Michele Tartara
import Ganeti.Confd.Types
49 d7e9323b Michele Tartara
import Ganeti.Common
50 d7e9323b Michele Tartara
import Ganeti.DataCollectors.CLI
51 d7e9323b Michele Tartara
import Ganeti.DataCollectors.InstStatusTypes
52 fc4be2bf Michele Tartara
import Ganeti.DataCollectors.Types
53 d7e9323b Michele Tartara
import Ganeti.Hypervisor.Xen
54 d4de2ea8 Michele Tartara
import Ganeti.Hypervisor.Xen.Types
55 17ae9cdb Michele Tartara
import Ganeti.Logging
56 d7e9323b Michele Tartara
import Ganeti.Objects
57 17ae9cdb Michele Tartara
import Ganeti.Path
58 17ae9cdb Michele Tartara
import Ganeti.Types
59 d7e9323b Michele Tartara
import Ganeti.Utils
60 d7e9323b Michele Tartara
61 7660aaf3 Michele Tartara
62 7660aaf3 Michele Tartara
-- | The name of this data collector.
63 7660aaf3 Michele Tartara
dcName :: String
64 7660aaf3 Michele Tartara
dcName = "inst-status-xen"
65 7660aaf3 Michele Tartara
66 7660aaf3 Michele Tartara
-- | The version of this data collector.
67 7660aaf3 Michele Tartara
dcVersion :: DCVersion
68 7660aaf3 Michele Tartara
dcVersion = DCVerBuiltin
69 7660aaf3 Michele Tartara
70 7660aaf3 Michele Tartara
-- | The version number for the data format of this data collector.
71 7660aaf3 Michele Tartara
dcFormatVersion :: Int
72 7660aaf3 Michele Tartara
dcFormatVersion = 1
73 7660aaf3 Michele Tartara
74 7660aaf3 Michele Tartara
-- | The category of this data collector.
75 7660aaf3 Michele Tartara
dcCategory :: Maybe DCCategory
76 7660aaf3 Michele Tartara
dcCategory = Just DCInstance
77 7660aaf3 Michele Tartara
78 7660aaf3 Michele Tartara
-- | The kind of this data collector.
79 7660aaf3 Michele Tartara
dcKind :: DCKind
80 7660aaf3 Michele Tartara
dcKind = DCKStatus
81 7660aaf3 Michele Tartara
82 e8b46463 Michele Tartara
-- | The report of this data collector.
83 e8b46463 Michele Tartara
dcReport :: IO DCReport
84 e8b46463 Michele Tartara
dcReport = buildInstStatusReport Nothing Nothing
85 e8b46463 Michele Tartara
86 d7e9323b Michele Tartara
-- * Command line options
87 d7e9323b Michele Tartara
88 d7e9323b Michele Tartara
options :: IO [OptType]
89 d7e9323b Michele Tartara
options = return
90 d7e9323b Michele Tartara
  [ oConfdAddr
91 d7e9323b Michele Tartara
  , oConfdPort
92 d7e9323b Michele Tartara
  ]
93 d7e9323b Michele Tartara
94 d7e9323b Michele Tartara
-- | The list of arguments supported by the program.
95 d7e9323b Michele Tartara
arguments :: [ArgCompletion]
96 d7e9323b Michele Tartara
arguments = []
97 d7e9323b Michele Tartara
98 d7e9323b Michele Tartara
-- | Get the list of instances ([primary], [secondary]) on the given node.
99 d7e9323b Michele Tartara
-- Implemented as a function, even if used a single time, to specify in a
100 d7e9323b Michele Tartara
-- convenient and elegant way the return data type, required in order to
101 d7e9323b Michele Tartara
-- prevent incurring in the monomorphism restriction.
102 d7e9323b Michele Tartara
-- The server address and the server port parameters are mainly intended
103 d7e9323b Michele Tartara
-- for testing purposes. If they are Nothing, the default values will be used.
104 d7e9323b Michele Tartara
getInstances
105 d7e9323b Michele Tartara
  :: String
106 d7e9323b Michele Tartara
  -> Maybe String
107 d7e9323b Michele Tartara
  -> Maybe Int
108 d7e9323b Michele Tartara
  -> IO (BT.Result ([Ganeti.Objects.Instance], [Ganeti.Objects.Instance]))
109 d7e9323b Michele Tartara
getInstances node srvAddr srvPort = do
110 d7e9323b Michele Tartara
  client <- getConfdClient srvAddr srvPort
111 d7e9323b Michele Tartara
  reply <- query client ReqNodeInstances $ PlainQuery node
112 d7e9323b Michele Tartara
  return $
113 d7e9323b Michele Tartara
    case fmap (J.readJSON . confdReplyAnswer) reply of
114 d7e9323b Michele Tartara
      Just (J.Ok instances) -> BT.Ok instances
115 d7e9323b Michele Tartara
      Just (J.Error msg) -> BT.Bad msg
116 d7e9323b Michele Tartara
      Nothing -> BT.Bad "No answer from the Confd server"
117 d7e9323b Michele Tartara
118 17ae9cdb Michele Tartara
-- | Try to get the reason trail for an instance. In case it is not possible,
119 17ae9cdb Michele Tartara
-- log the failure and return an empty list instead.
120 17ae9cdb Michele Tartara
getReasonTrail :: String -> IO ReasonTrail
121 17ae9cdb Michele Tartara
getReasonTrail instanceName = do
122 17ae9cdb Michele Tartara
  fileName <- getInstReasonFilename instanceName
123 17ae9cdb Michele Tartara
  content <- try $ readFile fileName
124 17ae9cdb Michele Tartara
  case content of
125 17ae9cdb Michele Tartara
    Left e -> do
126 17ae9cdb Michele Tartara
      logWarning $
127 17ae9cdb Michele Tartara
        "Unable to open the reason trail for instance " ++ instanceName ++
128 17ae9cdb Michele Tartara
        " expected at " ++ fileName ++ ": " ++ show (e :: IOException)
129 17ae9cdb Michele Tartara
      return []
130 17ae9cdb Michele Tartara
    Right trailString ->
131 17ae9cdb Michele Tartara
      case J.decode trailString of
132 17ae9cdb Michele Tartara
        J.Ok t -> return t
133 17ae9cdb Michele Tartara
        J.Error msg -> do
134 17ae9cdb Michele Tartara
          logWarning $ "Unable to parse the reason trail: " ++ msg
135 17ae9cdb Michele Tartara
          return []
136 17ae9cdb Michele Tartara
137 fc4be2bf Michele Tartara
-- | Determine the value of the status field for the report of one instance
138 fc4be2bf Michele Tartara
computeStatusField :: AdminState -> ActualState -> DCStatus
139 fc4be2bf Michele Tartara
computeStatusField AdminDown actualState =
140 fc4be2bf Michele Tartara
  if actualState `notElem` [ActualShutdown, ActualDying]
141 fc4be2bf Michele Tartara
    then DCStatus DCSCBad "The instance is not stopped as it should be"
142 fc4be2bf Michele Tartara
    else DCStatus DCSCOk ""
143 fc4be2bf Michele Tartara
computeStatusField AdminUp ActualHung =
144 fc4be2bf Michele Tartara
  DCStatus DCSCUnknown "Instance marked as running, but it appears to be hung"
145 fc4be2bf Michele Tartara
computeStatusField AdminUp actualState =
146 fc4be2bf Michele Tartara
  if actualState `notElem` [ActualRunning, ActualBlocked]
147 fc4be2bf Michele Tartara
    then DCStatus DCSCBad "The instance is not running as it should be"
148 fc4be2bf Michele Tartara
    else DCStatus DCSCOk ""
149 fc4be2bf Michele Tartara
computeStatusField AdminOffline _ =
150 fc4be2bf Michele Tartara
  -- FIXME: The "offline" status seems not to be used anywhere in the source
151 fc4be2bf Michele Tartara
  -- code, but it is defined, so we have to consider it anyway here.
152 fc4be2bf Michele Tartara
  DCStatus DCSCUnknown "The instance is marked as offline"
153 fc4be2bf Michele Tartara
154 d7e9323b Michele Tartara
-- Builds the status of an instance using runtime information about the Xen
155 d7e9323b Michele Tartara
-- Domains, their uptime information and the static information provided by
156 d7e9323b Michele Tartara
-- the ConfD server.
157 d7e9323b Michele Tartara
buildStatus :: Map.Map String Domain -> Map.Map Int UptimeInfo -> Instance
158 d7e9323b Michele Tartara
  -> IO InstStatus
159 d7e9323b Michele Tartara
buildStatus domains uptimes inst = do
160 d7e9323b Michele Tartara
  let name = instName inst
161 d7e9323b Michele Tartara
      currDomain = Map.lookup name domains
162 d7e9323b Michele Tartara
      idNum = fmap domId currDomain
163 d7e9323b Michele Tartara
      currUInfo = idNum >>= (`Map.lookup` uptimes)
164 d7e9323b Michele Tartara
      uptime = fmap uInfoUptime currUInfo
165 d7e9323b Michele Tartara
      adminState = instAdminState inst
166 d4de2ea8 Michele Tartara
      actualState =
167 d4de2ea8 Michele Tartara
        if adminState == AdminDown && isNothing currDomain
168 d4de2ea8 Michele Tartara
          then ActualShutdown
169 d4de2ea8 Michele Tartara
          else case currDomain of
170 d4de2ea8 Michele Tartara
            (Just dom@(Domain _ _ _ _ (Just isHung))) ->
171 d4de2ea8 Michele Tartara
              if isHung
172 d4de2ea8 Michele Tartara
                then ActualHung
173 d4de2ea8 Michele Tartara
                else domState dom
174 d4de2ea8 Michele Tartara
            _ -> ActualUnknown
175 fc4be2bf Michele Tartara
      status = computeStatusField adminState actualState
176 17ae9cdb Michele Tartara
  trail <- getReasonTrail name
177 d7e9323b Michele Tartara
  return $
178 d7e9323b Michele Tartara
    InstStatus
179 d7e9323b Michele Tartara
      name
180 d7e9323b Michele Tartara
      (instUuid inst)
181 d7e9323b Michele Tartara
      adminState
182 d4de2ea8 Michele Tartara
      actualState
183 d7e9323b Michele Tartara
      uptime
184 d7e9323b Michele Tartara
      (instMtime inst)
185 17ae9cdb Michele Tartara
      trail
186 fc4be2bf Michele Tartara
      status
187 d7e9323b Michele Tartara
188 79731e21 Michele Tartara
-- | Compute the status code and message, given the current DRBD data
189 79731e21 Michele Tartara
-- The final state will have the code corresponding to the worst code of
190 79731e21 Michele Tartara
-- all the devices, and the error message given from the concatenation of the
191 79731e21 Michele Tartara
-- non-empty error messages.
192 79731e21 Michele Tartara
computeGlobalStatus :: [InstStatus] -> DCStatus
193 79731e21 Michele Tartara
computeGlobalStatus instStatusList =
194 79731e21 Michele Tartara
  let dcstatuses = map iStatStatus instStatusList
195 79731e21 Michele Tartara
      statuses = map (\s -> (dcStatusCode s, dcStatusMessage s)) dcstatuses
196 79731e21 Michele Tartara
      (code, strList) = foldr mergeStatuses (DCSCOk, [""]) statuses
197 79731e21 Michele Tartara
  in DCStatus code $ intercalate "\n" strList
198 79731e21 Michele Tartara
199 4fe04580 Michele Tartara
-- | Build the report of this data collector, containing all the information
200 4fe04580 Michele Tartara
-- about the status of the instances.
201 4fe04580 Michele Tartara
buildInstStatusReport :: Maybe String -> Maybe Int -> IO DCReport
202 4fe04580 Michele Tartara
buildInstStatusReport srvAddr srvPort = do
203 4fe04580 Michele Tartara
  node <- getHostName
204 4fe04580 Michele Tartara
  answer <- getInstances node srvAddr srvPort
205 d7e9323b Michele Tartara
  inst <- exitIfBad "Can't get instance info from ConfD" answer
206 d7e9323b Michele Tartara
  domains <- getInferredDomInfo
207 d7e9323b Michele Tartara
  uptimes <- getUptimeInfo
208 d7e9323b Michele Tartara
  let primaryInst =  fst inst
209 d7e9323b Michele Tartara
  iStatus <- mapM (buildStatus domains uptimes) primaryInst
210 79731e21 Michele Tartara
  let globalStatus = computeGlobalStatus iStatus
211 79731e21 Michele Tartara
      jsonReport = J.showJSON $ ReportData iStatus globalStatus
212 4fe04580 Michele Tartara
  buildReport dcName dcVersion dcFormatVersion dcCategory dcKind jsonReport
213 4fe04580 Michele Tartara
214 4fe04580 Michele Tartara
-- | Main function.
215 4fe04580 Michele Tartara
main :: Options -> [String] -> IO ()
216 4fe04580 Michele Tartara
main opts _ = do
217 4fe04580 Michele Tartara
  report <- buildInstStatusReport (optConfdAddr opts) (optConfdPort opts)
218 4fe04580 Michele Tartara
  putStrLn $ J.encode report