Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / DataCollectors / CLI.hs @ 229da00f

History | View | Annotate | Download (4.7 kB)

1 55abd2c7 Iustin Pop
{-| Implementation of DataCollectors CLI functions.
2 55abd2c7 Iustin Pop
3 55abd2c7 Iustin Pop
This module holds the common command-line related functions for the
4 55abd2c7 Iustin Pop
collector binaries.
5 55abd2c7 Iustin Pop
6 55abd2c7 Iustin Pop
-}
7 55abd2c7 Iustin Pop
8 55abd2c7 Iustin Pop
{-
9 55abd2c7 Iustin Pop
10 55abd2c7 Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012 Google Inc.
11 55abd2c7 Iustin Pop
12 55abd2c7 Iustin Pop
This program is free software; you can redistribute it and/or modify
13 55abd2c7 Iustin Pop
it under the terms of the GNU General Public License as published by
14 55abd2c7 Iustin Pop
the Free Software Foundation; either version 2 of the License, or
15 55abd2c7 Iustin Pop
(at your option) any later version.
16 55abd2c7 Iustin Pop
17 55abd2c7 Iustin Pop
This program is distributed in the hope that it will be useful, but
18 55abd2c7 Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
19 55abd2c7 Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
20 55abd2c7 Iustin Pop
General Public License for more details.
21 55abd2c7 Iustin Pop
22 55abd2c7 Iustin Pop
You should have received a copy of the GNU General Public License
23 55abd2c7 Iustin Pop
along with this program; if not, write to the Free Software
24 55abd2c7 Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
25 55abd2c7 Iustin Pop
02110-1301, USA.
26 55abd2c7 Iustin Pop
27 55abd2c7 Iustin Pop
-}
28 55abd2c7 Iustin Pop
29 55abd2c7 Iustin Pop
module Ganeti.DataCollectors.CLI
30 55abd2c7 Iustin Pop
  ( Options(..)
31 55abd2c7 Iustin Pop
  , OptType
32 55abd2c7 Iustin Pop
  , defaultOptions
33 55abd2c7 Iustin Pop
  -- * The options
34 55abd2c7 Iustin Pop
  , oShowHelp
35 55abd2c7 Iustin Pop
  , oShowVer
36 55abd2c7 Iustin Pop
  , oShowComp
37 d78970ba Michele Tartara
  , oDrbdPairing
38 d78970ba Michele Tartara
  , oDrbdStatus
39 7dc27988 Michele Tartara
  , oNode
40 7dc27988 Michele Tartara
  , oConfdAddr
41 7dc27988 Michele Tartara
  , oConfdPort
42 67ebc173 Michele Tartara
  , oInputFile
43 53753d20 Michele Tartara
  , oInstances
44 55abd2c7 Iustin Pop
  , genericOptions
45 55abd2c7 Iustin Pop
  ) where
46 55abd2c7 Iustin Pop
47 d78970ba Michele Tartara
import System.Console.GetOpt
48 d78970ba Michele Tartara
49 d78970ba Michele Tartara
import Ganeti.BasicTypes
50 55abd2c7 Iustin Pop
import Ganeti.Common as Common
51 7dc27988 Michele Tartara
import Ganeti.Utils
52 7dc27988 Michele Tartara
53 55abd2c7 Iustin Pop
54 55abd2c7 Iustin Pop
-- * Data types
55 55abd2c7 Iustin Pop
56 55abd2c7 Iustin Pop
-- | Command line options structure.
57 55abd2c7 Iustin Pop
data Options = Options
58 55abd2c7 Iustin Pop
  { optShowHelp    :: Bool           -- ^ Just show the help
59 55abd2c7 Iustin Pop
  , optShowComp    :: Bool           -- ^ Just show the completion info
60 55abd2c7 Iustin Pop
  , optShowVer     :: Bool           -- ^ Just show the program version
61 d78970ba Michele Tartara
  , optDrbdStatus  :: Maybe FilePath -- ^ Path to the file containing DRBD
62 d78970ba Michele Tartara
                                     -- status information
63 d78970ba Michele Tartara
  , optDrbdPairing :: Maybe FilePath -- ^ Path to the file containing pairings
64 d78970ba Michele Tartara
                                     -- between instances and DRBD minors
65 7dc27988 Michele Tartara
  , optNode        :: Maybe String   -- ^ Info are requested for this node
66 7dc27988 Michele Tartara
  , optConfdAddr   :: Maybe String   -- ^ IP address of the Confd server
67 7dc27988 Michele Tartara
  , optConfdPort   :: Maybe Int      -- ^ The port of the Confd server to
68 7dc27988 Michele Tartara
                                     -- connect to
69 67ebc173 Michele Tartara
  , optInputFile   :: Maybe FilePath -- ^ Path to the file containing the
70 67ebc173 Michele Tartara
                                     -- information to be parsed
71 53753d20 Michele Tartara
  , optInstances   :: Maybe FilePath -- ^ Path to the file contained a
72 53753d20 Michele Tartara
                                     -- serialized list of instances as in:
73 53753d20 Michele Tartara
                                     -- ([Primary], [Secondary])
74 55abd2c7 Iustin Pop
  } deriving Show
