]> gitweb @ CieloNegro.org - Lucu.git/blob - Network/HTTP/Lucu/ETag.hs
76df18378bf3e48417dddd8c73dc6222b65d5136
[Lucu.git] / Network / HTTP / Lucu / ETag.hs
1 {-# LANGUAGE
2     OverloadedStrings
3   , UnicodeSyntax
4   #-}
5 -- |Entity tags
6 module Network.HTTP.Lucu.ETag
7     ( ETag(..)
8     , parseETag
9     , printETag
10
11     , strongETag
12     , weakETag
13     , eTag
14     , eTagList
15     )
16     where
17 import Control.Applicative
18 import Control.Monad
19 import Data.Ascii (Ascii, AsciiBuilder)
20 import qualified Data.Ascii as A
21 import Data.Attoparsec.Char8
22 import Data.Monoid.Unicode
23 import Network.HTTP.Lucu.Parser.Http hiding (token)
24 import Network.HTTP.Lucu.Utils
25 import Prelude.Unicode
26
27 -- |An entity tag consists of a weakness flag and an opaque string.
28 data ETag = ETag {
29       -- |The weakness flag. Weak tags looks like W\/\"blahblah\" and
30       -- strong tags are like \"blahblah\". See:
31       -- <http://www.w3.org/Protocols/rfc2616/rfc2616-sec13.html#sec13.3.3>
32       etagIsWeak ∷ !Bool
33       -- |An opaque string. Only characters from 0x20 (sp) to 0x7e (~)
34       -- are allowed.
35     , etagToken  ∷ !Ascii
36     } deriving (Eq, Show)
37
38 -- |Convert an 'ETag' to an 'AsciiBuilder'.
39 printETag ∷ ETag → AsciiBuilder
40 {-# INLINEABLE printETag #-}
41 printETag et
42     = ( if etagIsWeak et then
43             A.toAsciiBuilder "W/"
44         else
45             (∅)
46       )
47       ⊕
48       quoteStr (etagToken et)
49
50 -- |Parse 'Etag' from an 'Ascii'. This functions throws an exception
51 -- for parse error.
52 parseETag ∷ Ascii → ETag
53 {-# INLINEABLE parseETag #-}
54 parseETag str
55     = case parseOnly p $ A.toByteString str of
56         Right et → et
57         Left err → error ("unparsable ETag: " ⧺ A.toString str ⧺ ": " ⧺ err)
58     where
59       p ∷ Parser ETag
60       {-# INLINE p #-}
61       p = do et ← eTag
62              endOfInput
63              return et
64
65 -- |This is equivalent to @'ETag' 'False'@. If you want to generate an
66 -- ETag from a file, try using
67 -- 'Network.HTTP.Lucu.StaticFile.generateETagFromFile'.
68 strongETag ∷ Ascii → ETag
69 {-# INLINE strongETag #-}
70 strongETag = ETag False
71
72 -- |This is equivalent to @'ETag' 'True'@.
73 weakETag ∷ Ascii → ETag
74 {-# INLINE weakETag #-}
75 weakETag = ETag True
76
77 -- |'Parser' for an 'ETag'.
78 eTag ∷ Parser ETag
79 {-# INLINEABLE eTag #-}
80 eTag = do isWeak ← option False (string "W/" *> return True)
81           str    ← quotedStr
82           return $ ETag isWeak str
83
84 -- |'Parser' for a list of 'ETag's.
85 eTagList ∷ Parser [ETag]
86 {-# INLINEABLE eTagList #-}
87 eTagList = do xs ← listOf eTag
88               when (null xs) $
89                   fail "empty list of ETags"
90               return xs