X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FHeaders.hs;h=ff3213bc20860e98f18db7a3a89c8e96385cf797;hb=67f9e87;hp=2ee9cbb8ce60e39311b496aa2b8ebfe7666e9cbc;hpb=19763f7de78daf2d4c794f4010039f70c7f73994;p=Lucu.git diff --git a/Network/HTTP/Lucu/Headers.hs b/Network/HTTP/Lucu/Headers.hs index 2ee9cbb..ff3213b 100644 --- a/Network/HTTP/Lucu/Headers.hs +++ b/Network/HTTP/Lucu/Headers.hs @@ -2,10 +2,12 @@ FlexibleInstances , GeneralizedNewtypeDeriving , MultiParamTypeClasses + , TemplateHaskell , TypeSynonymInstances , OverloadedStrings , UnicodeSyntax #-} +{-# OPTIONS_GHC -fno-warn-missing-methods #-} -- |An internal module for HTTP headers. module Network.HTTP.Lucu.Headers ( Headers @@ -17,19 +19,19 @@ module Network.HTTP.Lucu.Headers where import Control.Applicative hiding (empty) import Control.Applicative.Unicode hiding ((∅)) -import Control.Arrow import Control.Monad import Data.Ascii (Ascii, AsciiBuilder, CIAscii) import qualified Data.Ascii as A -import Data.Attoparsec.Char8 as P +import Data.Attoparsec.Char8 +import qualified Data.Collections.Newtype.TH as C import Data.List (intersperse) -import qualified Data.Map as M +import qualified Data.Map as M (Map) import Data.Collections import Data.Collections.BaseInstances () import Data.Monoid import Data.Monoid.Unicode import Network.HTTP.Lucu.Parser.Http -import Prelude hiding (filter, foldr, lookup, null) +import Prelude hiding (lookup, null) import Prelude.Unicode newtype Headers @@ -68,75 +70,28 @@ instance HasHeaders Headers where getHeaders = id setHeaders _ = id +C.derive [d| instance Foldable Headers (CIAscii, Ascii) + instance Collection Headers (CIAscii, Ascii) + instance Indexed Headers CIAscii Ascii + instance Map Headers CIAscii Ascii + instance SortingCollection Headers (CIAscii, Ascii) + |] + -- |@'insert' (key, val)@ merges @val@ with an existing one if any. instance Unfoldable Headers (CIAscii, Ascii) where {-# INLINE insert #-} insert (key, val) (Headers m) = Headers $ insertWith merge key val m {-# INLINE empty #-} - empty - = Headers empty + empty = Headers empty {-# INLINE singleton #-} - singleton v - = Headers $ singleton v - {-# INLINE insertMany #-} - insertMany f (Headers m) - = Headers $ insertMany f m - {-# INLINE insertManySorted #-} - insertManySorted f (Headers m) - = Headers $ insertManySorted f m - -instance Foldable Headers (CIAscii, Ascii) where - {-# INLINE foldr #-} - foldr f b (Headers m) = foldr f b m - -instance Collection Headers (CIAscii, Ascii) where - {-# INLINE filter #-} - filter f (Headers m) = Headers $ filter f m - -instance Indexed Headers CIAscii Ascii where - {-# INLINE index #-} - index k (Headers m) = index k m - {-# INLINE adjust #-} - adjust f k (Headers m) = Headers $ adjust f k m - {-# INLINE inDomain #-} - inDomain k (Headers m) = inDomain k m + singleton = Headers ∘ singleton instance Monoid Headers where {-# INLINE mempty #-} - mempty = empty + mempty = empty {-# INLINE mappend #-} - mappend (Headers α) (Headers β) - = Headers $ insertManySorted β α - -instance Map Headers CIAscii Ascii where - {-# INLINE lookup #-} - lookup k (Headers m) = lookup k m - {-# INLINE insertWith #-} - insertWith f k v (Headers m) - = Headers $ insertWith f k v m - {-# INLINE mapWithKey #-} - mapWithKey f (Headers m) - = Headers $ mapWithKey f m - {-# INLINE unionWith #-} - unionWith f (Headers α) (Headers β) - = Headers $ unionWith f α β - {-# INLINE intersectionWith #-} - intersectionWith f (Headers α) (Headers β) - = Headers $ intersectionWith f α β - {-# INLINE differenceWith #-} - differenceWith f (Headers α) (Headers β) - = Headers $ differenceWith f α β - {-# INLINE isSubmapBy #-} - isSubmapBy f (Headers α) (Headers β) - = isSubmapBy f α β - {-# INLINE isProperSubmapBy #-} - isProperSubmapBy f (Headers α) (Headers β) - = isProperSubmapBy f α β - -instance SortingCollection Headers (CIAscii, Ascii) where - {-# INLINE minView #-} - minView (Headers m) = second Headers <$> minView m + mappend = insertMany merge ∷ Ascii → Ascii → Ascii {-# INLINE merge #-} @@ -163,7 +118,7 @@ merge a b -} headers ∷ Parser Headers {-# INLINEABLE headers #-} -headers = do xs ← P.many header +headers = do xs ← many header crlf return $ fromFoldable xs where @@ -187,11 +142,11 @@ headers = do xs ← P.many header joinValues = A.fromAsciiBuilder ∘ mconcat ∘ intersperse (A.toAsciiBuilder "\x20") - ∘ map A.toAsciiBuilder + ∘ (A.toAsciiBuilder <$>) printHeaders ∷ Headers → AsciiBuilder printHeaders (Headers m) - = mconcat (map printHeader (fromFoldable m)) ⊕ + = mconcat (printHeader <$> fromFoldable m) ⊕ A.toAsciiBuilder "\x0D\x0A" where printHeader ∷ (CIAscii, Ascii) → AsciiBuilder