File: UtilSpec.hs

package info (click to toggle)
haskell-libmpd 0.10.0.1-1
  • links: PTS
  • area: main
  • in suites: sid, trixie
  • size: 332 kB
  • sloc: haskell: 2,776; makefile: 6
file content (98 lines) | stat: -rw-r--r-- 2,965 bytes parent folder | download | duplicates (4)
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
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
{-# LANGUAGE OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-type-defaults #-}

module UtilSpec (main, spec) where

import           Arbitrary
import           TestUtil

import           Test.Hspec.QuickCheck (prop)
import           Test.QuickCheck

import           Data.List (sort)
import           Data.Maybe (fromJust, isJust)
import           Data.ByteString.Char8 (ByteString)
import qualified Data.ByteString.UTF8 as UTF8

import           Network.MPD.Util

main :: IO ()
main = hspec spec

spec :: Spec
spec = do
    describe "splitGroups" $ do
        it "breaks an association list into sublists" $ do
            splitGroups ["1", "5"]
                        [("1","a"),("2","b"),
                         ("5","c"),("6","d"),
                         ("1","z"),("2","y"),("3","x")]
            `shouldBe`
            [[("1","a"),("2","b")],
             [("5","c"),("6","d")],
             [("1","z"),("2","y"),("3","x")]]
        prop "is reversible" prop_splitGroups_rev
        prop "preserves input" prop_splitGroups_integrity

    describe "parseDate" $ do
        prop "simple year strings" prop_parseDate_simple
        prop "complex year strings" prop_parseDate_complex

    describe "toAssoc" $ do
        prop "is reversible" prop_toAssoc_rev

    describe "parseBool" $ do
        prop "parses boolean values" prop_parseBool
        prop "is reversible" prop_parseBool_rev

    describe "showBool" $ do
        prop "unparses boolean values" prop_showBool

    describe "parseNum" $ do
        prop "parses positive and negative integers" prop_parseNum


prop_parseDate_simple :: YearString -> Bool
prop_parseDate_simple (YS x) = isJust $ parseDate x

prop_parseDate_complex :: DateString -> Bool
prop_parseDate_complex (DS x) = isJust $ parseDate x

prop_toAssoc_rev :: AssocString -> Bool
prop_toAssoc_rev x = k == k' && v == v'
    where
        AS str k v = x
        (k',v') = toAssoc str

prop_parseBool_rev :: BoolString -> Bool
prop_parseBool_rev (BS x) = showBool (fromJust $ parseBool x) == x

prop_parseBool :: BoolString -> Bool
prop_parseBool (BS xs) =
    case parseBool xs of
        Nothing    -> False
        Just True  -> xs == "1"
        Just False -> xs == "0"

prop_showBool :: Bool -> Bool
prop_showBool True = showBool True == "1"
prop_showBool x    = showBool x == "0"

prop_splitGroups_rev :: [(ByteString, ByteString)] -> Property
prop_splitGroups_rev xs = not (null xs) ==>
    let wrappers = [fst $ head xs]
        r = splitGroups wrappers xs
    in r == splitGroups wrappers (concat r)

prop_splitGroups_integrity :: [(ByteString, ByteString)] -> Property
prop_splitGroups_integrity xs = not (null xs) ==>
    sort (concat $ splitGroups [fst $ head xs] xs) == sort xs

prop_parseNum :: Integer -> Bool
prop_parseNum x =
    case xs of
        '-':_ -> ((<= 0) `fmap` parseNum bs) == Just True
        _     -> ((>= 0) `fmap` parseNum bs) == Just True
    where
      xs = show x
      bs = UTF8.fromString xs