Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / InstStatus.hs @ 9611c32e

History | View | Annotate | Download (6.2 kB)

1
{-| Instance status data collector.
2

    
3
-}
4

    
5
{-
6

    
7
Copyright (C) 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.DataCollectors.InstStatus
27
  ( main
28
  , options
29
  , arguments
30
  , dcName
31
  , dcVersion
32
  , dcFormatVersion
33
  , dcCategory
34
  , dcKind
35
  , dcReport
36
  ) where
37

    
38

    
39
import Control.Exception.Base
40
import Data.List
41
import Data.Maybe
42
import qualified Data.Map as Map
43
import Network.BSD (getHostName)
44
import qualified Text.JSON as J
45

    
46
import Ganeti.Confd.ClientFunctions
47
import Ganeti.Common
48
import Ganeti.DataCollectors.CLI
49
import Ganeti.DataCollectors.InstStatusTypes
50
import Ganeti.DataCollectors.Types
51
import Ganeti.Hypervisor.Xen
52
import Ganeti.Hypervisor.Xen.Types
53
import Ganeti.Logging
54
import Ganeti.Objects
55
import Ganeti.Path
56
import Ganeti.Types
57
import Ganeti.Utils
58

    
59

    
60
-- | The name of this data collector.
61
dcName :: String
62
dcName = "inst-status-xen"
63

    
64
-- | The version of this data collector.
65
dcVersion :: DCVersion
66
dcVersion = DCVerBuiltin
67

    
68
-- | The version number for the data format of this data collector.
69
dcFormatVersion :: Int
70
dcFormatVersion = 1
71

    
72
-- | The category of this data collector.
73
dcCategory :: Maybe DCCategory
74
dcCategory = Just DCInstance
75

    
76
-- | The kind of this data collector.
77
dcKind :: DCKind
78
dcKind = DCKStatus
79

    
80
-- | The report of this data collector.
81
dcReport :: IO DCReport
82
dcReport = buildInstStatusReport Nothing Nothing
83

    
84
-- * Command line options
85

    
86
options :: IO [OptType]
87
options = return
88
  [ oConfdAddr
89
  , oConfdPort
90
  ]
91

    
92
-- | The list of arguments supported by the program.
93
arguments :: [ArgCompletion]
94
arguments = []
95

    
96
-- | Try to get the reason trail for an instance. In case it is not possible,
97
-- log the failure and return an empty list instead.
98
getReasonTrail :: String -> IO ReasonTrail
99
getReasonTrail instanceName = do
100
  fileName <- getInstReasonFilename instanceName
101
  content <- try $ readFile fileName
102
  case content of
103
    Left e -> do
104
      logWarning $
105
        "Unable to open the reason trail for instance " ++ instanceName ++
106
        " expected at " ++ fileName ++ ": " ++ show (e :: IOException)
107
      return []
108
    Right trailString ->
109
      case J.decode trailString of
110
        J.Ok t -> return t
111
        J.Error msg -> do
112
          logWarning $ "Unable to parse the reason trail: " ++ msg
113
          return []
114

    
115
-- | Determine the value of the status field for the report of one instance
116
computeStatusField :: AdminState -> ActualState -> DCStatus
117
computeStatusField AdminDown actualState =
118
  if actualState `notElem` [ActualShutdown, ActualDying]
119
    then DCStatus DCSCBad "The instance is not stopped as it should be"
120
    else DCStatus DCSCOk ""
121
computeStatusField AdminUp ActualHung =
122
  DCStatus DCSCUnknown "Instance marked as running, but it appears to be hung"
123
computeStatusField AdminUp actualState =
124
  if actualState `notElem` [ActualRunning, ActualBlocked]
125
    then DCStatus DCSCBad "The instance is not running as it should be"
126
    else DCStatus DCSCOk ""
127
computeStatusField AdminOffline _ =
128
  -- FIXME: The "offline" status seems not to be used anywhere in the source
129
  -- code, but it is defined, so we have to consider it anyway here.
130
  DCStatus DCSCUnknown "The instance is marked as offline"
131

    
132
-- Builds the status of an instance using runtime information about the Xen
133
-- Domains, their uptime information and the static information provided by
134
-- the ConfD server.
135
buildStatus :: Map.Map String Domain -> Map.Map Int UptimeInfo -> Instance
136
  -> IO InstStatus
137
buildStatus domains uptimes inst = do
138
  let name = instName inst
139
      currDomain = Map.lookup name domains
140
      idNum = fmap domId currDomain
141
      currUInfo = idNum >>= (`Map.lookup` uptimes)
142
      uptime = fmap uInfoUptime currUInfo
143
      adminState = instAdminState inst
144
      actualState =
145
        if adminState == AdminDown && isNothing currDomain
146
          then ActualShutdown
147
          else case currDomain of
148
            (Just dom@(Domain _ _ _ _ (Just isHung))) ->
149
              if isHung
150
                then ActualHung
151
                else domState dom
152
            _ -> ActualUnknown
153
      status = computeStatusField adminState actualState
154
  trail <- getReasonTrail name
155
  return $
156
    InstStatus
157
      name
158
      (instUuid inst)
159
      adminState
160
      actualState
161
      uptime
162
      (instMtime inst)
163
      trail
164
      status
165

    
166
-- | Compute the status code and message, given the current DRBD data
167
-- The final state will have the code corresponding to the worst code of
168
-- all the devices, and the error message given from the concatenation of the
169
-- non-empty error messages.
170
computeGlobalStatus :: [InstStatus] -> DCStatus
171
computeGlobalStatus instStatusList =
172
  let dcstatuses = map iStatStatus instStatusList
173
      statuses = map (\s -> (dcStatusCode s, dcStatusMessage s)) dcstatuses
174
      (code, strList) = foldr mergeStatuses (DCSCOk, [""]) statuses
175
  in DCStatus code $ intercalate "\n" strList
176

    
177
-- | Build the report of this data collector, containing all the information
178
-- about the status of the instances.
179
buildInstStatusReport :: Maybe String -> Maybe Int -> IO DCReport
180
buildInstStatusReport srvAddr srvPort = do
181
  node <- getHostName
182
  answer <- getInstances node srvAddr srvPort
183
  inst <- exitIfBad "Can't get instance info from ConfD" answer
184
  domains <- getInferredDomInfo
185
  uptimes <- getUptimeInfo
186
  let primaryInst =  fst inst
187
  iStatus <- mapM (buildStatus domains uptimes) primaryInst
188
  let globalStatus = computeGlobalStatus iStatus
189
      jsonReport = J.showJSON $ ReportData iStatus globalStatus
190
  buildReport dcName dcVersion dcFormatVersion dcCategory dcKind jsonReport
191

    
192
-- | Main function.
193
main :: Options -> [String] -> IO ()
194
main opts _ = do
195
  report <- buildInstStatusReport (optConfdAddr opts) (optConfdPort opts)
196
  putStrLn $ J.encode report