File: Zepto.hs

package info (click to toggle)
haskell-scanner 0.3.1-4
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 168 kB
  • sloc: haskell: 810; makefile: 5
file content (73 lines) | stat: -rw-r--r-- 1,509 bytes parent folder | download | duplicates (3)
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
{-# LANGUAGE OverloadedStrings #-}

module Redis.Zepto
( reply
)
where

import Redis.Reply

import Prelude hiding (error)
import Data.ByteString (ByteString)
import Data.Attoparsec.Zepto (Parser)
import qualified Data.Attoparsec.Zepto as Zepto
import qualified Data.Text.Encoding as Text
import qualified Data.Text.Read as Text
import Control.Monad

{-# INLINE reply #-}
reply :: Parser Reply
reply = do
  c <- Zepto.take 1
  case c of
    "+" -> string
    "-" -> error
    ":" -> integer
    "$" -> bulk
    "*" -> multi
    _ -> fail "Unknown reply type"

{-# INLINE string #-}
string :: Parser Reply
string = String <$> line

{-# INLINE error #-}
error :: Parser Reply
error = Error <$> line

{-# INLINE integer #-}
integer :: Parser Reply
integer = Integer <$> integral

{-# INLINE integral #-}
integral :: Integral i => Parser i
integral = do
  str <- line
  case Text.signed Text.decimal (Text.decodeUtf8 str) of
    Left err -> fail (show err)
    Right (l, _) -> return l

{-# INLINE bulk #-}
bulk :: Parser Reply
bulk = Bulk <$> do
  len <- integral
  if len < 0
    then return Nothing
    else Just <$> Zepto.take len <* eol

-- don't inline it to break the circle between reply and multi
{-# NOINLINE multi #-}
multi :: Parser Reply
multi = Multi <$> do
  len <- integral
  if len < 0
    then return Nothing
    else Just <$> replicateM len reply

{-# INLINE line #-}
line :: Parser ByteString
line = Zepto.takeWhile (/= 13) <* eol

{-# INLINE eol #-}
eol :: Parser ()
eol = Zepto.string "\r\n"