Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / Drbd.hs @ e71c47d3

History | View | Annotate | Download (4.2 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 332b1340 Michele Tartara
Copyright (C) 2012 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 332b1340 Michele Tartara
  ) where
31 332b1340 Michele Tartara
32 332b1340 Michele Tartara
33 332b1340 Michele Tartara
import qualified Control.Exception as E
34 d78970ba Michele Tartara
import Control.Monad
35 332b1340 Michele Tartara
import Data.Attoparsec.Text.Lazy as A
36 d78970ba Michele Tartara
import Data.Maybe
37 332b1340 Michele Tartara
import Data.Text.Lazy (pack, unpack)
38 d78970ba Michele Tartara
import Network.BSD (getHostName)
39 d78970ba Michele Tartara
import qualified Text.JSON as J
40 332b1340 Michele Tartara
41 332b1340 Michele Tartara
import qualified Ganeti.BasicTypes as BT
42 332b1340 Michele Tartara
import qualified Ganeti.Constants as C
43 332b1340 Michele Tartara
import Ganeti.Block.Drbd.Parser(drbdStatusParser)
44 d78970ba Michele Tartara
import Ganeti.Block.Drbd.Types(DrbdInstMinor)
45 332b1340 Michele Tartara
import Ganeti.Common
46 d78970ba Michele Tartara
import Ganeti.Confd.Client
47 d78970ba Michele Tartara
import Ganeti.Confd.Types
48 55abd2c7 Iustin Pop
import Ganeti.DataCollectors.CLI
49 e71c47d3 Michele Tartara
import Ganeti.DataCollectors.Types
50 332b1340 Michele Tartara
import Ganeti.Utils
51 332b1340 Michele Tartara
52 332b1340 Michele Tartara
53 332b1340 Michele Tartara
-- | The default path of the DRBD status file.
54 332b1340 Michele Tartara
-- It is hardcoded because it is not likely to change.
55 332b1340 Michele Tartara
defaultFile :: FilePath
56 332b1340 Michele Tartara
defaultFile = C.drbdStatusFile
57 332b1340 Michele Tartara
58 332b1340 Michele Tartara
-- | The default setting for the maximum amount of not parsed character to
59 332b1340 Michele Tartara
-- print in case of error.
60 332b1340 Michele Tartara
-- It is set to use most of the screen estate on a standard 80x25 terminal.
61 332b1340 Michele Tartara
-- TODO: add the possibility to set this with a command line parameter.
62 332b1340 Michele Tartara
defaultCharNum :: Int
63 332b1340 Michele Tartara
defaultCharNum = 80*20
64 332b1340 Michele Tartara
65 e71c47d3 Michele Tartara
-- | The name of this data collector.
66 e71c47d3 Michele Tartara
dcName :: String
67 e71c47d3 Michele Tartara
dcName = "drbd"
68 e71c47d3 Michele Tartara
69 e71c47d3 Michele Tartara
-- | The version number for the data format of this data collector.
70 e71c47d3 Michele Tartara
dcFormatVersion :: Int
71 e71c47d3 Michele Tartara
dcFormatVersion = 1
72 e71c47d3 Michele Tartara
73 332b1340 Michele Tartara
options :: IO [OptType]
74 d78970ba Michele Tartara
options =
75 d78970ba Michele Tartara
  return
76 d78970ba Michele Tartara
    [ oDrbdStatus
77 d78970ba Michele Tartara
    , oDrbdPairing
78 d78970ba Michele Tartara
    ]
79 332b1340 Michele Tartara
80 332b1340 Michele Tartara
-- | The list of arguments supported by the program.
81 332b1340 Michele Tartara
arguments :: [ArgCompletion]
82 d78970ba Michele Tartara
arguments = [ArgCompletion OptComplFile 0 (Just 0)]
83 332b1340 Michele Tartara
84 332b1340 Michele Tartara
-- * Command line options
85 332b1340 Michele Tartara
86 d78970ba Michele Tartara
-- | Get information about the pairing of DRBD minors and Ganeti instances
87 d78970ba Michele Tartara
-- on the current node. The information is taken from the Confd client
88 d78970ba Michele Tartara
-- or, if a filename is specified, from a JSON encoded file (for testing
89 d78970ba Michele Tartara
-- purposes).
90 d78970ba Michele Tartara
getPairingInfo :: Maybe String -> IO (BT.Result [DrbdInstMinor])
91 d78970ba Michele Tartara
getPairingInfo Nothing = do
92 d78970ba Michele Tartara
  curNode <- getHostName
