Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (6.5 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.BasicTypes as BT
47
import Ganeti.Confd.ClientFunctions
48
import Ganeti.Common
49
import Ganeti.DataCollectors.CLI
50
import Ganeti.DataCollectors.InstStatusTypes
51
import Ganeti.DataCollectors.Types
52
import Ganeti.Hypervisor.Xen
53
import Ganeti.Hypervisor.Xen.Types
54
import Ganeti.Logging
55
import Ganeti.Objects
56
import Ganeti.Path
57
import Ganeti.Types
58
import Ganeti.Utils
59

    
60

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

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

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

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

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

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

    
85
-- * Command line options
86

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

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

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

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

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

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

    
178
-- | Build the report of this data collector, containing all the information
179
-- about the status of the instances.
180
buildInstStatusReport :: Maybe String -> Maybe Int -> IO DCReport
181
buildInstStatusReport srvAddr srvPort = do
182
  node <- getHostName
183
  answer <- getInstances node srvAddr srvPort
184
  inst <- exitIfBad "Can't get instance info from ConfD" answer
185
  d <- getInferredDomInfo
186
  reportData <-
187
    case d of
188
      BT.Ok domains -> do
189
        uptimes <- getUptimeInfo
190
        let primaryInst =  fst inst
191
        iStatus <- mapM (buildStatus domains uptimes) primaryInst
192
        let globalStatus = computeGlobalStatus iStatus
193
        return $ ReportData iStatus globalStatus
194
      BT.Bad m ->
195
        return . ReportData [] . DCStatus DCSCBad $
196
          "Unable to receive the list of instances: " ++ m
197
  let jsonReport = J.showJSON reportData
198
  buildReport dcName dcVersion dcFormatVersion dcCategory dcKind jsonReport
199

    
200
-- | Main function.
201
main :: Options -> [String] -> IO ()
202
main opts _ = do
203
  report <- buildInstStatusReport (optConfdAddr opts) (optConfdPort opts)
204
  putStrLn $ J.encode report