Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / InstStatus.hs @ 17ae9cdb

History | View | Annotate | Download (5.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
  ) where
31

    
32

    
33
import Control.Exception.Base
34
import Data.Maybe
35
import qualified Data.Map as Map
36
import Network.BSD (getHostName)
37
import qualified Text.JSON as J
38

    
39
import qualified Ganeti.BasicTypes as BT
40
import Ganeti.Confd.Client
41
import Ganeti.Confd.Types
42
import Ganeti.Common
43
import Ganeti.DataCollectors.CLI
44
import Ganeti.DataCollectors.InstStatusTypes
45
import Ganeti.DataCollectors.Types
46
import Ganeti.Hypervisor.Xen
47
import Ganeti.Hypervisor.Xen.Types
48
import Ganeti.Logging
49
import Ganeti.Objects
50
import Ganeti.Path
51
import Ganeti.Types
52
import Ganeti.Utils
53

    
54
-- * Command line options
55

    
56
options :: IO [OptType]
57
options = return
58
  [ oConfdAddr
59
  , oConfdPort
60
  ]
61

    
62
-- | The list of arguments supported by the program.
63
arguments :: [ArgCompletion]
64
arguments = []
65

    
66
-- | Get the list of instances ([primary], [secondary]) on the given node.
67
-- Implemented as a function, even if used a single time, to specify in a
68
-- convenient and elegant way the return data type, required in order to
69
-- prevent incurring in the monomorphism restriction.
70
-- The server address and the server port parameters are mainly intended
71
-- for testing purposes. If they are Nothing, the default values will be used.
72
getInstances
73
  :: String
74
  -> Maybe String
75
  -> Maybe Int
76
  -> IO (BT.Result ([Ganeti.Objects.Instance], [Ganeti.Objects.Instance]))
77
getInstances node srvAddr srvPort = do
78
  client <- getConfdClient srvAddr srvPort
79
  reply <- query client ReqNodeInstances $ PlainQuery node
80
  return $
81
    case fmap (J.readJSON . confdReplyAnswer) reply of
82
      Just (J.Ok instances) -> BT.Ok instances
83
      Just (J.Error msg) -> BT.Bad msg
84
      Nothing -> BT.Bad "No answer from the Confd server"
85

    
86
-- | Try to get the reason trail for an instance. In case it is not possible,
87
-- log the failure and return an empty list instead.
88
getReasonTrail :: String -> IO ReasonTrail
89
getReasonTrail instanceName = do
90
  fileName <- getInstReasonFilename instanceName
91
  content <- try $ readFile fileName
92
  case content of
93
    Left e -> do
94
      logWarning $
95
        "Unable to open the reason trail for instance " ++ instanceName ++
96
        " expected at " ++ fileName ++ ": " ++ show (e :: IOException)
97
      return []
98
    Right trailString ->
99
      case J.decode trailString of
100
        J.Ok t -> return t
101
        J.Error msg -> do
102
          logWarning $ "Unable to parse the reason trail: " ++ msg
103
          return []
104

    
105
-- | Determine the value of the status field for the report of one instance
106
computeStatusField :: AdminState -> ActualState -> DCStatus
107
computeStatusField AdminDown actualState =
108
  if actualState `notElem` [ActualShutdown, ActualDying]
109
    then DCStatus DCSCBad "The instance is not stopped as it should be"
110
    else DCStatus DCSCOk ""
111
computeStatusField AdminUp ActualHung =
112
  DCStatus DCSCUnknown "Instance marked as running, but it appears to be hung"
113
computeStatusField AdminUp actualState =
114
  if actualState `notElem` [ActualRunning, ActualBlocked]
115
    then DCStatus DCSCBad "The instance is not running as it should be"
116
    else DCStatus DCSCOk ""
117
computeStatusField AdminOffline _ =
118
  -- FIXME: The "offline" status seems not to be used anywhere in the source
119
  -- code, but it is defined, so we have to consider it anyway here.
120
  DCStatus DCSCUnknown "The instance is marked as offline"
121

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

    
156
-- | Main function.
157
main :: Options -> [String] -> IO ()
158
main opts _ = do
159
  curNode <- getHostName
160
  let node = fromMaybe curNode $ optNode opts
161
  answer <- getInstances node (optConfdAddr opts) (optConfdPort opts)
162
  inst <- exitIfBad "Can't get instance info from ConfD" answer
163
  domains <- getInferredDomInfo
164
  uptimes <- getUptimeInfo
165
  let primaryInst =  fst inst
166
  iStatus <- mapM (buildStatus domains uptimes) primaryInst
167
  putStrLn $ J.encode iStatus