Statistics
| Branch: | Tag: | Revision:

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

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