Revision 7dc27988

b/src/Ganeti/Confd/Client.hs
31 31
import Control.Concurrent
32 32
import Control.Monad
33 33
import Data.List
34
import Data.Maybe
34 35
import qualified Network.Socket as S
35 36
import System.Posix.Time
36 37
import qualified Text.JSON as J
......
42 43
import Ganeti.Hash
43 44
import Ganeti.Ssconf
44 45

  
45
-- | Builds a properly initialized ConfdClient
46
getConfdClient :: IO ConfdClient
47
getConfdClient = S.withSocketsDo $ do
46
-- | Builds a properly initialized ConfdClient.
47
-- The parameters (an IP address and the port number for the Confd client
48
-- to connect to) are mainly meant for testing purposes. If they are not
49
-- provided, the list of master candidates and the default port number will
50
-- be used.
51
getConfdClient :: Maybe String -> Maybe Int -> IO ConfdClient
52
getConfdClient addr portNum = S.withSocketsDo $ do
48 53
  hmac <- getClusterHmac
49 54
  candList <- getMasterCandidatesIps Nothing
50 55
  peerList <-
51 56
    case candList of
52 57
      (Ok p) -> return p
53 58
      (Bad msg) -> fail msg
54
  return . ConfdClient hmac peerList $ fromIntegral C.defaultConfdPort
59
  let addrList = maybe peerList (:[]) addr
60
      port = fromMaybe C.defaultConfdPort portNum
61
  return . ConfdClient hmac addrList $ fromIntegral port
55 62

  
56 63
-- | Sends a query to all the Confd servers the client is connected to.
57 64
-- Returns the most up-to-date result according to the serial number,
b/src/Ganeti/DataCollectors/CLI.hs
36 36
  , oShowComp
37 37
  , oDrbdPairing
38 38
  , oDrbdStatus
39
  , oNode
40
  , oConfdAddr
41
  , oConfdPort
39 42
  , genericOptions
40 43
  ) where
41 44

  
......
43 46

  
44 47
import Ganeti.BasicTypes
45 48
import Ganeti.Common as Common
49
import Ganeti.Utils
50

  
46 51

  
47 52
-- * Data types
48 53

  
......
55 60
                                     -- status information
56 61
  , optDrbdPairing :: Maybe FilePath -- ^ Path to the file containing pairings
57 62
                                     -- between instances and DRBD minors
63
  , optNode        :: Maybe String   -- ^ Info are requested for this node
64
  , optConfdAddr   :: Maybe String   -- ^ IP address of the Confd server
65
  , optConfdPort   :: Maybe Int      -- ^ The port of the Confd server to
66
                                     -- connect to
58 67
  } deriving Show
59 68

  
60 69
-- | Default values for the command line options.
......
65 74
  , optShowVer     = False
66 75
  , optDrbdStatus  = Nothing
67 76
  , optDrbdPairing = Nothing
77
  , optNode        = Nothing
78
  , optConfdAddr   = Nothing
79
  , optConfdPort   = Nothing
68 80
  }
69 81

  
70 82
-- | Abbreviation for the option type.
......
93 105
      "the DRBD status FILE",
94 106
    OptComplFile)
95 107

  
108
oNode :: OptType
109
oNode =
110
  ( Option "n" ["node"]
111
      (ReqArg (\ n o -> Ok o { optNode = Just n }) "NODE")
112
      "the FQDN of the NODE about which information is requested",
113
    OptComplFile)
114

  
115
oConfdAddr :: OptType
116
oConfdAddr =
117
  ( Option "a" ["address"]
118
      (ReqArg (\ a o -> Ok o { optConfdAddr = Just a }) "IP_ADDR")
119
      "the IP address of the Confd server to connect to",
120
    OptComplFile)
121

  
122
oConfdPort :: OptType
123
oConfdPort =
124
  (Option "p" ["port"]
125
    (reqWithConversion (tryRead "reading port")
126
      (\port opts -> Ok opts { optConfdPort = Just port }) "PORT")
127
    "Network port of the Confd server to connect to",
128
    OptComplInteger)
129

  
96 130
-- | Generic options.
97 131
genericOptions :: [GenericOptType Options]
98 132
genericOptions =  [ oShowVer
b/src/Ganeti/DataCollectors/Drbd.hs
90 90
getPairingInfo :: Maybe String -> IO (BT.Result [DrbdInstMinor])
91 91
getPairingInfo Nothing = do
92 92
  curNode <- getHostName
93
  client <- getConfdClient
93
  client <- getConfdClient Nothing Nothing
94 94
  reply <- query client ReqNodeDrbd $ PlainQuery curNode
95 95
  return $
96 96
    case fmap (J.readJSONs . confdReplyAnswer) reply of

Also available in: Unified diff