Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / InstStatus.hs @ 7ea201c9

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