File: ParserSpec.hs

package info (click to toggle)
haskell-http-link-header 1.2.1-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 112 kB
  • sloc: haskell: 309; makefile: 8
file content (62 lines) | stat: -rw-r--r-- 2,858 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
{-# LANGUAGE OverloadedStrings, UnicodeSyntax #-}

module Network.HTTP.Link.ParserSpec where

import           Test.Hspec
import           Test.Hspec.Attoparsec
import           Data.Text
import           Data.Maybe (fromJust)
import           Network.HTTP.Link (lnk)
import           Network.HTTP.Link.Types
import           Network.HTTP.Link.Parser
import           Network.URI (URI)
import           Data.Attoparsec.Text (Parser)

spec ∷ Spec
spec = do
  describe "linkHeader" $ do
    let l u r = fromJust $ lnk u r

    it "parses a single link" $ do
      ("<http://example.com>; rel=\"example\"" ∷ Text) ~> linkHeaderURI
        `shouldParse` [ l "http://example.com" [(Rel, "example")] ]

    it "parses empty attributes" $ do
      ("<http://example.com>; title=\"\"" ∷ Text) ~> linkHeaderURI
        `shouldParse` [ l "http://example.com" [(Title, "")] ]

    it "parses custom attributes" $ do
      ("<http://example.com>; weirdThingy=\"something\"" ∷ Text) ~> linkHeaderURI
        `shouldParse` [ l "http://example.com" [(Other "weirdThingy", "something")] ]

    it "parses backslash escaped attributes" $ do
      ("<http://example.com>; title=\"some \\\" thing \\\"\"" ∷ Text) ~> linkHeaderURI
        `shouldParse` [ l "http://example.com" [(Title, "some \" thing \"")] ]

    it "parses escaped attributes" $ do
      ("<http://example.com>; title=\"some %22 thing %22\"" ∷ Text) ~> linkHeaderURI
        `shouldParse` [ l "http://example.com" [(Title, "some \" thing \"")] ]

    it "parses multiple attributes" $ do
      ("<http://example.com>; rel=\"example\"; title=\"example dot com\"" ∷ Text) ~> linkHeaderURI
        `shouldParse` [ l "http://example.com" [(Rel, "example"), (Title, "example dot com")] ]

    it "parses custom attributes named similarly to standard ones" $ do
      -- this was caught by QuickCheck! <3
      ("<http://example.com>; rel=hello; relAtion=\"something\"; rev=next" ∷ Text) ~> linkHeaderURI
        `shouldParse` [ l "http://example.com" [(Rel, "hello"), (Other "relAtion", "something"), (Rev, "next")] ]

    it "parses unquoted rel, rev attributes" $ do
      ("<http://example.com>; rel=next; rev=prev" ∷ Text) ~> linkHeaderURI
        `shouldParse` [ l "http://example.com" [(Rel, "next"), (Rev, "prev")] ]

    it "does not blow up on title*" $ do
      ("<http://example.com>; title*=UTF-8'de'n%c3%a4chstes%20Kapitel" ∷ Text) ~> linkHeaderURI
        `shouldParse` [ l "http://example.com" [(Title', "UTF-8'de'n%c3%a4chstes%20Kapitel")] ]

    it "parses weird whitespace all over the place" $ do
      ("\n\t   < http://example.com\t>;rel=\t\"example\";   \ttitle =\"example dot com\" \n " ∷ Text) ~> linkHeaderURI
        `shouldParse` [ l "http://example.com" [(Rel, "example"), (Title, "example dot com")] ]

  where
    linkHeaderURI = linkHeader :: Parser [Link URI]