93 d78970ba Michele Tartara
  client <- getConfdClient
94 d78970ba Michele Tartara
  reply <- query client ReqNodeDrbd $ PlainQuery curNode
95 d78970ba Michele Tartara
  return $
96 d78970ba Michele Tartara
    case fmap (J.readJSONs . confdReplyAnswer) reply of
97 d78970ba Michele Tartara
      Just (J.Ok instMinor) -> BT.Ok instMinor
98 d78970ba Michele Tartara
      Just (J.Error msg) -> BT.Bad msg
99 d78970ba Michele Tartara
      Nothing -> BT.Bad "No answer from the Confd server"
100 d78970ba Michele Tartara
getPairingInfo (Just filename) = do
101 d78970ba Michele Tartara
  content <- readFile filename
102 d78970ba Michele Tartara
  return $
103 d78970ba Michele Tartara
    case J.decode content of
104 d78970ba Michele Tartara
      J.Ok instMinor -> BT.Ok instMinor
105 d78970ba Michele Tartara
      J.Error msg -> BT.Bad msg
106 d78970ba Michele Tartara
107 e71c47d3 Michele Tartara
-- | This function builds a report with the DRBD status.
108 e71c47d3 Michele Tartara
buildDRBDReport :: FilePath -> Maybe FilePath -> IO DCReport
109 e71c47d3 Michele Tartara
buildDRBDReport statusFile pairingFile = do
110 332b1340 Michele Tartara
  contents <-
111 e71c47d3 Michele Tartara
    ((E.try $ readFile statusFile) :: IO (Either IOError String)) >>=
112 638e0a6f Iustin Pop
      exitIfBad "reading from file" . either (BT.Bad . show) BT.Ok
113 e71c47d3 Michele Tartara
  pairingResult <- getPairingInfo pairingFile
114 d78970ba Michele Tartara
  pairing <- exitIfBad "Can't get pairing info" pairingResult
115 e71c47d3 Michele Tartara
  jsonData <-
116 d78970ba Michele Tartara
    case A.parse (drbdStatusParser pairing) $ pack contents of
117 332b1340 Michele Tartara
      A.Fail unparsedText contexts errorMessage -> exitErr $
118 332b1340 Michele Tartara
        show (Prelude.take defaultCharNum $ unpack unparsedText) ++ "\n"
119 332b1340 Michele Tartara
          ++ show contexts ++ "\n" ++ errorMessage
120 e71c47d3 Michele Tartara
      A.Done _ drbdStatus -> return $ J.showJSON drbdStatus
121 e71c47d3 Michele Tartara
  buildReport dcName Nothing dcFormatVersion jsonData
122 e71c47d3 Michele Tartara
123 e71c47d3 Michele Tartara
-- | Main function.
124 e71c47d3 Michele Tartara
main :: Options -> [String] -> IO ()
125 e71c47d3 Michele Tartara
main opts args = do
126 e71c47d3 Michele Tartara
  let statusFile = fromMaybe defaultFile $ optDrbdStatus opts
127 e71c47d3 Michele Tartara
      pairingFile = optDrbdPairing opts
128 e71c47d3 Michele Tartara
  unless (null args) . exitErr $ "This program takes exactly zero" ++
129 e71c47d3 Michele Tartara
                                  " arguments, got '" ++ unwords args ++ "'"
130 e71c47d3 Michele Tartara
  report <- buildDRBDReport statusFile pairingFile
131 e71c47d3 Michele Tartara
  putStrLn $ J.encode report