Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / Drbd.hs @ 7a171e3f

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