]> gitweb @ CieloNegro.org - Lucu.git/blobdiff - Network/HTTP/Lucu/OrphanInstances.hs
It must be a bad idea to expose overlapped orphan instances.
[Lucu.git] / Network / HTTP / Lucu / OrphanInstances.hs
index b0bd421082eb10cb4948d1e6ebf58dafb0e3f751..333e162cdf5075bb1230059ddc723c13d5bb927a 100644 (file)
@@ -1,10 +1,9 @@
 {-# LANGUAGE
     FlexibleContexts
   , FlexibleInstances
-  , OverlappingInstances
   , RecordWildCards
+  , ScopedTypeVariables
   , TemplateHaskell
-  , UndecidableInstances
   , UnicodeSyntax
   #-}
 {-# OPTIONS_GHC -fno-warn-orphans #-}
@@ -12,6 +11,7 @@ module Network.HTTP.Lucu.OrphanInstances
     (
     )
     where
+import Control.Applicative hiding (empty)
 import Data.Ascii (Ascii)
 import qualified Data.Ascii as A
 import Data.ByteString (ByteString)
@@ -21,6 +21,7 @@ import Data.CaseInsensitive (CI, FoldCase)
 import qualified Data.CaseInsensitive as CI
 import Data.Collections
 import Data.Collections.BaseInstances ()
+import qualified Data.Map as M
 import Data.Ratio
 import Data.Text (Text)
 import qualified Data.Text as T
@@ -31,7 +32,7 @@ import Prelude hiding (last, mapM, null, reverse)
 import Prelude.Unicode
 
 instance Lift ByteString where
-    lift bs = [| Strict.pack $(litE $ stringL $ Strict.unpack bs) |]
+    lift bs = [| Strict.pack $(litE  stringL $ Strict.unpack bs) |]
 
 instance Lift Lazy.ByteString where
     lift = Lazy.foldrChunks f [| Lazy.Empty |]
@@ -46,14 +47,17 @@ instance (Lift s, FoldCase s) ⇒ Lift (CI s) where
     lift s = [| CI.mk $(lift $ CI.original s) |]
 
 instance Lift Text where
-    lift t = [| T.pack $(litE $ stringL $ T.unpack t) |]
+    lift t = [| T.pack $(litE  stringL $ T.unpack t) |]
 
-instance (Lift k, Lift v, Collection c (k, v)) ⇒ Lift c where
-    lift c
-        | null c    = [| empty |]
-        | otherwise = [| fromList $(liftPairs (fromFoldable c)) |]
+instance (Lift k, Lift v) ⇒ Lift (M.Map k v) where
+    lift m
+        | null m    = [| empty |]
+        | otherwise = [| fromAscList $(liftPairs (M.toAscList m)) |]
         where
-          liftPairs       = listE ∘ map liftPair
+          liftPairs ∷ [(k, v)] → Q Exp
+          liftPairs = listE ∘ (liftPair <$>)
+
+          liftPair ∷ (k, v) → Q Exp
           liftPair (k, v) = tupE [lift k, lift v]
 
 instance Lift UTCTime where
@@ -68,5 +72,5 @@ instance Lift DiffTime where
     lift dt = [| fromRational ($n % $d) ∷ DiffTime |]
         where
           n, d ∷ Q Exp
-          n = lift $ numerator   $ toRational dt
-          d = lift $ denominator $ toRational dt
+          n = lift  numerator   $ toRational dt
+          d = lift  denominator $ toRational dt