Statistics
| Branch: | Tag: | Revision:

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

History | View | Annotate | Download (6.1 kB)

1 d7e9323b Michele Tartara
{-| Instance status data collector.
2 d7e9323b Michele Tartara
3 d7e9323b Michele Tartara
-}
4 d7e9323b Michele Tartara
5 d7e9323b Michele Tartara
{-
6 d7e9323b Michele Tartara
7 d7e9323b Michele Tartara
Copyright (C) 2013 Google Inc.
8 d7e9323b Michele Tartara
9 d7e9323b Michele Tartara
This program is free software; you can redistribute it and/or modify
10 d7e9323b Michele Tartara
it under the terms of the GNU General Public License as published by
11 d7e9323b Michele Tartara
the Free Software Foundation; either version 2 of the License, or
12 d7e9323b Michele Tartara
(at your option) any later version.
13 d7e9323b Michele Tartara
14 d7e9323b Michele Tartara
This program is distributed in the hope that it will be useful, but
15 d7e9323b Michele Tartara
WITHOUT ANY WARRANTY; without even the implied warranty of
16 d7e9323b Michele Tartara
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 d7e9323b Michele Tartara
General Public License for more details.
18 d7e9323b Michele Tartara
19 d7e9323b Michele Tartara
You should have received a copy of the GNU General Public License
20 d7e9323b Michele Tartara
along with this program; if not, write to the Free Software
21 d7e9323b Michele Tartara
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 d7e9323b Michele Tartara
02110-1301, USA.
23 d7e9323b Michele Tartara
24 d7e9323b Michele Tartara
-}
25 d7e9323b Michele Tartara
26 d7e9323b Michele Tartara
module Ganeti.DataCollectors.InstStatus
27 d7e9323b Michele Tartara
  ( main
28 d7e9323b Michele Tartara
  , options
29 d7e9323b Michele Tartara
  , arguments
30 7660aaf3 Michele Tartara
  , dcName
31 7660aaf3 Michele Tartara
  , dcVersion
32 7660aaf3 Michele Tartara
  , dcFormatVersion
33 7660aaf3 Michele Tartara
  , dcCategory
34 7660aaf3 Michele Tartara
  , dcKind
35 d7e9323b Michele Tartara
  ) where
36 d7e9323b Michele Tartara
37 d7e9323b Michele Tartara
38 17ae9cdb Michele Tartara
import Control.Exception.Base
39 d7e9323b Michele Tartara
import Data.Maybe
40 d7e9323b Michele Tartara
import qualified Data.Map as Map
41 d7e9323b Michele Tartara
import Network.BSD (getHostName)
42 d7e9323b Michele Tartara
import qualified Text.JSON as J
43 d7e9323b Michele Tartara
44 d7e9323b Michele Tartara
import qualified Ganeti.BasicTypes as BT
45 d7e9323b Michele Tartara
import Ganeti.Confd.Client
46 d7e9323b Michele Tartara
import Ganeti.Confd.Types
47 d7e9323b Michele Tartara
import Ganeti.Common
48 d7e9323b Michele Tartara
import Ganeti.DataCollectors.CLI
49 d7e9323b Michele Tartara
import Ganeti.DataCollectors.InstStatusTypes
50 fc4be2bf Michele Tartara
import Ganeti.DataCollectors.Types
51 d7e9323b Michele Tartara
import Ganeti.Hypervisor.Xen
52 d4de2ea8 Michele Tartara
import Ganeti.Hypervisor.Xen.Types
53 17ae9cdb Michele Tartara
import Ganeti.Logging
54 d7e9323b Michele Tartara
import Ganeti.Objects
55 17ae9cdb Michele Tartara
import Ganeti.Path
56 17ae9cdb Michele Tartara
import Ganeti.Types
57 d7e9323b Michele Tartara
import Ganeti.Utils
58 d7e9323b Michele Tartara
59 7660aaf3 Michele Tartara
60 7660aaf3 Michele Tartara
-- | The name of this data collector.
61 7660aaf3 Michele Tartara
dcName :: String
62 7660aaf3 Michele Tartara
dcName = "inst-status-xen"
63 7660aaf3 Michele Tartara
64 7660aaf3 Michele Tartara
-- | The version of this data collector.
65 7660aaf3 Michele Tartara
dcVersion :: DCVersion
66 7660aaf3 Michele Tartara
dcVersion = DCVerBuiltin
67 7660aaf3 Michele Tartara
68 7660aaf3 Michele Tartara
-- | The version number for the data format of this data collector.
69 7660aaf3 Michele Tartara
dcFormatVersion :: Int
70 7660aaf3 Michele Tartara
dcFormatVersion = 1
71 7660aaf3 Michele Tartara
72 7660aaf3 Michele Tartara
-- | The category of this data collector.
73 7660aaf3 Michele Tartara
dcCategory :: Maybe DCCategory
74 7660aaf3 Michele Tartara
dcCategory = Just DCInstance
75 7660aaf3 Michele Tartara
76 7660aaf3 Michele Tartara
-- | The kind of this data collector.
77 7660aaf3 Michele Tartara
dcKind :: DCKind
78 7660aaf3 Michele Tartara
dcKind = DCKStatus
79 7660aaf3 Michele Tartara
80 d7e9323b Michele Tartara
-- * Command line options
81 d7e9323b Michele Tartara
82 d7e9323b Michele Tartara
options :: IO [OptType]
83 d7e9323b Michele Tartara
options = return
84 d7e9323b Michele Tartara
  [ oConfdAddr
85 d7e9323b Michele Tartara
  , oConfdPort
86 d7e9323b Michele Tartara
  ]