75 55abd2c7 Iustin Pop
76 55abd2c7 Iustin Pop
-- | Default values for the command line options.
77 55abd2c7 Iustin Pop
defaultOptions :: Options
78 55abd2c7 Iustin Pop
defaultOptions  = Options
79 55abd2c7 Iustin Pop
  { optShowHelp    = False
80 55abd2c7 Iustin Pop
  , optShowComp    = False
81 55abd2c7 Iustin Pop
  , optShowVer     = False
82 d78970ba Michele Tartara
  , optDrbdStatus  = Nothing
83 d78970ba Michele Tartara
  , optDrbdPairing = Nothing
84 7dc27988 Michele Tartara
  , optNode        = Nothing
85 7dc27988 Michele Tartara
  , optConfdAddr   = Nothing
86 7dc27988 Michele Tartara
  , optConfdPort   = Nothing
87 67ebc173 Michele Tartara
  , optInputFile   = Nothing
88 53753d20 Michele Tartara
  , optInstances   = Nothing
89 55abd2c7 Iustin Pop
  }
90 55abd2c7 Iustin Pop
91 55abd2c7 Iustin Pop
-- | Abbreviation for the option type.
92 55abd2c7 Iustin Pop
type OptType = GenericOptType Options
93 55abd2c7 Iustin Pop
94 55abd2c7 Iustin Pop
instance StandardOptions Options where
95 55abd2c7 Iustin Pop
  helpRequested = optShowHelp
96 55abd2c7 Iustin Pop
  verRequested  = optShowVer
97 55abd2c7 Iustin Pop
  compRequested = optShowComp
98 55abd2c7 Iustin Pop
  requestHelp o = o { optShowHelp = True }
99 55abd2c7 Iustin Pop
  requestVer  o = o { optShowVer  = True }
100 55abd2c7 Iustin Pop
  requestComp o = o { optShowComp = True }
101 55abd2c7 Iustin Pop
102 55abd2c7 Iustin Pop
-- * Command line options
103 d78970ba Michele Tartara
oDrbdPairing :: OptType
104 d78970ba Michele Tartara
oDrbdPairing =
105 d78970ba Michele Tartara
  ( Option "p" ["drbd-pairing"]
106 d78970ba Michele Tartara
      (ReqArg (\ f o -> Ok o { optDrbdPairing = Just f}) "FILE")
107 d78970ba Michele Tartara
      "the FILE containing pairings between instances and DRBD minors",
108 d78970ba Michele Tartara
    OptComplFile)
109 d78970ba Michele Tartara
110 d78970ba Michele Tartara
oDrbdStatus :: OptType
111 d78970ba Michele Tartara
oDrbdStatus =
112 d78970ba Michele Tartara
  ( Option "s" ["drbd-status"]
113 d78970ba Michele Tartara
      (ReqArg (\ f o -> Ok o { optDrbdStatus = Just f }) "FILE")
114 d78970ba Michele Tartara
      "the DRBD status FILE",
115 d78970ba Michele Tartara
    OptComplFile)
116 55abd2c7 Iustin Pop
117 7dc27988 Michele Tartara
oNode :: OptType
118 7dc27988 Michele Tartara
oNode =
119 7dc27988 Michele Tartara
  ( Option "n" ["node"]
120 7dc27988 Michele Tartara
      (ReqArg (\ n o -> Ok o { optNode = Just n }) "NODE")
121 7dc27988 Michele Tartara
      "the FQDN of the NODE about which information is requested",
122 7dc27988 Michele Tartara
    OptComplFile)
123 7dc27988 Michele Tartara
124 7dc27988 Michele Tartara
oConfdAddr :: OptType
125 7dc27988 Michele Tartara
oConfdAddr =
126 7dc27988 Michele Tartara
  ( Option "a" ["address"]
127 7dc27988 Michele Tartara
      (ReqArg (\ a o -> Ok o { optConfdAddr = Just a }) "IP_ADDR")
128 7dc27988 Michele Tartara
      "the IP address of the Confd server to connect to",
129 7dc27988 Michele Tartara
    OptComplFile)
130 7dc27988 Michele Tartara
131 7dc27988 Michele Tartara
oConfdPort :: OptType
132 7dc27988 Michele Tartara
oConfdPort =
133 7dc27988 Michele Tartara
  (Option "p" ["port"]
134 7dc27988 Michele Tartara
    (reqWithConversion (tryRead "reading port")
135 7dc27988 Michele Tartara
      (\port opts -> Ok opts { optConfdPort = Just port }) "PORT")
136 7dc27988 Michele Tartara
    "Network port of the Confd server to connect to",
137 7dc27988 Michele Tartara
    OptComplInteger)
138 7dc27988 Michele Tartara
139 67ebc173 Michele Tartara
oInputFile :: OptType
140 67ebc173 Michele Tartara
oInputFile =
141 67ebc173 Michele Tartara
  ( Option "f" ["file"]
142 67ebc173 Michele Tartara
      (ReqArg (\ f o -> Ok o { optInputFile = Just f }) "FILE")
143 67ebc173 Michele Tartara
      "the input FILE",
144 67ebc173 Michele Tartara
    OptComplFile)
145 67ebc173 Michele Tartara
146 53753d20 Michele Tartara
oInstances :: OptType
147 53753d20 Michele Tartara
oInstances =
148 53753d20 Michele Tartara
  ( Option "i" ["instances"]
149 53753d20 Michele Tartara
      (ReqArg (\ f o -> Ok o { optInstances = Just f}) "FILE")
150 53753d20 Michele Tartara
      "the FILE containing serialized instances",
151 53753d20 Michele Tartara
    OptComplFile)
152 53753d20 Michele Tartara
153 55abd2c7 Iustin Pop
-- | Generic options.
154 55abd2c7 Iustin Pop
genericOptions :: [GenericOptType Options]
155 55abd2c7 Iustin Pop
genericOptions =  [ oShowVer
156 55abd2c7 Iustin Pop
                  , oShowHelp
157 55abd2c7 Iustin Pop
                  , oShowComp
158 55abd2c7 Iustin Pop
                  ]