File: Main.hs

package info (click to toggle)
haskell-vector-builder 0.3.8.5-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 88 kB
  • sloc: haskell: 364; makefile: 6
file content (58 lines) | stat: -rw-r--r-- 2,152 bytes parent folder | download
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
module Main where

import qualified Data.Attoparsec.Text as D
import qualified Data.Text as G
import qualified Data.Vector as E
import qualified Main.Sample as C
import Test.Tasty
import Test.Tasty.HUnit
import Test.Tasty.QuickCheck
import qualified VectorBuilder.Alternative as F
import qualified VectorBuilder.Builder as A
import qualified VectorBuilder.MonadPlus as H
import qualified VectorBuilder.Vector as B
import Prelude

main :: IO ()
main =
  defaultMain
    $ testGroup
      "All tests"
      [ testProperty "samples" $ \(samples :: [C.Sample Int]) ->
          foldMap C.toVector samples
            === B.build (foldMap C.toBuilder samples),
        testCase "Alternative.some"
          $ assertEqual
            ""
            (Right (E.fromList "1234"))
            (D.parseOnly (F.some D.anyChar) "1234"),
        testCase "Alternative.some on empty"
          $ assertEqual
            ""
            (Left "not enough input")
            (D.parseOnly (F.some D.anyChar :: D.Parser (Vector Char)) ""),
        testProperty "mconcat" $ \(samples :: [C.Sample Int]) ->
          foldMap C.toVector samples
            === B.build (mconcat (map C.toBuilder samples)),
        testProperty "foldable" $ \(elements :: [Int]) ->
          E.fromList elements
            === B.build (A.foldable elements),
        testGroup
          "MonadPlus"
          [ testProperty "many" $ \(elements :: [Char]) ->
              Right (E.fromList elements)
                === D.parseOnly (H.many D.anyChar) (fromString elements),
            testProperty "many1" $ \(elements :: [Char]) ->
              ( if null elements
                  then Left "not enough input"
                  else Right (E.fromList elements)
              )
                === D.parseOnly (H.many1 D.anyChar) (fromString elements),
            testProperty "sepBy1" $ \(elements :: [Char]) ->
              ( if null elements
                  then Left "not enough input"
                  else Right (E.fromList elements)
              )
                === D.parseOnly (H.sepBy1 D.anyChar (D.char ',')) (G.intersperse ',' (fromString elements))
          ]
      ]