Statistics
| Branch: | Tag: | Revision:

root / htest / Test / Ganeti / Attoparsec.hs @ da1dcce1

History | View | Annotate | Download (2 kB)

1 43b3b5c1 Michele Tartara
{-# LANGUAGE TemplateHaskell #-}
2 43b3b5c1 Michele Tartara
3 43b3b5c1 Michele Tartara
{-| Unittests for Attoparsec support for unicode -}
4 43b3b5c1 Michele Tartara
5 43b3b5c1 Michele Tartara
{-
6 43b3b5c1 Michele Tartara
7 43b3b5c1 Michele Tartara
Copyright (C) 2012 Google Inc.
8 43b3b5c1 Michele Tartara
9 43b3b5c1 Michele Tartara
This program is free software; you can redistribute it and/or modify
10 43b3b5c1 Michele Tartara
it under the terms of the GNU General Public License as published by
11 43b3b5c1 Michele Tartara
the Free Software Foundation; either version 2 of the License, or
12 43b3b5c1 Michele Tartara
(at your option) any later version.
13 43b3b5c1 Michele Tartara
14 43b3b5c1 Michele Tartara
This program is distributed in the hope that it will be useful, but
15 43b3b5c1 Michele Tartara
WITHOUT ANY WARRANTY; without even the implied warranty of
16 43b3b5c1 Michele Tartara
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
17 43b3b5c1 Michele Tartara
General Public License for more details.
18 43b3b5c1 Michele Tartara
19 43b3b5c1 Michele Tartara
You should have received a copy of the GNU General Public License
20 43b3b5c1 Michele Tartara
along with this program; if not, write to the Free Software
21 43b3b5c1 Michele Tartara
Foundation, Inc., 51 Franklin Street, Fifth Floor, Boston, MA
22 43b3b5c1 Michele Tartara
02110-1301, USA.
23 43b3b5c1 Michele Tartara
24 43b3b5c1 Michele Tartara
-}
25 43b3b5c1 Michele Tartara
26 43b3b5c1 Michele Tartara
module Test.Ganeti.Attoparsec (testAttoparsec) where
27 43b3b5c1 Michele Tartara
28 61899e64 Iustin Pop
import Test.HUnit
29 43b3b5c1 Michele Tartara
30 43b3b5c1 Michele Tartara
import Test.Ganeti.TestHelper
31 43b3b5c1 Michele Tartara
32 43b3b5c1 Michele Tartara
import qualified Data.Attoparsec.Text as A
33 43b3b5c1 Michele Tartara
import Data.Attoparsec.Text (Parser)
34 43b3b5c1 Michele Tartara
import Data.Text (pack, unpack)
35 43b3b5c1 Michele Tartara
36 43b3b5c1 Michele Tartara
-- | Unicode test string, first part.
37 43b3b5c1 Michele Tartara
part1 :: String
38 43b3b5c1 Michele Tartara
part1 = "äßĉ"
39 43b3b5c1 Michele Tartara
40 43b3b5c1 Michele Tartara
-- | Unicode test string, second part.
41 43b3b5c1 Michele Tartara
part2 :: String
42 43b3b5c1 Michele Tartara
part2 = "ðèق"
43 43b3b5c1 Michele Tartara
44 43b3b5c1 Michele Tartara
-- | Simple parser able to split a string in two parts, name and
45 43b3b5c1 Michele Tartara
-- value, separated by a '=' sign.
46 43b3b5c1 Michele Tartara
simpleParser :: Parser (String, String)
47 43b3b5c1 Michele Tartara
simpleParser = do
48 43b3b5c1 Michele Tartara
  n <- A.takeTill (\c -> A.isHorizontalSpace c || c == '=')
49 43b3b5c1 Michele Tartara
  A.skipWhile A.isHorizontalSpace
50 43b3b5c1 Michele Tartara
  _ <- A.char '='
51 43b3b5c1 Michele Tartara
  A.skipWhile A.isHorizontalSpace
52 43b3b5c1 Michele Tartara
  v <- A.takeTill A.isEndOfLine
53 43b3b5c1 Michele Tartara
  return (unpack n, unpack v)
54 43b3b5c1 Michele Tartara
55 469a1490 Iustin Pop
{-# ANN case_unicodeParsing "HLint: ignore Use camelCase" #-}
56 43b3b5c1 Michele Tartara
-- | Tests whether a Unicode string is still Unicode after being
57 43b3b5c1 Michele Tartara
-- parsed.
58 61899e64 Iustin Pop
case_unicodeParsing :: Assertion
59 61899e64 Iustin Pop
case_unicodeParsing =
60 61899e64 Iustin Pop
  case A.parseOnly simpleParser text of
61 61899e64 Iustin Pop
    Right (name, value) -> do
62 61899e64 Iustin Pop
      assertEqual "name part" part1 name
63 61899e64 Iustin Pop
      assertEqual "value part" part2 value
64 61899e64 Iustin Pop
    Left msg -> assertFailure $ "Failed to parse: " ++ msg
65 43b3b5c1 Michele Tartara
  where text = Data.Text.pack $ part1 ++ "  = \t" ++ part2
66 43b3b5c1 Michele Tartara
67 43b3b5c1 Michele Tartara
testSuite "Attoparsec"
68 61899e64 Iustin Pop
          [ 'case_unicodeParsing
69 43b3b5c1 Michele Tartara
          ]