87 d7e9323b Michele Tartara
88 d7e9323b Michele Tartara
-- | The list of arguments supported by the program.
89 d7e9323b Michele Tartara
arguments :: [ArgCompletion]
90 d7e9323b Michele Tartara
arguments = []
91 d7e9323b Michele Tartara
92 d7e9323b Michele Tartara
-- | Get the list of instances ([primary], [secondary]) on the given node.
93 d7e9323b Michele Tartara
-- Implemented as a function, even if used a single time, to specify in a
94 d7e9323b Michele Tartara
-- convenient and elegant way the return data type, required in order to
95 d7e9323b Michele Tartara
-- prevent incurring in the monomorphism restriction.
96 d7e9323b Michele Tartara
-- The server address and the server port parameters are mainly intended
97 d7e9323b Michele Tartara
-- for testing purposes. If they are Nothing, the default values will be used.
98 d7e9323b Michele Tartara
getInstances
99 d7e9323b Michele Tartara
  :: String
100 d7e9323b Michele Tartara
  -> Maybe String
101 d7e9323b Michele Tartara
  -> Maybe Int
102 d7e9323b Michele Tartara
  -> IO (BT.Result ([Ganeti.Objects.Instance], [Ganeti.Objects.Instance]))
103 d7e9323b Michele Tartara
getInstances node srvAddr srvPort = do
104 d7e9323b Michele Tartara
  client <- getConfdClient srvAddr srvPort
105 d7e9323b Michele Tartara
  reply <- query client ReqNodeInstances $ PlainQuery node
106 d7e9323b Michele Tartara
  return $
107 d7e9323b Michele Tartara
    case fmap (J.readJSON . confdReplyAnswer) reply of
108 d7e9323b Michele Tartara
      Just (J.Ok instances) -> BT.Ok instances
109 d7e9323b Michele Tartara
      Just (J.Error msg) -> BT.Bad msg
110 d7e9323b Michele Tartara
      Nothing -> BT.Bad "No answer from the Confd server"
111 d7e9323b Michele Tartara
112 17ae9cdb Michele Tartara
-- | Try to get the reason trail for an instance. In case it is not possible,
113 17ae9cdb Michele Tartara
-- log the failure and return an empty list instead.
114 17ae9cdb Michele Tartara
getReasonTrail :: String -> IO ReasonTrail
115 17ae9cdb Michele Tartara
getReasonTrail instanceName = do
116 17ae9cdb Michele Tartara
  fileName <- getInstReasonFilename instanceName
117 17ae9cdb Michele Tartara
  content <- try $ readFile fileName
118 17ae9cdb Michele Tartara
  case content of
119 17ae9cdb Michele Tartara
    Left e -> do
120 17ae9cdb Michele Tartara
      logWarning $
121 17ae9cdb Michele Tartara
        "Unable to open the reason trail for instance " ++ instanceName ++
122 17ae9cdb Michele Tartara
        " expected at " ++ fileName ++ ": " ++ show (e :: IOException)
123 17ae9cdb Michele Tartara
      return []
124 17ae9cdb Michele Tartara
    Right trailString ->
125 17ae9cdb Michele Tartara
      case J.decode trailString of
126 17ae9cdb Michele Tartara
        J.Ok t -> return t
127 17ae9cdb Michele Tartara
        J.Error msg -> do
128 17ae9cdb Michele Tartara
          logWarning $ "Unable to parse the reason trail: " ++ msg
129 17ae9cdb Michele Tartara
          return []
130 17ae9cdb Michele Tartara
131 fc4be2bf Michele Tartara
-- | Determine the value of the status field for the report of one instance
132 fc4be2bf Michele Tartara
computeStatusField :: AdminState -> ActualState -> DCStatus
133 fc4be2bf Michele Tartara
computeStatusField AdminDown actualState =
134 fc4be2bf Michele Tartara
  if actualState `notElem` [ActualShutdown, ActualDying]
