Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / Drbd.hs @ 8c5419ee

History | View | Annotate | Download (4.7 kB)

1 332b1340 Michele Tartara
{-| DRBD data collector.
2 332b1340 Michele Tartara
3 332b1340 Michele Tartara
-}
4 332b1340 Michele Tartara
5 332b1340 Michele Tartara
{-
6 332b1340 Michele Tartara
7 ddceb4c5 Michele Tartara
Copyright (C) 2012, 2013 Google Inc.
8 332b1340 Michele Tartara
9 332b1340 Michele Tartara
This program is free software; you can redistribute it and/or modify
10 332b1340 Michele Tartara
it under the terms of the GNU General Public License as published by
11 332b1340 Michele Tartara
the Free Software Foundation; either version 2 of the License, or
12 332b1340 Michele Tartara
(at your option) any later version.
13 332b1340 Michele Tartara
14 332b1340 Michele Tartara
This program is distributed in the hope that it will be useful, but
15 332b1340 Michele Tartara
WITHOUT ANY WARRANTY; without even the implied warranty of
16 332b1340 Michele Tartara
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 332b1340 Michele Tartara
General Public License for more details.
18 332b1340 Michele Tartara
19 332b1340 Michele Tartara
You should have received a copy of the GNU General Public License
20 332b1340 Michele Tartara
along with this program; if not, write to the Free Software
21 332b1340 Michele Tartara
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 332b1340 Michele Tartara
02110-1301, USA.
23 332b1340 Michele Tartara
24 332b1340 Michele Tartara
-}
25 332b1340 Michele Tartara
26 332b1340 Michele Tartara
module Ganeti.DataCollectors.Drbd
27 332b1340 Michele Tartara
  ( main
28 332b1340 Michele Tartara
  , options
29 332b1340 Michele Tartara
  , arguments
30 ddceb4c5 Michele Tartara
  , dcName
31 a895fa19 Michele Tartara
  , dcVersion
32 834dc290 Michele Tartara
  , dcFormatVersion
33 f0e4b2a4 Michele Tartara
  , dcCategory
34 54c7dff7 Michele Tartara
  , dcKind
35 8c5419ee Michele Tartara
  , dcData
36 332b1340 Michele Tartara
  ) where
37 332b1340 Michele Tartara
38 332b1340 Michele Tartara
39 332b1340 Michele Tartara
import qualified Control.Exception as E
40 d78970ba Michele Tartara
import Control.Monad
41 332b1340 Michele Tartara
import Data.Attoparsec.Text.Lazy as A
42 d78970ba Michele Tartara
import Data.Maybe
43 332b1340 Michele Tartara
import Data.Text.Lazy (pack, unpack)
44 d78970ba Michele Tartara
import Network.BSD (getHostName)
45 d78970ba Michele Tartara
import qualified Text.JSON as J
46 332b1340 Michele Tartara
47 332b1340 Michele Tartara
import qualified Ganeti.BasicTypes as BT
48 332b1340 Michele Tartara
import qualified Ganeti.Constants as C
49 332b1340 Michele Tartara
import Ganeti.Block.Drbd.Parser(drbdStatusParser)
50 d78970ba Michele Tartara
import Ganeti.Block.Drbd.Types(DrbdInstMinor)
51 332b1340 Michele Tartara
import Ganeti.Common
52 d78970ba Michele Tartara
import Ganeti.Confd.Client
53 d78970ba Michele Tartara
import Ganeti.Confd.Types
54 55abd2c7 Iustin Pop
import Ganeti.DataCollectors.CLI
55 e71c47d3 Michele Tartara
import Ganeti.DataCollectors.Types
56 332b1340 Michele Tartara
import Ganeti.Utils
57 332b1340 Michele Tartara
58 332b1340 Michele Tartara
59 332b1340 Michele Tartara
-- | The default path of the DRBD status file.
60 332b1340 Michele Tartara
-- It is hardcoded because it is not likely to change.
61 332b1340 Michele Tartara
defaultFile :: FilePath
62 332b1340 Michele Tartara
defaultFile = C.drbdStatusFile
63 332b1340 Michele Tartara
64 332b1340 Michele Tartara
-- | The default setting for the maximum amount of not parsed character to
65 332b1340 Michele Tartara
-- print in case of error.
66 332b1340 Michele Tartara
-- It is set to use most of the screen estate on a standard 80x25 terminal.
67 332b1340 Michele Tartara
-- TODO: add the possibility to set this with a command line parameter.
68 332b1340 Michele Tartara
defaultCharNum :: Int
69 332b1340 Michele Tartara
defaultCharNum = 80*20
70 332b1340 Michele Tartara
71 e71c47d3 Michele Tartara
-- | The name of this data collector.
72 e71c47d3 Michele Tartara
dcName :: String
73 e71c47d3 Michele Tartara
dcName = "drbd"
74 e71c47d3 Michele Tartara
75 a895fa19 Michele Tartara
-- | The version of this data collector.
76 a895fa19 Michele Tartara
dcVersion :: DCVersion
77 a895fa19 Michele Tartara
dcVersion = DCVerBuiltin
78 a895fa19 Michele Tartara
79 e71c47d3 Michele Tartara
-- | The version number for the data format of this data collector.
80 e71c47d3 Michele Tartara
dcFormatVersion :: Int
81 e71c47d3 Michele Tartara
dcFormatVersion = 1
82 e71c47d3 Michele Tartara
83 f0e4b2a4 Michele Tartara
-- | The category of this data collector.
84 f0e4b2a4 Michele Tartara
dcCategory :: Maybe DCCategory
85 f0e4b2a4 Michele Tartara
dcCategory = Just DCStorage
86 f0e4b2a4 Michele Tartara
87 54c7dff7 Michele Tartara
-- | The kind of this data collector.
88 54c7dff7 Michele Tartara
dcKind :: DCKind
89 54c7dff7 Michele Tartara
dcKind = DCKStatus
90 54c7dff7 Michele Tartara
91 8c5419ee Michele Tartara
-- | The data exported by the data collector, taken from the default location.
92 8c5419ee Michele Tartara
dcData :: IO J.JSValue
93 8c5419ee Michele Tartara
dcData = buildJsonReport defaultFile Nothing
94 8c5419ee Michele Tartara
95 7a171e3f Michele Tartara
-- * Command line options
96 7a171e3f Michele Tartara
97 332b1340 Michele Tartara
options :: IO [OptType]
98 d78970ba Michele Tartara
options =
99 d78970ba Michele Tartara
  return
