X-Git-Url: http://git.cielonegro.org/gitweb.cgi?p=Lucu.git;a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FRequest.hs;h=13ccf9c9420b8265fa244934ed2d98cebc1a497f;hp=66511e24c1f869490469ea637e0ea763ffd1ec34;hb=90fca0675b1694e69b8e431c989343855cbd125d;hpb=72a3e24a952616e32845eeb4fc05048e841c91a2 diff --git a/Network/HTTP/Lucu/Request.hs b/Network/HTTP/Lucu/Request.hs index 66511e2..13ccf9c 100644 --- a/Network/HTTP/Lucu/Request.hs +++ b/Network/HTTP/Lucu/Request.hs @@ -1,5 +1,8 @@ {-# LANGUAGE - OverloadedStrings + FlexibleInstances + , MultiParamTypeClasses + , OverloadedStrings + , TypeSynonymInstances , UnicodeSyntax , ViewPatterns #-} @@ -9,8 +12,7 @@ module Network.HTTP.Lucu.Request ( Method(..) , Request(..) - , reqMustHaveBody - , requestP + , reqHasBody ) 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 @@ -53,50 +56,54 @@ instance HasHeaders Request where {-# INLINE setHeaders #-} setHeaders req hdr = req { reqHeaders = hdr } --- |Returns 'True' iff the 'Request' must have an entity body. -reqMustHaveBody ∷ Request → Bool -{-# INLINEABLE reqMustHaveBody #-} -reqMustHaveBody (reqMethod → m) +-- |Returns 'True' iff the 'Request' would have an entity body. +reqHasBody ∷ Request → Bool +{-# INLINEABLE reqHasBody #-} +reqHasBody (reqMethod → m) | 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