Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / InstStatus.hs @ 79731e21

History | View | Annotate | Download (7.1 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
  ) where
36

    
37

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

    
45
import qualified Ganeti.BasicTypes as BT
46
import Ganeti.Confd.Client
47
import Ganeti.Confd.Types
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
-- * Command line options
82

    
83
options :: IO [OptType]
84
options = return
85
  [ oConfdAddr
86
  , oConfdPort
87
  ]
88

    
89
-- | The list of arguments supported by the program.
90
arguments :: [ArgCompletion]
91
arguments = []
92

    
93
-- | Get the list of instances ([primary], [secondary]) on the given node.
94
-- Implemented as a function, even if used a single time, to specify in a
95
-- convenient and elegant way the return data type, required in order to
96
-- prevent incurring in the monomorphism restriction.
97
-- The server address and the server port parameters are mainly intended
98
-- for testing purposes. If they are Nothing, the default values will be used.
99
getInstances
100
  :: String
101
  -> Maybe String
102
  -> Maybe Int
103
  -> IO (BT.Result ([Ganeti.Objects.Instance], [Ganeti.Objects.Instance]))
104
getInstances node srvAddr srvPort = do
105
  client <- getConfdClient srvAddr srvPort
106
  reply <- query client ReqNodeInstances $ PlainQuery node
107
  return $
108
    case fmap (J.readJSON . confdReplyAnswer) reply of
109
      Just (J.Ok instances) -> BT.Ok instances
110
      Just (J.Error msg) -> BT.Bad msg
111
      Nothing -> BT.Bad "No answer from the Confd server"
112

    
113
-- | Try to get the reason trail for an instance. In case it is not possible,
114
-- log the failure and return an empty list instead.
115
getReasonTrail :: String -> IO ReasonTrail
116
getReasonTrail instanceName = do
117
  fileName <- getInstReasonFilename instanceName
118
  content <- try $ readFile fileName
119
  case content of
120
    Left e -> do
121
      logWarning $
122
        "Unable to open the reason trail for instance " ++ instanceName ++
123
        " expected at " ++ fileName ++ ": " ++ show (e :: IOException)
124
      return []
125
    Right trailString ->
126
      case J.decode trailString of
127
        J.Ok t -> return t
128
        J.Error msg -> do
129
          logWarning $ "Unable to parse the reason trail: " ++ msg
130
          return []
131

    
132
-- | Determine the value of the status field for the report of one instance
133
computeStatusField :: AdminState -> ActualState -> DCStatus
134
computeStatusField AdminDown actualState =
135
  if actualState `notElem` [ActualShutdown, ActualDying]
136
    then DCStatus DCSCBad "The instance is not stopped as it should be"
137
    else DCStatus DCSCOk ""
138
computeStatusField AdminUp ActualHung =
139
  DCStatus DCSCUnknown "Instance marked as running, but it appears to be hung"
140
computeStatusField AdminUp actualState =
141
  if actualState `notElem` [ActualRunning, ActualBlocked]
142
    then DCStatus DCSCBad "The instance is not running as it should be"
143
    else DCStatus DCSCOk ""
144
computeStatusField AdminOffline _ =
145
  -- FIXME: The "offline" status seems not to be used anywhere in the source
146
  -- code, but it is defined, so we have to consider it anyway here.
147
  DCStatus DCSCUnknown "The instance is marked as offline"
148

    
149
-- Builds the status of an instance using runtime information about the Xen
150
-- Domains, their uptime information and the static information provided by
151
-- the ConfD server.
152
buildStatus :: Map.Map String Domain -> Map.Map Int UptimeInfo -> Instance
153
  -> IO InstStatus
154
buildStatus domains uptimes inst = do
155
  let name = instName inst
156
      currDomain = Map.lookup name domains
157
      idNum = fmap domId currDomain
158
      currUInfo = idNum >>= (`Map.lookup` uptimes)
159
      uptime = fmap uInfoUptime currUInfo
160
      adminState = instAdminState inst
161
      actualState =
162
        if adminState == AdminDown && isNothing currDomain
163
          then ActualShutdown
164
          else case currDomain of
165
            (Just dom@(Domain _ _ _ _ (Just isHung))) ->
166
              if isHung
167
                then ActualHung
168
                else domState dom
169
            _ -> ActualUnknown
170
      status = computeStatusField adminState actualState
171
  trail <- getReasonTrail name
172
  return $
173
    InstStatus
174
      name
175
      (instUuid inst)
176
      adminState
177
      actualState
178
      uptime
179
      (instMtime inst)
180
      trail
181
      status
182

    
183
-- | Compute the status code and message, given the current DRBD data
184
-- The final state will have the code corresponding to the worst code of
185
-- all the devices, and the error message given from the concatenation of the
186
-- non-empty error messages.
187
computeGlobalStatus :: [InstStatus] -> DCStatus
188
computeGlobalStatus instStatusList =
189
  let dcstatuses = map iStatStatus instStatusList
190
      statuses = map (\s -> (dcStatusCode s, dcStatusMessage s)) dcstatuses
191
      (code, strList) = foldr mergeStatuses (DCSCOk, [""]) statuses
192
  in DCStatus code $ intercalate "\n" strList
193

    
194
-- | Build the report of this data collector, containing all the information
195
-- about the status of the instances.
196
buildInstStatusReport :: Maybe String -> Maybe Int -> IO DCReport
197
buildInstStatusReport srvAddr srvPort = do
198
  node <- getHostName
199
  answer <- getInstances node srvAddr srvPort
200
  inst <- exitIfBad "Can't get instance info from ConfD" answer
201
  domains <- getInferredDomInfo
202
  uptimes <- getUptimeInfo
203
  let primaryInst =  fst inst
204
  iStatus <- mapM (buildStatus domains uptimes) primaryInst
205
  let globalStatus = computeGlobalStatus iStatus
206
      jsonReport = J.showJSON $ ReportData iStatus globalStatus
207
  buildReport dcName dcVersion dcFormatVersion dcCategory dcKind jsonReport
208

    
209
-- | Main function.
210
main :: Options -> [String] -> IO ()
211
main opts _ = do
212
  report <- buildInstStatusReport (optConfdAddr opts) (optConfdPort opts)
213
  putStrLn $ J.encode report