100 d78970ba Michele Tartara
    [ oDrbdStatus
101 d78970ba Michele Tartara
    , oDrbdPairing
102 d78970ba Michele Tartara
    ]
103 332b1340 Michele Tartara
104 332b1340 Michele Tartara
-- | The list of arguments supported by the program.
105 332b1340 Michele Tartara
arguments :: [ArgCompletion]
106 d78970ba Michele Tartara
arguments = [ArgCompletion OptComplFile 0 (Just 0)]
107 332b1340 Michele Tartara
108 d78970ba Michele Tartara
-- | Get information about the pairing of DRBD minors and Ganeti instances
109 d78970ba Michele Tartara
-- on the current node. The information is taken from the Confd client
110 d78970ba Michele Tartara
-- or, if a filename is specified, from a JSON encoded file (for testing
111 d78970ba Michele Tartara
-- purposes).
112 d78970ba Michele Tartara
getPairingInfo :: Maybe String -> IO (BT.Result [DrbdInstMinor])
113 d78970ba Michele Tartara
getPairingInfo Nothing = do
114 d78970ba Michele Tartara
  curNode <- getHostName
115 7dc27988 Michele Tartara
  client <- getConfdClient Nothing Nothing
116 d78970ba Michele Tartara
  reply <- query client ReqNodeDrbd $ PlainQuery curNode
117 d78970ba Michele Tartara
  return $
118 d78970ba Michele Tartara
    case fmap (J.readJSONs . confdReplyAnswer) reply of
119 d78970ba Michele Tartara
      Just (J.Ok instMinor) -> BT.Ok instMinor
120 d78970ba Michele Tartara
      Just (J.Error msg) -> BT.Bad msg
121 d78970ba Michele Tartara
      Nothing -> BT.Bad "No answer from the Confd server"
122 d78970ba Michele Tartara
getPairingInfo (Just filename) = do
123 d78970ba Michele Tartara
  content <- readFile filename
124 d78970ba Michele Tartara
  return $
125 d78970ba Michele Tartara
    case J.decode content of
126 d78970ba Michele Tartara
      J.Ok instMinor -> BT.Ok instMinor
127 d78970ba Michele Tartara
      J.Error msg -> BT.Bad msg
128 d78970ba Michele Tartara
129 8c5419ee Michele Tartara
-- | This function computes the JSON representation of the DRBD status.
130 8c5419ee Michele Tartara
buildJsonReport :: FilePath -> Maybe FilePath -> IO J.JSValue
131 8c5419ee Michele Tartara
buildJsonReport statusFile pairingFile = do
132 332b1340 Michele Tartara
  contents <-
133 e71c47d3 Michele Tartara
    ((E.try $ readFile statusFile) :: IO (Either IOError String)) >>=
134 638e0a6f Iustin Pop
      exitIfBad "reading from file" . either (BT.Bad . show) BT.Ok
135 e71c47d3 Michele Tartara
  pairingResult <- getPairingInfo pairingFile
136 d78970ba Michele Tartara
  pairing <- exitIfBad "Can't get pairing info" pairingResult
137 8c5419ee Michele Tartara
  case A.parse (drbdStatusParser pairing) $ pack contents of
138 8c5419ee Michele Tartara
    A.Fail unparsedText contexts errorMessage -> exitErr $
139 8c5419ee Michele Tartara
      show (Prelude.take defaultCharNum $ unpack unparsedText) ++ "\n"
140 8c5419ee Michele Tartara
        ++ show contexts ++ "\n" ++ errorMessage
141 8c5419ee Michele Tartara
    A.Done _ drbdStatus -> return $ J.showJSON drbdStatus
142 e71c47d3 Michele Tartara
143 e71c47d3 Michele Tartara
-- | Main function.
144 e71c47d3 Michele Tartara
main :: Options -> [String] -> IO ()
145 e71c47d3 Michele Tartara
main opts args = do
146 e71c47d3 Michele Tartara
  let statusFile = fromMaybe defaultFile $ optDrbdStatus opts
147 e71c47d3 Michele Tartara
      pairingFile = optDrbdPairing opts
148 e71c47d3 Michele Tartara
  unless (null args) . exitErr $ "This program takes exactly zero" ++
149 e71c47d3 Michele Tartara
                                  " arguments, got '" ++ unwords args ++ "'"
150 8c5419ee Michele Tartara
  report <- buildJsonReport statusFile pairingFile >>=
151 8c5419ee Michele Tartara
    buildReport dcName dcVersion dcFormatVersion dcCategory dcKind
152 e71c47d3 Michele Tartara
  putStrLn $ J.encode report