Revision 256e28c4

b/htest/Test/Ganeti/Utils.hs
31 31
import Test.QuickCheck hiding (Result)
32 32
import Test.HUnit
33 33

  
34
import Data.Char (isSpace)
34 35
import Data.List
35 36
import qualified Text.JSON as J
36 37

  
......
202 203
                                                    zip numbers names)
203 204
  ]
204 205

  
206
-- | Tests 'rstripSpace'.
207
prop_rStripSpace :: NonEmptyList Char -> Property
208
prop_rStripSpace (NonEmpty str) =
209
  forAll (resize 50 $ listOf1 (arbitrary `suchThat` isSpace)) $ \whitespace ->
210
  conjoin [ printTestCase "arb. string last char is not space" $
211
              case rStripSpace str of
212
                [] -> True
213
                xs -> not . isSpace $ last xs
214
          , printTestCase "whitespace suffix is stripped" $
215
              rStripSpace str ==? rStripSpace (str ++ whitespace)
216
          , printTestCase "whitespace reduced to null" $
217
              rStripSpace whitespace ==? ""
218
          , printTestCase "idempotent on empty strings" $
219
              rStripSpace "" ==? ""
220
          ]
221

  
205 222
-- | Test list for the Utils module.
206 223
testSuite "Utils"
207 224
            [ 'prop_commaJoinSplit
......
217 234
            , 'prop_niceSort_generic
218 235
            , 'prop_niceSort_numbers
219 236
            , 'prop_niceSortKey_equiv
237
            , 'prop_rStripSpace
220 238
            ]
b/htools/Ganeti/Ssconf.hs
38 38

  
39 39
import Control.Exception
40 40
import Control.Monad (liftM)
41
import Data.Char (isSpace)
42 41
import Data.Maybe (fromMaybe)
43 42
import qualified Network.Socket as Socket
44 43
import System.FilePath ((</>))
......
116 115
            keyToFilename (fromMaybe dpath optpath) $ key
117 116
  return (liftM (take maxFileSize) result)
118 117

  
119
-- | Strip space characthers (including newline). As this is
120
-- expensive, should only be run on small strings.
121
rstripSpace :: String -> String
122
rstripSpace = reverse . dropWhile isSpace . reverse
123

  
124 118
-- | Parses a string containing an IP family
125 119
parseIPFamily :: Int -> Result Socket.Family
126 120
parseIPFamily fam | fam == C.ip4Family = Ok Socket.AF_INET
......
131 125
getPrimaryIPFamily :: Maybe FilePath -> IO (Result Socket.Family)
132 126
getPrimaryIPFamily optpath = do
133 127
  result <- readSSConfFile optpath (Just (show C.ip4Family)) SSPrimaryIpFamily
134
  return (liftM rstripSpace result >>=
128
  return (liftM rStripSpace result >>=
135 129
          tryRead "Parsing af_family" >>= parseIPFamily)
b/htools/Ganeti/Utils.hs
43 43
  , exitErr
44 44
  , exitWhen
45 45
  , exitUnless
46
  , rStripSpace
46 47
  ) where
47 48

  
48
import Data.Char (toUpper, isAlphaNum, isDigit)
49
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
49 50
import Data.Function (on)
50 51
import Data.List
51 52

  
......
271 272
niceSortKey keyfn =
272 273
  map snd . sortBy (compare `on` fst) .
273 274
  map (\s -> (fst . extractKey [] $ keyfn s, s))
275

  
276
-- | Strip space characthers (including newline). As this is
277
-- expensive, should only be run on small strings.
278
rStripSpace :: String -> String
279
rStripSpace = reverse . dropWhile isSpace . reverse

Also available in: Unified diff