File: spec.hs

package info (click to toggle)
haskell-scanner 0.3.1-5
  • links: PTS, VCS
  • area: main
  • in suites: sid
  • size: 164 kB
  • sloc: haskell: 810; makefile: 3
file content (146 lines) | stat: -rw-r--r-- 4,082 bytes parent folder | download | duplicates (6)
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
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
{-# LANGUAGE OverloadedStrings #-}

module Main
( main
)
where

import Scanner

import Prelude hiding (take, takeWhile)
import Data.Either
import qualified Data.ByteString as ByteString
import qualified Data.ByteString.Lazy as Lazy.ByteString
import Test.Hspec

main :: IO ()
main = hspec $ do
  anyWord8Spec
  stringSpec
  takeSpec
  takeWhileSpec
  lookAheadSpec
  scanWithSpec

anyWord8Spec :: Spec
anyWord8Spec = describe "anyWord8" $ do
  it "should return the current byte" $ do
    let bs = ByteString.pack [42, 43]
    scanOnly anyWord8 bs `shouldBe` Right 42

  it "should consume the current byte" $ do
    let bs = ByteString.pack [42, 43]
    scanOnly (anyWord8 *> anyWord8) bs `shouldBe` Right 43

    let bs' = Lazy.ByteString.fromChunks
          [ ByteString.pack [42]
          , ByteString.pack [43]
          , ByteString.pack [44]
          ]
    scanLazy (anyWord8 *> anyWord8 *> anyWord8) bs' `shouldBe` Right 44

  it "should ask for more input" $ do
    let bs = Lazy.ByteString.fromChunks
          [ ByteString.pack [42]
          , ByteString.pack [43]
          ]
    scanLazy (anyWord8 *> anyWord8) bs `shouldBe` Right 43

  it "should fail on end of input" $ do
    let bs = ByteString.empty
    scanOnly anyWord8 bs `shouldSatisfy` isLeft

stringSpec :: Spec
stringSpec = describe "string" $ do
  it "should consume the string" $ do
    let bs = "hello world"
    scanOnly (string "hello" *> anyWord8) bs `shouldBe` Right 32

  it "should ask for more input" $ do
    let bs = Lazy.ByteString.fromChunks
          [ "hel"
          , "lo"
          ]
    scanLazy (string "hello") bs `shouldBe` Right ()

  it "should fail on wrong input" $ do
    let bs = "helo world"
    scanOnly (string "hello") bs `shouldSatisfy` isLeft

takeSpec :: Spec
takeSpec = describe "take" $ do
  it "should return the first n bytes" $ do
    let bs = "hello world"
    scanOnly (take 5) bs `shouldBe` Right "hello"

  it "should ask for more input" $ do
    let bs = Lazy.ByteString.fromChunks
          [ "he"
          , "l"
          , "lo world"
          ]
    scanLazy (take 5) bs `shouldBe` Right "hello"

  it "should fail on end of input" $ do
    let bs = "hell"
    scanOnly (take 5) bs `shouldSatisfy` isLeft

    let bs' = Lazy.ByteString.fromChunks
          [ "he"
          , "l"
          , "l"
          ]
    scanLazy (take 5) bs' `shouldSatisfy` isLeft

takeWhileSpec :: Spec
takeWhileSpec = describe "takeWhile" $ do
  it "should return bytes according to the predicate" $ do
    let bs = "hello world"
    scanOnly (takeWhile (/= 32)) bs `shouldBe` Right "hello"

  it "should ask for more input" $ do
    let bs = Lazy.ByteString.fromChunks
          [ "he"
          , "l"
          , "lo world"
          ]
    scanLazy (takeWhile (/= 32)) bs `shouldBe` Right "hello"

  it "should return everything is predicate where becomes False" $ do
    let bs = "hello"
    scanOnly (takeWhile (/= 32)) bs `shouldBe` Right "hello"

lookAheadSpec :: Spec
lookAheadSpec = describe "lookAhead" $ do
  it "should return the next byte" $ do
    let bs = ByteString.pack [42, 43]
    scanOnly lookAhead bs `shouldBe` Right (Just 42)

  it "should return Nothing on end of input" $ do
    let bs = ByteString.empty
    scanOnly lookAhead bs `shouldBe` Right Nothing

  it "should not consume input" $ do
    let bs = ByteString.pack [42, 43]
    scanOnly (lookAhead *> anyWord8) bs `shouldBe` Right 42

  it "should ask for more input" $ do
    let bs = Lazy.ByteString.fromChunks
          [ ByteString.pack [42]
          , ByteString.pack [43]
          ]
    scanLazy (anyWord8 *> lookAhead) bs `shouldBe` Right (Just 43)

scanWithSpec :: Spec
scanWithSpec = describe "scanWith" $ do
  it "should apply the scanner" $ do
    let bs = ByteString.pack [42, 43]
    let Just (Scanner.Done _ r) = scanWith (Just ByteString.empty) anyWord8 bs
    r `shouldBe` 42

  it "should resupply scanner when necessary" $ do
    let bs = "a"
        p = Scanner.anyChar8 *> Scanner.anyChar8

    let Just (Scanner.Done _ r) = scanWith (Just "b") p bs
    r `shouldBe` 'b'