Revision e4dac3e1

b/Makefile.am
725 725
	src/Ganeti/Utils.hs
726 726

  
727 727
HS_TEST_SRCS = \
728
	test/hs/Test/AutoConf.hs \
728 729
	test/hs/Test/Ganeti/Attoparsec.hs \
729 730
	test/hs/Test/Ganeti/BasicTypes.hs \
730 731
	test/hs/Test/Ganeti/Common.hs \
b/test/hs/Test/AutoConf.hs
1
{-# LANGUAGE TemplateHaskell #-}
2
{-| Unittests for 'AutoConf'
3

  
4
-}
5

  
6
{-
7

  
8
Copyright (C) 2013 Google Inc.
9

  
10
This program is free software; you can redistribute it and/or modify
11
it under the terms of the GNU General Public License as published by
12
the Free Software Foundation; either version 2 of the License, or
13
(at your option) any later version.
14

  
15
This program is distributed in the hope that it will be useful, but
16
WITHOUT ANY WARRANTY; without even the implied warranty of
17
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
18
General Public License for more details.
19

  
20
You should have received a copy of the GNU General Public License
21
along with this program; if not, write to the Free Software
22
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
23
02110-1301, USA.
24

  
25
-}
26

  
27
module Test.AutoConf where
28

  
29
import qualified Data.Char as Char (isAlpha)
30
import Test.HUnit as HUnit
31

  
32
import qualified AutoConf
33
import qualified Test.Ganeti.TestHelper as TestHelper
34

  
35
{-# ANN module "HLint: ignore Use camelCase" #-}
36

  
37
-- | 'isFilePath x' tests whether @x@ is a valid filepath
38
--
39
-- A valid filepath must be absolute and must not contain commas.
40
isFilePath :: String -> Bool
41
isFilePath ('/':str) = ',' `notElem` str
42
isFilePath _ = False
43

  
44
-- | 'isGntScript x' tests whether @x@ is a valid Ganeti script
45
--
46
-- A valid Ganeti script is prefixed by "gnt-" and the rest of the
47
-- 'String' contains only alphabetic 'Char's.
48
isGntScript :: String -> Bool
49
isGntScript str =
50
  case span (/= '-') str of
51
    (x, '-':y) -> x == "gnt" && all Char.isAlpha y
52
    _ -> False
53

  
54
-- | 'isGroup x' tests whether @x@ is a valid group name
55
--
56
-- A valid group name name is an alphabetic 'String' possibly
57
-- containing '-'.
58
isGroup :: String -> Bool
59
isGroup = all (\c -> Char.isAlpha c || c == '-')
60

  
61
-- | 'isProgram x' tests whether @x@ is a valid program name
62
--
63
-- A valid program name is an alphabetic 'String'.
64
isProgram :: String -> Bool
65
isProgram = all Char.isAlpha
66

  
67
-- | 'isUser x' tests whether @x@ is a valid username
68
--
69
-- See 'isGroup'.
70
isUser :: String -> Bool
71
isUser = isGroup
72

  
73
case_versionSuffix :: Assertion
74
case_versionSuffix =
75
  HUnit.assertBool
76
    "'versionSuffix' is invalid"
77
    (case AutoConf.versionSuffix of
78
        "" -> True
79
        '~':x -> not (null x)
80
        _ -> False)
81

  
82
case_localstatedir :: Assertion
83
case_localstatedir =
84
  HUnit.assertBool
85
    "'localstatedir' is invalid"
86
    (isFilePath AutoConf.localstatedir)
87

  
88
case_sysconfdir :: Assertion
89
case_sysconfdir =
90
  HUnit.assertBool
91
    "'sysconfdir' is invalid"
92
    (isFilePath AutoConf.sysconfdir)
93

  
94
case_sshConfigDir :: Assertion
95
case_sshConfigDir =
96
  HUnit.assertBool
97
    "'sshConfigDir' is invalid"
98
    (isFilePath AutoConf.sshConfigDir)
99

  
100
case_sshLoginUser :: Assertion
101
case_sshLoginUser =
102
  HUnit.assertBool
103
    "'sshLoginUser' is invalid"
104
    (isUser AutoConf.sshLoginUser)
105

  
106
case_sshConsoleUser :: Assertion
107
case_sshConsoleUser =
108
  HUnit.assertBool
109
    "'sshConsoleUser' is invalid"
110
    (isUser AutoConf.sshConsoleUser)
111

  
112
case_exportDir :: Assertion
113
case_exportDir =
114
  HUnit.assertBool
115
    "'exportDir' is invalid"
116
    (isFilePath AutoConf.exportDir)
117

  
118
case_osSearchPath :: Assertion
119
case_osSearchPath =
120
  HUnit.assertBool
121
    "'osSearchPath' is invalid"
122
    (all isFilePath AutoConf.osSearchPath)
123

  
124
case_esSearchPath :: Assertion
125
case_esSearchPath =
126
  HUnit.assertBool
127
    "'esSearchPath' is invalid"
128
    (all isFilePath AutoConf.esSearchPath)
129

  
130
case_xenBootloader :: Assertion
131
case_xenBootloader =
132
  HUnit.assertBool
133
    "'xenBootloader' is invalid"
134
    (null AutoConf.xenBootloader || isFilePath AutoConf.xenBootloader)
135

  
136
case_xenConfigDir :: Assertion
137
case_xenConfigDir =
138
  HUnit.assertBool
139
    "'xenConfigDir' is invalid"
140
    (isFilePath AutoConf.xenConfigDir)
141

  
142
case_xenKernel :: Assertion
143
case_xenKernel =
144
  HUnit.assertBool
145
    "'xenKernel' is invalid"
146
    (isFilePath AutoConf.xenKernel)
147

  
148
case_xenInitrd :: Assertion
149
case_xenInitrd =
150
  HUnit.assertBool
151
    "'xenInitrd' is invalid"
152
    (isFilePath AutoConf.xenInitrd)
153

  
154
case_kvmKernel :: Assertion
155
case_kvmKernel =
156
  HUnit.assertBool
157
    "'kvmKernel' is invalid"
158
    (isFilePath AutoConf.kvmKernel)
159

  
160
case_iallocatorSearchPath :: Assertion
161
case_iallocatorSearchPath =
162
  HUnit.assertBool
163
    "'iallocatorSearchPath' is invalid"
164
    (all isFilePath AutoConf.iallocatorSearchPath)
165

  
166
case_kvmPath :: Assertion
167
case_kvmPath =
168
  HUnit.assertBool
169
    "'kvmPath' is invalid"
170
    (isFilePath AutoConf.kvmPath)
171

  
172
case_ipPath :: Assertion
173
case_ipPath =
174
  HUnit.assertBool
175
    "'ipPath' is invalid"
176
    (isFilePath AutoConf.ipPath)
177

  
178
case_socatPath :: Assertion
179
case_socatPath =
180
  HUnit.assertBool
181
    "'socatPath' is invalid"
182
    (isFilePath AutoConf.socatPath)
183

  
184
case_toolsdir :: Assertion
185
case_toolsdir =
186
  HUnit.assertBool
187
    "'toolsdir' is invalid"
188
    (isFilePath AutoConf.toolsdir)
189

  
190
case_gntScripts :: Assertion
191
case_gntScripts =
192
  HUnit.assertBool
193
    "'gntScripts' is invalid"
194
    (all isGntScript AutoConf.gntScripts)
195

  
196
case_htoolsProgs :: Assertion
197
case_htoolsProgs =
198
  HUnit.assertBool
199
    "'htoolsProgs' is invalid"
200
    (all isProgram AutoConf.htoolsProgs)
201

  
202
case_pkglibdir :: Assertion
203
case_pkglibdir =
204
  HUnit.assertBool
205
    "'pkglibdir' is invalid"
206
    (isFilePath AutoConf.pkglibdir)
207

  
208
case_sharedir :: Assertion
209
case_sharedir =
210
  HUnit.assertBool
211
    "'sharedir' is invalid"
212
    (isFilePath AutoConf.sharedir)
213

  
214
case_versionedsharedir :: Assertion
215
case_versionedsharedir =
216
  HUnit.assertBool
217
    "'versionedsharedir' is invalid"
218
    (isFilePath AutoConf.versionedsharedir)
219

  
220
case_drbdBarriers :: Assertion
221
case_drbdBarriers =
222
  HUnit.assertBool
223
    "'drbdBarriers' is invalid"
224
    (AutoConf.drbdBarriers `elem` ["n", "bf"])
225

  
226
case_syslogUsage :: Assertion
227
case_syslogUsage =
228
  HUnit.assertBool
229
    "'syslogUsage' is invalid"
230
    (AutoConf.syslogUsage `elem` ["no", "yes", "only"])
231

  
232
case_daemonsGroup :: Assertion
233
case_daemonsGroup =
234
  HUnit.assertBool
235
    "'daemonsGroup' is invalid"
236
    (isGroup AutoConf.daemonsGroup)
237

  
238
case_adminGroup :: Assertion
239
case_adminGroup =
240
  HUnit.assertBool
241
    "'adminGroup' is invalid"
242
    (isGroup AutoConf.adminGroup)
243

  
244
case_masterdUser :: Assertion
245
case_masterdUser =
246
  HUnit.assertBool
247
    "'masterdUser' is invalid"
248
    (isUser AutoConf.masterdUser)
249

  
250
case_masterdGroup :: Assertion
251
case_masterdGroup =
252
  HUnit.assertBool
253
    "'masterdGroup' is invalid"
254
    (isGroup AutoConf.masterdGroup)
255

  
256
case_rapiUser :: Assertion
257
case_rapiUser =
258
  HUnit.assertBool
259
    "'rapiUser' is invalid"
260
    (isUser AutoConf.rapiUser)
261

  
262
case_rapiGroup :: Assertion
263
case_rapiGroup =
264
  HUnit.assertBool
265
    "'rapiGroup' is invalid"
266
    (isGroup AutoConf.rapiGroup)
267

  
268
case_confdUser :: Assertion
269
case_confdUser =
270
  HUnit.assertBool
271
    "'confdUser' is invalid"
272
    (isUser AutoConf.confdUser)
273

  
274
case_confdGroup :: Assertion
275
case_confdGroup =
276
  HUnit.assertBool
277
    "'confdGroup' is invalid"
278
    (isGroup AutoConf.confdGroup)
279

  
280
case_luxidUser :: Assertion
281
case_luxidUser =
282
  HUnit.assertBool
283
    "'luxidUser' is invalid"
284
    (isUser AutoConf.luxidUser)
285

  
286
case_luxidGroup :: Assertion
287
case_luxidGroup =
288
  HUnit.assertBool
289
    "'luxidGroup' is invalid"
290
    (isGroup AutoConf.luxidGroup)
291

  
292
case_nodedUser :: Assertion
293
case_nodedUser =
294
  HUnit.assertBool
295
    "'nodedUser' is invalid"
296
    (isUser AutoConf.nodedUser)
297

  
298
case_nodedGroup :: Assertion
299
case_nodedGroup =
300
  HUnit.assertBool
301
    "'nodedGroup' is invalid"
302
    (isGroup AutoConf.nodedGroup)
303

  
304
case_mondUser :: Assertion
305
case_mondUser =
306
  HUnit.assertBool
307
    "'mondUser' is invalid"
308
    (isUser AutoConf.mondUser)
309

  
310
case_mondGroup :: Assertion
311
case_mondGroup =
312
  HUnit.assertBool
313
    "'mondGroup' is invalid"
314
    (isUser AutoConf.mondGroup)
315

  
316
case_diskSeparator :: Assertion
317
case_diskSeparator =
318
  HUnit.assertBool
319
    "'diskSeparator' is invalid"
320
    (not (null AutoConf.diskSeparator))
321

  
322
case_qemuimgPath :: Assertion
323
case_qemuimgPath =
324
  HUnit.assertBool
325
    "'qemuimgPath' is invalid"
326
    (isFilePath AutoConf.qemuimgPath)
327

  
328
TestHelper.testSuite "AutoConf"
329
  [ 'case_versionSuffix
330
  , 'case_localstatedir
331
  , 'case_sysconfdir
332
  , 'case_sshConfigDir
333
  , 'case_sshLoginUser
334
  , 'case_sshConsoleUser
335
  , 'case_exportDir
336
  , 'case_osSearchPath
337
  , 'case_esSearchPath
338
  , 'case_xenBootloader
339
  , 'case_xenConfigDir
340
  , 'case_xenKernel
341
  , 'case_xenInitrd
342
  , 'case_kvmKernel
343
  , 'case_iallocatorSearchPath
344
  , 'case_kvmPath
345
  , 'case_ipPath
346
  , 'case_socatPath
347
  , 'case_toolsdir
348
  , 'case_gntScripts
349
  , 'case_htoolsProgs
350
  , 'case_pkglibdir
351
  , 'case_sharedir
352
  , 'case_versionedsharedir
353
  , 'case_drbdBarriers
354
  , 'case_syslogUsage
355
  , 'case_daemonsGroup
356
  , 'case_adminGroup
357
  , 'case_masterdUser
358
  , 'case_masterdGroup
359
  , 'case_rapiUser
360
  , 'case_rapiGroup
361
  , 'case_confdUser
362
  , 'case_confdGroup
363
  , 'case_luxidUser
364
  , 'case_luxidGroup
365
  , 'case_nodedUser
366
  , 'case_nodedGroup
367
  , 'case_mondUser
368
  , 'case_mondGroup
369
  , 'case_diskSeparator
370
  , 'case_qemuimgPath ]
b/test/hs/htest.hs
30 30
import System.Environment (getArgs)
31 31
import System.Log.Logger
32 32

  
33
import Test.AutoConf
33 34
import Test.Ganeti.TestImports ()
34 35
import Test.Ganeti.Attoparsec
35 36
import Test.Ganeti.BasicTypes
......
88 89
-- | All our defined tests.
89 90
allTests :: [Test]
90 91
allTests =
91
  [ testBasicTypes
92
  [ testAutoConf
93
  , testBasicTypes
92 94
  , testAttoparsec
93 95
  , testCommon
94 96
  , testConstants

Also available in: Unified diff