]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/MIMEParams.hs
Fixed lots of bugs
[Lucu.git] / Network / HTTP / Lucu / MIMEParams.hs
index f4b503ee6ddd176d3febb9e61aa0691967844070..ce0b6915a4118c2dbf178b786960ce8556f85355 100644 (file)
@@ -40,7 +40,6 @@ import Data.Text.Encoding
 import Data.Text.Encoding.Error
 import Data.Typeable
 import Data.Word
-import Language.Haskell.TH.Syntax
 import Network.HTTP.Lucu.OrphanInstances ()
 import Network.HTTP.Lucu.Parser.Http
 import Network.HTTP.Lucu.Utils
@@ -54,9 +53,7 @@ newtype MIMEParams
     = MIMEParams (M.Map CIAscii Text)
     deriving (Eq, Show, Read, Monoid, Typeable)
 
-instance Lift MIMEParams where
-    lift (MIMEParams m) = [| MIMEParams $(lift m) |]
-
+-- FIXME: auto-derive
 instance Unfoldable MIMEParams (CIAscii, Text) where
     {-# INLINE insert #-}
     insert p (MIMEParams m)
@@ -74,6 +71,7 @@ instance Unfoldable MIMEParams (CIAscii, Text) where
     insertManySorted f (MIMEParams m)
         = MIMEParams $ insertManySorted f m
 
+-- FIXME: auto-derive
 instance Foldable MIMEParams (CIAscii, Text) where
     {-# INLINE null #-}
     null (MIMEParams m) = null m
@@ -82,10 +80,12 @@ instance Foldable MIMEParams (CIAscii, Text) where
     {-# INLINE foldr #-}
     foldr f b (MIMEParams m) = foldr f b m
 
+-- FIXME: auto-derive
 instance Collection MIMEParams (CIAscii, Text) where
     {-# INLINE filter #-}
     filter f (MIMEParams m) = MIMEParams $ filter f m
 
+-- FIXME: auto-derive
 instance Indexed MIMEParams CIAscii Text where
     {-# INLINE index #-}
     index k (MIMEParams m) = index k m
@@ -94,6 +94,7 @@ instance Indexed MIMEParams CIAscii Text where
     {-# INLINE inDomain #-}
     inDomain k (MIMEParams m) = inDomain k m
 
+-- FIXME: auto-derive
 instance Map MIMEParams CIAscii Text where
     {-# INLINE lookup #-}
     lookup k (MIMEParams m) = lookup k m
@@ -116,6 +117,7 @@ instance Map MIMEParams CIAscii Text where
     isProperSubmapBy f (MIMEParams α) (MIMEParams β)
         = isProperSubmapBy f α β
 
+-- FIXME: auto-derive
 instance SortingCollection MIMEParams (CIAscii, Text) where
     {-# INLINE minView #-}
     minView (MIMEParams m) = second MIMEParams <$> minView m