Statistics
| Branch: | Tag: | Revision:

root / src / Ganeti / Utils.hs @ 9411474b

History | View | Annotate | Download (12.3 kB)

1 525bfb36 Iustin Pop
{-| Utility functions. -}
2 e4f08c46 Iustin Pop
3 e2fa2baf Iustin Pop
{-
4 e2fa2baf Iustin Pop
5 a7f0953a Iustin Pop
Copyright (C) 2009, 2010, 2011, 2012, 2013 Google Inc.
6 e2fa2baf Iustin Pop
7 e2fa2baf Iustin Pop
This program is free software; you can redistribute it and/or modify
8 e2fa2baf Iustin Pop
it under the terms of the GNU General Public License as published by
9 e2fa2baf Iustin Pop
the Free Software Foundation; either version 2 of the License, or
10 e2fa2baf Iustin Pop
(at your option) any later version.
11 e2fa2baf Iustin Pop
12 e2fa2baf Iustin Pop
This program is distributed in the hope that it will be useful, but
13 e2fa2baf Iustin Pop
WITHOUT ANY WARRANTY; without even the implied warranty of
14 e2fa2baf Iustin Pop
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
15 e2fa2baf Iustin Pop
General Public License for more details.
16 e2fa2baf Iustin Pop
17 e2fa2baf Iustin Pop
You should have received a copy of the GNU General Public License
18 e2fa2baf Iustin Pop
along with this program; if not, write to the Free Software
19 e2fa2baf Iustin Pop
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
20 e2fa2baf Iustin Pop
02110-1301, USA.
21 e2fa2baf Iustin Pop
22 e2fa2baf Iustin Pop
-}
23 e2fa2baf Iustin Pop
24 26d62e4c Iustin Pop
module Ganeti.Utils
25 ebf38064 Iustin Pop
  ( debug
26 ebf38064 Iustin Pop
  , debugFn
27 ebf38064 Iustin Pop
  , debugXy
28 ebf38064 Iustin Pop
  , sepSplit
29 ebf38064 Iustin Pop
  , stdDev
30 ebf38064 Iustin Pop
  , if'
31 ebf38064 Iustin Pop
  , select
32 ebf38064 Iustin Pop
  , applyIf
33 ebf38064 Iustin Pop
  , commaJoin
34 79eef90b Agata Murawska
  , ensureQuoted
35 ebf38064 Iustin Pop
  , tryRead
36 ebf38064 Iustin Pop
  , formatTable
37 c3024b7e René Nussbaumer
  , printTable
38 ebf38064 Iustin Pop
  , parseUnit
39 19e310cc René Nussbaumer
  , plural
40 04edfc99 Iustin Pop
  , niceSort
41 04edfc99 Iustin Pop
  , niceSortKey
42 88a10df5 Iustin Pop
  , exitIfBad
43 88a10df5 Iustin Pop
  , exitErr
44 88a10df5 Iustin Pop
  , exitWhen
45 88a10df5 Iustin Pop
  , exitUnless
46 256e28c4 Iustin Pop
  , rStripSpace
47 80a0546b Michele Tartara
  , newUUID
48 ace37e24 Michele Tartara
  , getCurrentTime
49 a6e054a8 Iustin Pop
  , getCurrentTimeUSec
50 b6aeda4a Dato Simó
  , clockTimeToString
51 b009f682 Dato Simó
  , chompPrefix
52 9fb621af Yiannis Tsiouris
  , wrap
53 9fb621af Yiannis Tsiouris
  , trim
54 ebf38064 Iustin Pop
  ) where
