Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / InstStatus.hs @ 7660aaf3

History | View | Annotate | Download (6.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.Maybe
40
import qualified Data.Map as Map
41
import Network.BSD (getHostName)
42
import qualified Text.JSON as J
43

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

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

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

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

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

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

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

    
182
-- | Main function.
183
main :: Options -> [String] -> IO ()
184
main opts _ = do
185
  curNode <- getHostName
186
  let node = fromMaybe curNode $ optNode opts
187
  answer <- getInstances node (optConfdAddr opts) (optConfdPort opts)
188
  inst <- exitIfBad "Can't get instance info from ConfD" answer
189
  domains <- getInferredDomInfo
190
  uptimes <- getUptimeInfo
191
  let primaryInst =  fst inst
192
  iStatus <- mapM (buildStatus domains uptimes) primaryInst
193
  putStrLn $ J.encode iStatus