135 fc4be2bf Michele Tartara
    then DCStatus DCSCBad "The instance is not stopped as it should be"
136 fc4be2bf Michele Tartara
    else DCStatus DCSCOk ""
137 fc4be2bf Michele Tartara
computeStatusField AdminUp ActualHung =
138 fc4be2bf Michele Tartara
  DCStatus DCSCUnknown "Instance marked as running, but it appears to be hung"
139 fc4be2bf Michele Tartara
computeStatusField AdminUp actualState =
140 fc4be2bf Michele Tartara
  if actualState `notElem` [ActualRunning, ActualBlocked]
141 fc4be2bf Michele Tartara
    then DCStatus DCSCBad "The instance is not running as it should be"
142 fc4be2bf Michele Tartara
    else DCStatus DCSCOk ""
143 fc4be2bf Michele Tartara
computeStatusField AdminOffline _ =
144 fc4be2bf Michele Tartara
  -- FIXME: The "offline" status seems not to be used anywhere in the source
145 fc4be2bf Michele Tartara
  -- code, but it is defined, so we have to consider it anyway here.
146 fc4be2bf Michele Tartara
  DCStatus DCSCUnknown "The instance is marked as offline"
147 fc4be2bf Michele Tartara
148 d7e9323b Michele Tartara
-- Builds the status of an instance using runtime information about the Xen
149 d7e9323b Michele Tartara
-- Domains, their uptime information and the static information provided by
150 d7e9323b Michele Tartara
-- the ConfD server.
151 d7e9323b Michele Tartara
buildStatus :: Map.Map String Domain -> Map.Map Int UptimeInfo -> Instance
152 d7e9323b Michele Tartara
  -> IO InstStatus
153 d7e9323b Michele Tartara
buildStatus domains uptimes inst = do
154 d7e9323b Michele Tartara
  let name = instName inst
155 d7e9323b Michele Tartara
      currDomain = Map.lookup name domains
156 d7e9323b Michele Tartara
      idNum = fmap domId currDomain
157 d7e9323b Michele Tartara
      currUInfo = idNum >>= (`Map.lookup` uptimes)
158 d7e9323b Michele Tartara
      uptime = fmap uInfoUptime currUInfo
159 d7e9323b Michele Tartara
      adminState = instAdminState inst
160 d4de2ea8 Michele Tartara
      actualState =
161 d4de2ea8 Michele Tartara
        if adminState == AdminDown && isNothing currDomain
162 d4de2ea8 Michele Tartara
          then ActualShutdown
163 d4de2ea8 Michele Tartara
          else case currDomain of
164 d4de2ea8 Michele Tartara
            (Just dom@(Domain _ _ _ _ (Just isHung))) ->
165 d4de2ea8 Michele Tartara
              if isHung
166 d4de2ea8 Michele Tartara
                then ActualHung
167 d4de2ea8 Michele Tartara
                else domState dom
168 d4de2ea8 Michele Tartara
            _ -> ActualUnknown
169 fc4be2bf Michele Tartara
      status = computeStatusField adminState actualState
170 17ae9cdb Michele Tartara
  trail <- getReasonTrail name
171 d7e9323b Michele Tartara
  return $
172 d7e9323b Michele Tartara
    InstStatus
173 d7e9323b Michele Tartara
      name
174 d7e9323b Michele Tartara
      (instUuid inst)
175 d7e9323b Michele Tartara
      adminState
176 d4de2ea8 Michele Tartara
      actualState
177 d7e9323b Michele Tartara
      uptime
178 d7e9323b Michele Tartara
      (instMtime inst)
179 17ae9cdb Michele Tartara
      trail
180 fc4be2bf Michele Tartara
      status
181 d7e9323b Michele Tartara
182 d7e9323b Michele Tartara
-- | Main function.
183 d7e9323b Michele Tartara
main :: Options -> [String] -> IO ()
184 d7e9323b Michele Tartara
main opts _ = do
185 d7e9323b Michele Tartara
  curNode <- getHostName
186 d7e9323b Michele Tartara
  let node = fromMaybe curNode $ optNode opts
187 d7e9323b Michele Tartara
  answer <- getInstances node (optConfdAddr opts) (optConfdPort opts)
188 d7e9323b Michele Tartara
  inst <- exitIfBad "Can't get instance info from ConfD" answer
189 d7e9323b Michele Tartara
  domains <- getInferredDomInfo
190 d7e9323b Michele Tartara
  uptimes <- getUptimeInfo
191 d7e9323b Michele Tartara
  let primaryInst =  fst inst
192 d7e9323b Michele Tartara
  iStatus <- mapM (buildStatus domains uptimes) primaryInst
193 d7e9323b Michele Tartara
  putStrLn $ J.encode iStatus