55 e4f08c46 Iustin Pop
56 256e28c4 Iustin Pop
import Data.Char (toUpper, isAlphaNum, isDigit, isSpace)
57 04edfc99 Iustin Pop
import Data.Function (on)
58 29ac5975 Iustin Pop
import Data.List
59 e4f08c46 Iustin Pop
60 e4f08c46 Iustin Pop
import Debug.Trace
61 e4f08c46 Iustin Pop
62 88a10df5 Iustin Pop
import Ganeti.BasicTypes
63 80a0546b Michele Tartara
import qualified Ganeti.Constants as C
64 88a10df5 Iustin Pop
import System.IO
65 88a10df5 Iustin Pop
import System.Exit
66 b6aeda4a Dato Simó
import System.Time
67 88a10df5 Iustin Pop
68 9188aeef Iustin Pop
-- * Debug functions
69 9188aeef Iustin Pop
70 e4f08c46 Iustin Pop
-- | To be used only for debugging, breaks referential integrity.
71 e4f08c46 Iustin Pop
debug :: Show a => a -> a
72 e4f08c46 Iustin Pop
debug x = trace (show x) x
73 e4f08c46 Iustin Pop
74 525bfb36 Iustin Pop
-- | Displays a modified form of the second parameter before returning
75 525bfb36 Iustin Pop
-- it.
76 adc5c176 Iustin Pop
debugFn :: Show b => (a -> b) -> a -> a
77 adc5c176 Iustin Pop
debugFn fn x = debug (fn x) `seq` x
78 adc5c176 Iustin Pop
79 525bfb36 Iustin Pop
-- | Show the first parameter before returning the second one.
80 adc5c176 Iustin Pop
debugXy :: Show a => a -> b -> b
81 05ff7a00 Agata Murawska
debugXy = seq . debug
82 adc5c176 Iustin Pop
83 525bfb36 Iustin Pop
-- * Miscellaneous
84 1b7cf8ca Iustin Pop
85 61bbbed7 Agata Murawska
-- | Apply the function if condition holds, otherwise use default value.
86 61bbbed7 Agata Murawska
applyIf :: Bool -> (a -> a) -> a -> a
87 61bbbed7 Agata Murawska
applyIf b f x = if b then f x else x
88 61bbbed7 Agata Murawska
89 e4f08c46 Iustin Pop
-- | Comma-join a string list.
90 e4f08c46 Iustin Pop
commaJoin :: [String] -> String
91 e4f08c46 Iustin Pop
commaJoin = intercalate ","
92 e4f08c46 Iustin Pop
93 748d5d50 Iustin Pop
-- | Split a list on a separator and return an array.
94 748d5d50 Iustin Pop
sepSplit :: Eq a => a -> [a] -> [[a]]
95 e4f08c46 Iustin Pop
sepSplit sep s
96 ebf38064 Iustin Pop
  | null s    = []
97 ebf38064 Iustin Pop
  | null xs   = [x]
98 ebf38064 Iustin Pop
  | null ys   = [x,[]]
99 ebf38064 Iustin Pop
  | otherwise = x:sepSplit sep ys
100 ebf38064 Iustin Pop
  where (x, xs) = break (== sep) s
101 ebf38064 Iustin Pop
        ys = drop 1 xs
102 e4f08c46 Iustin Pop
103 19e310cc René Nussbaumer
-- | Simple pluralize helper
104 19e310cc René Nussbaumer
plural :: Int -> String -> String -> String
105 19e310cc René Nussbaumer
plural 1 s _ = s
106 19e310cc René Nussbaumer
plural _ _ p = p
107 19e310cc René Nussbaumer
108 79eef90b Agata Murawska
-- | Ensure a value is quoted if needed.
109 79eef90b Agata Murawska
ensureQuoted :: String -> String
110 79eef90b Agata Murawska
ensureQuoted v = if not (all (\c -> isAlphaNum c || c == '.') v)
111 79eef90b Agata Murawska
                 then '\'':v ++ "'"
112 79eef90b Agata Murawska
                 else v
113 79eef90b Agata Murawska
114 9188aeef Iustin Pop
-- * Mathematical functions
115 9188aeef Iustin Pop
116 185297fa Iustin Pop
-- Simple and slow statistical functions, please replace with better
117 185297fa Iustin Pop
-- versions
118 e4f08c46 Iustin Pop
119 525bfb36 Iustin Pop
-- | Standard deviation function.
120 4715711d Iustin Pop
stdDev :: [Double] -> Double
121 4715711d Iustin Pop
stdDev lst =
122 7570569e Iustin Pop
  -- first, calculate the list length and sum lst in a single step,
