module Ganeti.DataCollectors.Drbd
( main
, options
, arguments
, dcName
, dcVersion
, dcFormatVersion
, dcCategory
, dcKind
, dcReport
) where
import qualified Control.Exception as E
import Control.Monad
import Data.Attoparsec.Text.Lazy as A
import Data.List
import Data.Maybe
import Data.Text.Lazy (pack, unpack)
import Network.BSD (getHostName)
import qualified Text.JSON as J
import qualified Ganeti.BasicTypes as BT
import qualified Ganeti.Constants as C
import Ganeti.Storage.Drbd.Parser(drbdStatusParser)
import Ganeti.Storage.Drbd.Types
import Ganeti.Common
import Ganeti.Confd.Client
import Ganeti.Confd.Types
import Ganeti.DataCollectors.CLI
import Ganeti.DataCollectors.Types
import Ganeti.Utils
defaultFile :: FilePath
defaultFile = C.drbdStatusFile
defaultCharNum :: Int
defaultCharNum = 80*20
dcName :: String
dcName = C.dataCollectorDrbd
dcVersion :: DCVersion
dcVersion = DCVerBuiltin
dcFormatVersion :: Int
dcFormatVersion = 1
dcCategory :: Maybe DCCategory
dcCategory = Just DCStorage
dcKind :: DCKind
dcKind = DCKStatus
dcReport :: IO DCReport
dcReport = buildDCReport defaultFile Nothing
options :: IO [OptType]
options =
return
[ oDrbdStatus
, oDrbdPairing
]
arguments :: [ArgCompletion]
arguments = [ArgCompletion OptComplFile 0 (Just 0)]
getPairingInfo :: Maybe String -> IO (BT.Result [DrbdInstMinor])
getPairingInfo Nothing = do
curNode <- getHostName
client <- getConfdClient Nothing Nothing
reply <- query client ReqNodeDrbd $ PlainQuery curNode
return $
case fmap (J.readJSONs . confdReplyAnswer) reply of
Just (J.Ok instMinor) -> BT.Ok instMinor
Just (J.Error msg) -> BT.Bad msg
Nothing -> BT.Bad "No answer from the Confd server"
getPairingInfo (Just filename) = do
content <- readFile filename
return $
case J.decode content of
J.Ok instMinor -> BT.Ok instMinor
J.Error msg -> BT.Bad msg
computeStatus :: DRBDStatus -> DCStatus
computeStatus (DRBDStatus _ devInfos) =
let statuses = map computeDevStatus devInfos
(code, strList) = foldr mergeStatuses (DCSCOk, [""]) statuses
in DCStatus code $ intercalate "\n" strList
computeDevStatus :: DeviceInfo -> (DCStatusCode, String)
computeDevStatus (UnconfiguredDevice _) = (DCSCOk, "")
computeDevStatus dev =
let errMsg s = show (minorNumber dev) ++ ": " ++ s
compute_helper StandAlone =
(DCSCBad, errMsg "No network config available")
compute_helper Disconnecting =
(DCSCBad, errMsg "The peer is being disconnected")
compute_helper Unconnected =
(DCSCTempBad, errMsg "Trying to establish a network connection")
compute_helper Timeout =
(DCSCTempBad, errMsg "Communication problems between the peers")
compute_helper BrokenPipe =
(DCSCTempBad, errMsg "Communication problems between the peers")
compute_helper NetworkFailure =
(DCSCTempBad, errMsg "Communication problems between the peers")
compute_helper ProtocolError =
(DCSCTempBad, errMsg "Communication problems between the peers")
compute_helper TearDown =
(DCSCBad, errMsg "The peer is closing the connection")
compute_helper WFConnection =
(DCSCTempBad, errMsg "Trying to establish a network connection")
compute_helper WFReportParams =
(DCSCTempBad, errMsg "Trying to establish a network connection")
compute_helper Connected = (DCSCOk, "")
compute_helper StartingSyncS = (DCSCOk, "")
compute_helper StartingSyncT = (DCSCOk, "")
compute_helper WFBitMapS = (DCSCOk, "")
compute_helper WFBitMapT = (DCSCOk, "")
compute_helper WFSyncUUID = (DCSCOk, "")
compute_helper SyncSource = (DCSCOk, "")
compute_helper SyncTarget = (DCSCOk, "")
compute_helper PausedSyncS = (DCSCOk, "")
compute_helper PausedSyncT = (DCSCOk, "")
compute_helper VerifyS = (DCSCOk, "")
compute_helper VerifyT = (DCSCOk, "")
compute_helper Unconfigured = (DCSCOk, "")
in compute_helper $ connectionState dev
buildJsonReport :: FilePath -> Maybe FilePath -> IO J.JSValue
buildJsonReport statusFile pairingFile = do
contents <-
((E.try $ readFile statusFile) :: IO (Either IOError String)) >>=
exitIfBad "reading from file" . either (BT.Bad . show) BT.Ok
pairingResult <- getPairingInfo pairingFile
pairing <- logWarningIfBad "Can't get pairing info" [] pairingResult
drbdData <-
case A.parse (drbdStatusParser pairing) $ pack contents of
A.Fail unparsedText contexts errorMessage -> exitErr $
show (Prelude.take defaultCharNum $ unpack unparsedText) ++ "\n"
++ show contexts ++ "\n" ++ errorMessage
A.Done _ drbdS -> return drbdS
let status = computeStatus drbdData
return . addStatus status $ J.showJSON drbdData
buildDCReport :: FilePath -> Maybe FilePath -> IO DCReport
buildDCReport statusFile pairingFile =
buildJsonReport statusFile pairingFile >>=
buildReport dcName dcVersion dcFormatVersion dcCategory dcKind
main :: Options -> [String] -> IO ()
main opts args = do
let statusFile = fromMaybe defaultFile $ optDrbdStatus opts
pairingFile = optDrbdPairing opts
unless (null args) . exitErr $ "This program takes exactly zero" ++
" arguments, got '" ++ unwords args ++ "'"
report <- buildDCReport statusFile pairingFile
putStrLn $ J.encode report