]> gitweb @ CieloNegro.org - Lucu.git/blob - Network/HTTP/Lucu/ETag.hs
f7ef8387c7044d02acc1451a7fa0e140c3197c60
[Lucu.git] / Network / HTTP / Lucu / ETag.hs
1 {-# LANGUAGE
2     OverloadedStrings
3   , UnicodeSyntax
4   #-}
5 -- |Manipulation of entity tags.
6 module Network.HTTP.Lucu.ETag
7     ( ETag(..)
8     , parseETag
9     , printETag
10
11     , strongETag
12     , weakETag
13     , eTagP
14     , eTagListP
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 is made of a weakness flag and a opaque string.
28 data ETag = ETag {
29       -- |The weakness flag. Weak tags looks like W\/\"blahblah\" and
30       -- strong tags are like \"blahblah\".
31       etagIsWeak ∷ !Bool
32       -- |An opaque string. Only characters from 0x20 (sp) to 0x7e (~)
33       -- are allowed.
34     , etagToken  ∷ !Ascii
35     } deriving (Eq, Show)
36
37 -- |Convert an 'ETag' to 'AsciiBuilder'.
38 printETag ∷ ETag → AsciiBuilder
39 {-# INLINEABLE printETag #-}
40 printETag et
41     = ( if etagIsWeak et then
42             A.toAsciiBuilder "W/"
43         else
44             (∅)
45       )
46       ⊕
47       quoteStr (etagToken et)
48
49 -- |Parse 'Etag' from an 'Ascii'. This functions throws an exception
50 -- for parse error.
51 parseETag ∷ Ascii → ETag
52 {-# INLINEABLE parseETag #-}
53 parseETag str
54     = case parseOnly p $ A.toByteString str of
55         Right et → et
56         Left err → error ("unparsable ETag: " ⧺ A.toString str ⧺ ": " ⧺ err)
57     where
58       p ∷ Parser ETag
59       {-# INLINE p #-}
60       p = do et ← eTagP
61              endOfInput
62              return et
63
64 -- |This is equivalent to @'ETag' 'Prelude.False'@. If you want to
65 -- generate an ETag from a file, try using
66 -- 'Network.HTTP.Lucu.StaticFile.generateETagFromFile'.
67 strongETag ∷ Ascii → ETag
68 {-# INLINE strongETag #-}
69 strongETag = ETag False
70
71 -- |This is equivalent to @'ETag' 'Prelude.True'@.
72 weakETag ∷ Ascii → ETag
73 {-# INLINE weakETag #-}
74 weakETag = ETag True
75
76 eTagP ∷ Parser ETag
77 {-# INLINEABLE eTagP #-}
78 eTagP = do isWeak ← option False (string "W/" *> return True)
79            str    ← quotedStr
80            return $ ETag isWeak str
81
82 eTagListP ∷ Parser [ETag]
83 {-# INLINEABLE eTagListP #-}
84 eTagListP = do xs ← listOf eTagP
85                when (null xs) $
86                    fail "empty list of ETags"
87                return xs