123 7570569e Iustin Pop
  -- for performance reasons
124 7570569e Iustin Pop
  let (ll', sx) = foldl' (\(rl, rs) e ->
125 7570569e Iustin Pop
                           let rl' = rl + 1
126 7570569e Iustin Pop
                               rs' = rs + e
127 7570569e Iustin Pop
                           in rl' `seq` rs' `seq` (rl', rs')) (0::Int, 0) lst
128 7570569e Iustin Pop
      ll = fromIntegral ll'::Double
129 7570569e Iustin Pop
      mv = sx / ll
130 7570569e Iustin Pop
      av = foldl' (\accu em -> let d = em - mv in accu + d * d) 0.0 lst
131 4715711d Iustin Pop
  in sqrt (av / ll) -- stddev
132 dd4c56ed Iustin Pop
133 bfe6c954 Guido Trotter
-- *  Logical functions
134 bfe6c954 Guido Trotter
135 bfe6c954 Guido Trotter
-- Avoid syntactic sugar and enhance readability. These functions are proposed
136 bfe6c954 Guido Trotter
-- by some for inclusion in the Prelude, and at the moment they are present
137 bfe6c954 Guido Trotter
-- (with various definitions) in the utility-ht package. Some rationale and
138 bfe6c954 Guido Trotter
-- discussion is available at <http://www.haskell.org/haskellwiki/If-then-else>
139 bfe6c954 Guido Trotter
140 bfe6c954 Guido Trotter
-- | \"if\" as a function, rather than as syntactic sugar.
141 bfe6c954 Guido Trotter
if' :: Bool -- ^ condition
142 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" result
143 bfe6c954 Guido Trotter
    -> a    -- ^ \"else\" result
144 bfe6c954 Guido Trotter
    -> a    -- ^ \"then\" or "else" result depending on the condition
145 bfe6c954 Guido Trotter
if' True x _ = x
146 bfe6c954 Guido Trotter
if' _    _ y = y
147 bfe6c954 Guido Trotter
148 5b763470 Iustin Pop
-- * Parsing utility functions
149 5b763470 Iustin Pop
150 525bfb36 Iustin Pop
-- | Parse results from readsPrec.
151 5b763470 Iustin Pop
parseChoices :: (Monad m, Read a) => String -> String -> [(a, String)] -> m a
152 5b763470 Iustin Pop
parseChoices _ _ ((v, ""):[]) = return v
153 5b763470 Iustin Pop
parseChoices name s ((_, e):[]) =
154 5b763470 Iustin Pop
    fail $ name ++ ": leftover characters when parsing '"
155 5b763470 Iustin Pop
           ++ s ++ "': '" ++ e ++ "'"
156 5b763470 Iustin Pop
parseChoices name s _ = fail $ name ++ ": cannot parse string '" ++ s ++ "'"
157 5b763470 Iustin Pop
158 5b763470 Iustin Pop
-- | Safe 'read' function returning data encapsulated in a Result.
159 5b763470 Iustin Pop
tryRead :: (Monad m, Read a) => String -> String -> m a
160 5b763470 Iustin Pop
tryRead name s = parseChoices name s $ reads s
161 c5f7412e Iustin Pop
162 525bfb36 Iustin Pop
-- | Format a table of strings to maintain consistent length.
163 c5f7412e Iustin Pop
formatTable :: [[String]] -> [Bool] -> [[String]]
164 c5f7412e Iustin Pop
formatTable vals numpos =
165 c5f7412e Iustin Pop
    let vtrans = transpose vals  -- transpose, so that we work on rows
166 c5f7412e Iustin Pop
                                 -- rather than columns
167 c5f7412e Iustin Pop
        mlens = map (maximum . map length) vtrans
168 c5f7412e Iustin Pop
        expnd = map (\(flds, isnum, ml) ->
169 c5f7412e Iustin Pop
                         map (\val ->
170 c5f7412e Iustin Pop
                                  let delta = ml - length val
171 c5f7412e Iustin Pop
                                      filler = replicate delta ' '
172 c5f7412e Iustin Pop
                                  in if delta > 0
173 c5f7412e Iustin Pop
                                     then if isnum
174 c5f7412e Iustin Pop
                                          then filler ++ val
175 c5f7412e Iustin Pop
                                          else val ++ filler
176 c5f7412e Iustin Pop
                                     else val
177 c5f7412e Iustin Pop
                             ) flds
178 c5f7412e Iustin Pop
                    ) (zip3 vtrans numpos mlens)
179 c5f7412e Iustin Pop
   in transpose expnd
180 9b9da389 Iustin Pop
181 c3024b7e René Nussbaumer
-- | Constructs a printable table from given header and rows
182 c3024b7e René Nussbaumer
printTable :: String -> [String] -> [[String]] -> [Bool] -> String
183 c3024b7e René Nussbaumer
printTable lp header rows isnum =
184 2cdaf225 Iustin Pop
  unlines . map ((++) lp . (:) ' ' . unwords) $
185 c3024b7e René Nussbaumer
  formatTable (header:rows) isnum
186 c3024b7e René Nussbaumer
187 1cdcf8f3 Iustin Pop
-- | Converts a unit (e.g. m or GB) into a scaling factor.
188 1cdcf8f3 Iustin Pop
parseUnitValue :: (Monad m) => String -> m Rational
189 1cdcf8f3 Iustin Pop
parseUnitValue unit
190 1cdcf8f3 Iustin Pop
  -- binary conversions first
191 1cdcf8f3 Iustin Pop
  | null unit                     = return 1
192 1cdcf8f3 Iustin Pop
  | unit == "m" || upper == "MIB" = return 1
193 1cdcf8f3 Iustin Pop
  | unit == "g" || upper == "GIB" = return kbBinary
194 1cdcf8f3 Iustin Pop
  | unit == "t" || upper == "TIB" = return $ kbBinary * kbBinary
195 1cdcf8f3 Iustin Pop
  -- SI conversions
196 1cdcf8f3 Iustin Pop
  | unit == "M" || upper == "MB"  = return mbFactor
197 1cdcf8f3 Iustin Pop
  | unit == "G" || upper == "GB"  = return $ mbFactor * kbDecimal
198 1cdcf8f3 Iustin Pop
  | unit == "T" || upper == "TB"  = return $ mbFactor * kbDecimal * kbDecimal
199 1cdcf8f3 Iustin Pop
  | otherwise = fail $ "Unknown unit '" ++ unit ++ "'"
200 1cdcf8f3 Iustin Pop
  where upper = map toUpper unit
201 5850e990 Iustin Pop
        kbBinary = 1024 :: Rational
202 5850e990 Iustin Pop
        kbDecimal = 1000 :: Rational
203 1cdcf8f3 Iustin Pop
        decToBin = kbDecimal / kbBinary -- factor for 1K conversion
204 1cdcf8f3 Iustin Pop
        mbFactor = decToBin * decToBin -- twice the factor for just 1K
205 1cdcf8f3 Iustin Pop
206 1cb92fac Iustin Pop
-- | Tries to extract number and scale from the given string.
207 1cb92fac Iustin Pop
--
208 1cb92fac Iustin Pop
-- Input must be in the format NUMBER+ SPACE* [UNIT]. If no unit is
209 1cb92fac Iustin Pop
-- specified, it defaults to MiB. Return value is always an integral
210 1cb92fac Iustin Pop
-- value in MiB.
211 1cb92fac Iustin Pop
parseUnit :: (Monad m, Integral a, Read a) => String -> m a
212 1cb92fac Iustin Pop
parseUnit str =
213 ebf38064 Iustin Pop
  -- TODO: enhance this by splitting the unit parsing code out and
214 ebf38064 Iustin Pop
  -- accepting floating-point numbers
215 1cdcf8f3 Iustin Pop
  case (reads str::[(Int, String)]) of
216 ebf38064 Iustin Pop
    [(v, suffix)] ->
217 ebf38064 Iustin Pop
      let unit = dropWhile (== ' ') suffix
218 1cdcf8f3 Iustin Pop
      in do
219 1cdcf8f3 Iustin Pop
        scaling <- parseUnitValue unit
220 1cdcf8f3 Iustin Pop
        return $ truncate (fromIntegral v * scaling)
221 ebf38064 Iustin Pop
    _ -> fail $ "Can't parse string '" ++ str ++ "'"
222 88a10df5 Iustin Pop
223 88a10df5 Iustin Pop
-- | Unwraps a 'Result', exiting the program if it is a 'Bad' value,
224 88a10df5 Iustin Pop
-- otherwise returning the actual contained value.
225 88a10df5 Iustin Pop
exitIfBad :: String -> Result a -> IO a
226 707cd3d7 Helga Velroyen
exitIfBad msg (Bad s) = exitErr (msg ++ ": " ++ s)
227 88a10df5 Iustin Pop
exitIfBad _ (Ok v) = return v
228 88a10df5 Iustin Pop
229 88a10df5 Iustin Pop
-- | Exits immediately with an error message.
230 88a10df5 Iustin Pop
exitErr :: String -> IO a
231 88a10df5 Iustin Pop
exitErr errmsg = do
232 707cd3d7 Helga Velroyen
  hPutStrLn stderr $ "Error: " ++ errmsg
233 88a10df5 Iustin Pop
  exitWith (ExitFailure 1)
234 88a10df5 Iustin Pop
235 88a10df5 Iustin Pop
-- | Exits with an error message if the given boolean condition if true.
236 88a10df5 Iustin Pop
exitWhen :: Bool -> String -> IO ()
237 88a10df5 Iustin Pop
exitWhen True msg = exitErr msg
238 88a10df5 Iustin Pop
exitWhen False _  = return ()
239 88a10df5 Iustin Pop
240 88a10df5 Iustin Pop
-- | Exits with an error message /unless/ the given boolean condition
241 88a10df5 Iustin Pop
-- if true, the opposite of 'exitWhen'.
242 88a10df5 Iustin Pop
exitUnless :: Bool -> String -> IO ()
243 88a10df5 Iustin Pop
exitUnless cond = exitWhen (not cond)
244 04edfc99 Iustin Pop
245 04edfc99 Iustin Pop
-- | Helper for 'niceSort'. Computes the key element for a given string.
246 04edfc99 Iustin Pop
extractKey :: [Either Integer String]  -- ^ Current (partial) key, reversed
247 04edfc99 Iustin Pop
           -> String                   -- ^ Remaining string
248 04edfc99 Iustin Pop
           -> ([Either Integer String], String)
249 04edfc99 Iustin Pop
extractKey ek [] = (reverse ek, [])
250 04edfc99 Iustin Pop
extractKey ek xs@(x:_) =
251 04edfc99 Iustin Pop
  let (span_fn, conv_fn) = if isDigit x
252 04edfc99 Iustin Pop
                             then (isDigit, Left . read)
253 04edfc99 Iustin Pop
                             else (not . isDigit, Right)
254 04edfc99 Iustin Pop
      (k, rest) = span span_fn xs
255 04edfc99 Iustin Pop
  in extractKey (conv_fn k:ek) rest
256 04edfc99 Iustin Pop
257 04edfc99 Iustin Pop
{-| Sort a list of strings based on digit and non-digit groupings.
258 04edfc99 Iustin Pop
259 04edfc99 Iustin Pop
Given a list of names @['a1', 'a10', 'a11', 'a2']@ this function
260 04edfc99 Iustin Pop
will sort the list in the logical order @['a1', 'a2', 'a10', 'a11']@.
261 04edfc99 Iustin Pop
262 04edfc99 Iustin Pop
The sort algorithm breaks each name in groups of either only-digits or
263 04edfc99 Iustin Pop
no-digits, and sorts based on each group.
264 04edfc99 Iustin Pop
265 04edfc99 Iustin Pop
Internally, this is not implemented via regexes (like the Python
266 04edfc99 Iustin Pop
version), but via actual splitting of the string in sequences of
267 04edfc99 Iustin Pop
either digits or everything else, and converting the digit sequences
268 04edfc99 Iustin Pop
in /Left Integer/ and the non-digit ones in /Right String/, at which
269 04edfc99 Iustin Pop
point sorting becomes trivial due to the built-in 'Either' ordering;
270 04edfc99 Iustin Pop
we only need one extra step of dropping the key at the end.
271 04edfc99 Iustin Pop
272 04edfc99 Iustin Pop
-}
273 04edfc99 Iustin Pop
niceSort :: [String] -> [String]
274 a7f0953a Iustin Pop
niceSort = niceSortKey id
275 04edfc99 Iustin Pop
276 04edfc99 Iustin Pop
-- | Key-version of 'niceSort'. We use 'sortBy' and @compare `on` fst@
277 04edfc99 Iustin Pop
-- since we don't want to add an ordering constraint on the /a/ type,
278 04edfc99 Iustin Pop
-- hence the need to only compare the first element of the /(key, a)/
279 04edfc99 Iustin Pop
-- tuple.
280 04edfc99 Iustin Pop
niceSortKey :: (a -> String) -> [a] -> [a]
281 04edfc99 Iustin Pop
niceSortKey keyfn =
282 04edfc99 Iustin Pop
  map snd . sortBy (compare `on` fst) .
283 04edfc99 Iustin Pop
  map (\s -> (fst . extractKey [] $ keyfn s, s))
284 256e28c4 Iustin Pop
285 256e28c4 Iustin Pop
-- | Strip space characthers (including newline). As this is
286 256e28c4 Iustin Pop
-- expensive, should only be run on small strings.
287 256e28c4 Iustin Pop
rStripSpace :: String -> String
288 256e28c4 Iustin Pop
rStripSpace = reverse . dropWhile isSpace . reverse
289 80a0546b Michele Tartara
290 80a0546b Michele Tartara
-- | Returns a random UUID.
291 80a0546b Michele Tartara
-- This is a Linux-specific method as it uses the /proc filesystem.
292 80a0546b Michele Tartara
newUUID :: IO String
293 80a0546b Michele Tartara
newUUID = do
294 80a0546b Michele Tartara
  contents <- readFile C.randomUuidFile
295 37dfcacb Iustin Pop
  return $! rStripSpace $ take 128 contents
296 b6aeda4a Dato Simó
297 a6e054a8 Iustin Pop
-- | Returns the current time as an 'Integer' representing the number
298 a6e054a8 Iustin Pop
-- of seconds from the Unix epoch.
299 ace37e24 Michele Tartara
getCurrentTime :: IO Integer
300 ace37e24 Michele Tartara
getCurrentTime = do
301 ace37e24 Michele Tartara
  TOD ctime _ <- getClockTime
302 ace37e24 Michele Tartara
  return ctime
303 ace37e24 Michele Tartara
304 a6e054a8 Iustin Pop
-- | Returns the current time as an 'Integer' representing the number
305 a6e054a8 Iustin Pop
-- of microseconds from the Unix epoch (hence the need for 'Integer').
306 a6e054a8 Iustin Pop
getCurrentTimeUSec :: IO Integer
307 a6e054a8 Iustin Pop
getCurrentTimeUSec = do
308 a6e054a8 Iustin Pop
  TOD ctime pico <- getClockTime
309 a6e054a8 Iustin Pop
  -- pico: 10^-12, micro: 10^-6, so we have to shift seconds left and
310 a6e054a8 Iustin Pop
  -- picoseconds right
311 a6e054a8 Iustin Pop
  return $ ctime * 1000000 + pico `div` 1000000
312 a6e054a8 Iustin Pop
313 b6aeda4a Dato Simó
-- | Convert a ClockTime into a (seconds-only) timestamp.
314 b6aeda4a Dato Simó
clockTimeToString :: ClockTime -> String
315 b6aeda4a Dato Simó
clockTimeToString (TOD t _) = show t
316 b009f682 Dato Simó
317 b009f682 Dato Simó
{-| Strip a prefix from a string, allowing the last character of the prefix
318 b009f682 Dato Simó
(which is assumed to be a separator) to be absent from the string if the string
319 b009f682 Dato Simó
terminates there.
320 b009f682 Dato Simó
321 b009f682 Dato Simó
>>> chompPrefix "foo:bar:" "a:b:c"
322 b009f682 Dato Simó
Nothing
323 b009f682 Dato Simó
324 b009f682 Dato Simó
>>> chompPrefix "foo:bar:" "foo:bar:baz"
325 b009f682 Dato Simó
Just "baz"
326 b009f682 Dato Simó
327 b009f682 Dato Simó
>>> chompPrefix "foo:bar:" "foo:bar:"
328 b009f682 Dato Simó
Just ""
329 b009f682 Dato Simó
330 b009f682 Dato Simó
>>> chompPrefix "foo:bar:" "foo:bar"
331 b009f682 Dato Simó
Just ""
332 b009f682 Dato Simó
333 b009f682 Dato Simó
>>> chompPrefix "foo:bar:" "foo:barbaz"
334 b009f682 Dato Simó
Nothing
335 b009f682 Dato Simó
-}
336 b009f682 Dato Simó
chompPrefix :: String -> String -> Maybe String
337 b009f682 Dato Simó
chompPrefix pfx str =
338 b009f682 Dato Simó
  if pfx `isPrefixOf` str || str == init pfx
339 b009f682 Dato Simó
    then Just $ drop (length pfx) str
340 b009f682 Dato Simó
    else Nothing
341 9fb621af Yiannis Tsiouris
342 9fb621af Yiannis Tsiouris
-- | Breaks a string in lines with length \<= maxWidth.
343 9fb621af Yiannis Tsiouris
--
344 9fb621af Yiannis Tsiouris
-- NOTE: The split is OK if:
345 9fb621af Yiannis Tsiouris
--
346 9fb621af Yiannis Tsiouris
-- * It doesn't break a word, i.e. the next line begins with space
347 9fb621af Yiannis Tsiouris
--   (@isSpace . head $ rest@) or the current line ends with space
348 9fb621af Yiannis Tsiouris
--   (@null revExtra@);
349 9fb621af Yiannis Tsiouris
--
350 9fb621af Yiannis Tsiouris
-- * It breaks a very big word that doesn't fit anyway (@null revLine@).
351 9fb621af Yiannis Tsiouris
wrap :: Int      -- ^ maxWidth
352 9fb621af Yiannis Tsiouris
     -> String   -- ^ string that needs wrapping
353 9fb621af Yiannis Tsiouris
     -> [String] -- ^ string \"broken\" in lines
354 9fb621af Yiannis Tsiouris
wrap maxWidth = filter (not . null) . map trim . wrap0
355 9fb621af Yiannis Tsiouris
  where wrap0 :: String -> [String]
356 9fb621af Yiannis Tsiouris
        wrap0 text
357 9fb621af Yiannis Tsiouris
          | length text <= maxWidth = [text]
358 9fb621af Yiannis Tsiouris
          | isSplitOK               = line : wrap0 rest
359 9fb621af Yiannis Tsiouris
          | otherwise               = line' : wrap0 rest'
360 9fb621af Yiannis Tsiouris
          where (line, rest) = splitAt maxWidth text
361 9fb621af Yiannis Tsiouris
                (revExtra, revLine) = break isSpace . reverse $ line
362 9fb621af Yiannis Tsiouris
                (line', rest') = (reverse revLine, reverse revExtra ++ rest)
363 9fb621af Yiannis Tsiouris
                isSplitOK =
364 9fb621af Yiannis Tsiouris
                  null revLine || null revExtra || startsWithSpace rest
365 9fb621af Yiannis Tsiouris
                startsWithSpace (x:_) = isSpace x
366 9fb621af Yiannis Tsiouris
                startsWithSpace _     = False
367 9fb621af Yiannis Tsiouris
368 9fb621af Yiannis Tsiouris
-- | Removes surrounding whitespace. Should only be used in small
369 9fb621af Yiannis Tsiouris
-- strings.
370 9fb621af Yiannis Tsiouris
trim :: String -> String
371 9fb621af Yiannis Tsiouris
trim = reverse . dropWhile isSpace . reverse . dropWhile isSpace