File: ParserSpec.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 (63 lines) | stat: -rw-r--r-- 2,177 bytes parent folder | download | duplicates (2)
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
{-# LANGUAGE StandaloneDeriving, OverloadedStrings #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

module ParserSpec (main, spec) where

import           Arbitrary ()
import           Unparse

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

import           Network.MPD.Commands.Parse
import           Network.MPD.Commands.Types
import           Network.MPD.Util hiding (read)

import qualified Data.ByteString.UTF8 as UTF8
import           Data.List
import qualified Data.Map as M
import           Data.Time

main :: IO ()
main = hspec spec

spec :: Spec
spec = do
    describe "parseIso8601" $ do
        prop "parses dates in ISO8601 format" prop_parseIso8601

    describe "parseCount" $ do
        prop "parses counts" prop_parseCount

    describe "parseOutputs" $ do
        prop "parses outputs" prop_parseOutputs

    describe "parseSong" $ do
        prop "parses songs" prop_parseSong

    describe "parseStats" $ do
        prop "parses stats" prop_parseStats

-- This property also ensures, that (instance Arbitrary UTCTime) is sound.
-- Indeed, a bug in the instance declaration was the primary motivation to add
-- this property.
prop_parseIso8601 :: UTCTime -> Expectation
prop_parseIso8601 t = Just t `shouldBe` (parseIso8601 . UTF8.fromString . formatIso8601) t

prop_parseCount :: Count -> Expectation
prop_parseCount c = Right c `shouldBe` (parseCount . map UTF8.fromString . lines . unparse) c

prop_parseOutputs :: [Device] -> Expectation
prop_parseOutputs ds =
    Right ds `shouldBe` (parseOutputs . map UTF8.fromString . lines . concatMap unparse) ds

prop_parseSong :: Song -> Expectation
prop_parseSong s = Right (sortTags s) `shouldBe` sortTags `fmap` (parseSong . toAssocList . map UTF8.fromString . lines . unparse) s
  where
    -- We consider lists of tag values equal if they contain the same elements.
    -- To ensure that two lists with the same elements are equal, we bring the
    -- elements in a deterministic order.
    sortTags song = song { sgTags = M.map sort $ sgTags song }

prop_parseStats :: Stats -> Expectation
prop_parseStats s = Right s `shouldBe` (parseStats . map UTF8.fromString . lines . unparse) s