X-Git-Url: http://git.cielonegro.org/gitweb.cgi?p=Lucu.git;a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FUtils.hs;h=d36c81b2853cb7e01adf861bed59e344b4181f7c;hp=1070d66f28042193a0337b02f1e9d858d63c9403;hb=667baf9f664ccc093241287ad727b2839290f456;hpb=b22e702f8161447a460847c6e6c97104c150534f diff --git a/Network/HTTP/Lucu/Utils.hs b/Network/HTTP/Lucu/Utils.hs index 1070d66..d36c81b 100644 --- a/Network/HTTP/Lucu/Utils.hs +++ b/Network/HTTP/Lucu/Utils.hs @@ -5,9 +5,16 @@ #-} -- |Utility functions used internally in this package. module Network.HTTP.Lucu.Utils - ( splitBy + ( Scheme + , Host + , PathSegment + , PathSegments + + , splitBy , quoteStr , parseWWWFormURLEncoded + , uriCIScheme + , uriHost , uriPathSegments , trim @@ -21,15 +28,20 @@ module Network.HTTP.Lucu.Utils where import Control.Applicative hiding (empty) import Control.Monad hiding (mapM) -import Data.Ascii (Ascii, AsciiBuilder) +import Data.Ascii (Ascii, AsciiBuilder, CIAscii) import qualified Data.Ascii as A import Data.ByteString (ByteString) -import qualified Data.ByteString.Char8 as Strict +import qualified Data.ByteString.Char8 as BS +import Data.CaseInsensitive (CI) +import qualified Data.CaseInsensitive as CI import Data.Char import Data.Collections import Data.Collections.BaseInstances () +import Data.Maybe import Data.Monoid.Unicode import Data.Ratio +import Data.Text (Text) +import qualified Data.Text as T import Data.Time import Data.Time.Clock.POSIX import Network.URI @@ -38,6 +50,20 @@ import Prelude.Unicode import System.Directory import System.Time (ClockTime(..)) +-- |'Scheme' represents an URI scheme. +type Scheme = CIAscii + +-- |'Host' represents an IP address or a host name in an URI +-- authority. +type Host = CI Text + +-- |'PathSegment' represents an URI path segment, split by slashes and +-- percent-decoded. +type PathSegment = ByteString + +-- |'PathSegments' is a list of URI path segments. +type PathSegments = [PathSegment] + -- |>>> splitBy (== ':') "ab:c:def" -- ["ab", "c", "def"] splitBy ∷ (a → Bool) → [a] → [[a]] @@ -57,17 +83,17 @@ quoteStr str = A.toAsciiBuilder "\"" ⊕ go (A.toByteString str) (∅) ⊕ A.toAsciiBuilder "\"" where - go ∷ Strict.ByteString → AsciiBuilder → AsciiBuilder + go ∷ ByteString → AsciiBuilder → AsciiBuilder go bs ab - = case Strict.break (≡ '"') bs of + = case BS.break (≡ '"') bs of (x, y) - | Strict.null y + | BS.null y → ab ⊕ b2ab x | otherwise - → go (Strict.tail y) + → go (BS.tail y) (ab ⊕ b2ab x ⊕ A.toAsciiBuilder "\\\"") - b2ab ∷ Strict.ByteString → AsciiBuilder + b2ab ∷ ByteString → AsciiBuilder b2ab = A.toAsciiBuilder ∘ A.unsafeFromByteString -- |>>> parseWWWFormURLEncoded "aaa=bbb&ccc=ddd" @@ -86,20 +112,33 @@ parseWWWFormURLEncoded src ) where unescape ∷ String → ByteString - unescape = Strict.pack ∘ unEscapeString ∘ (plusToSpace <$>) + unescape = BS.pack ∘ unEscapeString ∘ (plusToSpace <$>) plusToSpace ∷ Char → Char plusToSpace '+' = ' ' plusToSpace c = c +-- |>>> uriCIScheme "http://example.com/foo/bar" +-- "http" +uriCIScheme ∷ URI → Scheme +{-# INLINE uriCIScheme #-} +uriCIScheme = A.toCIAscii ∘ A.unsafeFromString ∘ uriScheme + +-- |>>> uriHost "http://example.com/foo/bar" +-- "example.com" +uriHost ∷ URI → Host +{-# INLINE uriHost #-} +uriHost = CI.mk ∘ T.pack ∘ uriRegName ∘ fromJust ∘ uriAuthority + -- |>>> uriPathSegments "http://example.com/foo/bar" -- ["foo", "bar"] -uriPathSegments ∷ URI → [ByteString] +uriPathSegments ∷ URI → PathSegments uriPathSegments uri = let reqPathStr = uriPath uri - reqPath = [unEscapeString x | x ← splitBy (≡ '/') reqPathStr, (¬) (null x)] + reqPath = [ unEscapeString x + | x ← splitBy (≡ '/') reqPathStr, (¬) (null x) ] in - Strict.pack <$> reqPath + BS.pack <$> reqPath -- |>>> trim " ab c d " -- "ab c d"