]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/Request.hs
Destroy Data.Attoparsec.Parsable; use Data.Default instead
[Lucu.git] / Network / HTTP / Lucu / Request.hs
index d23dc6331790455b347f26f03371126ed069ee30..13ccf9c9420b8265fa244934ed2d98cebc1a497f 100644 (file)
@@ -1,5 +1,8 @@
 {-# LANGUAGE
-    OverloadedStrings
+    FlexibleInstances
+  , MultiParamTypeClasses
+  , OverloadedStrings
+  , TypeSynonymInstances
   , UnicodeSyntax
   , ViewPatterns
   #-}
@@ -10,7 +13,6 @@ module Network.HTTP.Lucu.Request
     ( Method(..)
     , Request(..)
     , reqHasBody
-    , requestP
     )
     where
 import Control.Applicative
@@ -18,6 +20,7 @@ import Control.Monad.Unicode
 import Data.Ascii (Ascii)
 import Data.Attoparsec.Char8
 import qualified Data.ByteString.Char8 as C8
+import Data.Default
 import Network.HTTP.Lucu.Headers
 import Network.HTTP.Lucu.HttpVersion
 import Network.HTTP.Lucu.Parser.Http
@@ -25,7 +28,7 @@ import Network.URI
 import Prelude.Unicode
 
 -- |This is the definition of HTTP request methods, which shouldn't
--- require any description.
+-- require any descriptions.
 data Method = OPTIONS
             | GET
             | HEAD
@@ -37,7 +40,7 @@ data Method = OPTIONS
             | ExtensionMethod !Ascii
               deriving (Eq, Show)
 
--- |This is the definition of HTTP reqest.
+-- |This is the definition of an HTTP reqest.
 data Request
     = Request {
         reqMethod  ∷ !Method
@@ -48,50 +51,59 @@ data Request
     deriving (Eq, Show)
 
 instance HasHeaders Request where
+    {-# INLINE getHeaders #-}
     getHeaders = reqHeaders
+    {-# INLINE setHeaders #-}
     setHeaders req hdr = req { reqHeaders = hdr }
 
--- |Returns 'True' iff the 'Request' must have an entity body.
+-- |Returns 'True' iff the 'Request' would have an entity body.
 reqHasBody ∷ Request → Bool
+{-# INLINEABLE reqHasBody #-}
 reqHasBody (reqMethod → m)
-    = m ≡ POST ∨ m ≡ PUT
+    | m ≡ POST  = True
+    | m ≡ PUT   = True
+    | otherwise = False
 
-requestP ∷ Parser Request
-requestP = do skipMany crlf
-              (method, uri, version) ← requestLineP
-              headers                ← headersP
-              return Request {
-                           reqMethod  = method
-                         , reqURI     = uri
-                         , reqVersion = version
-                         , reqHeaders = headers
-                         }
+instance Default (Parser Request) where
+    {-# INLINEABLE def #-}
+    def = do skipMany crlf
+             (meth, u, ver) ← requestLine
+             hdrs           ← def
+             return Request {
+                          reqMethod  = meth
+                        , reqURI     = u
+                        , reqVersion = ver
+                        , reqHeaders = hdrs
+                        }
 
-requestLineP ∷ Parser (Method, URI, HttpVersion)
-requestLineP = do method ← methodP
-                  sp
-                  uri    ← uriP
-                  sp
-                  ver    ← httpVersionP
-                  crlf
-                  return (method, uri, ver)
+requestLine ∷ Parser (Method, URI, HttpVersion)
+{-# INLINEABLE requestLine #-}
+requestLine = do meth ← method
+                 sp
+                 u ← uri
+                 sp
+                 ver ← def
+                 crlf
+                 return (meth, u, ver)
 
-methodP ∷ Parser Method
-methodP = choice
-          [ string "OPTIONS" ≫ return OPTIONS
-          , string "GET"     ≫ return GET
-          , string "HEAD"    ≫ return HEAD
-          , string "POST"    ≫ return POST
-          , string "PUT"     ≫ return PUT
-          , string "DELETE"  ≫ return DELETE
-          , string "TRACE"   ≫ return TRACE
-          , string "CONNECT" ≫ return CONNECT
-          , ExtensionMethod <$> token
-          ]
+method ∷ Parser Method
+{-# INLINEABLE method #-}
+method = choice
+         [ string "OPTIONS" ≫ return OPTIONS
+         , string "GET"     ≫ return GET
+         , string "HEAD"    ≫ return HEAD
+         , string "POST"    ≫ return POST
+         , string "PUT"     ≫ return PUT
+         , string "DELETE"  ≫ return DELETE
+         , string "TRACE"   ≫ return TRACE
+         , string "CONNECT" ≫ return CONNECT
+         , ExtensionMethod <$> token
+         ]
 
-uriP ∷ Parser URI
-uriP = do bs ← takeWhile1 (\c → (¬) (isCtl c ∨ c ≡ '\x20'))
-          let str = C8.unpack bs
-          case parseURIReference str of
-            Nothing  -> fail ("Unparsable URI: " ⧺ str)
-            Just uri -> return uri
+uri ∷ Parser URI
+{-# INLINEABLE uri #-}
+uri = do bs ← takeWhile1 (\c → (¬) (isCtl c ∨ c ≡ '\x20'))
+         let str = C8.unpack bs
+         case parseURIReference str of
+           Nothing → fail ("Unparsable URI: " ⧺ str)
+           Just u  → return u