X-Git-Url: http://git.cielonegro.org/gitweb.cgi?a=blobdiff_plain;f=Network%2FHTTP%2FLucu%2FOrphanInstances.hs;h=8fa7e68714437b8270abb7b42d13e3ab35d360dc;hb=HEAD;hp=b0bd421082eb10cb4948d1e6ebf58dafb0e3f751;hpb=6df5f92e37d27641f53e271f043c66dd3d085bb7;p=Lucu.git diff --git a/Network/HTTP/Lucu/OrphanInstances.hs b/Network/HTTP/Lucu/OrphanInstances.hs index b0bd421..8fa7e68 100644 --- a/Network/HTTP/Lucu/OrphanInstances.hs +++ b/Network/HTTP/Lucu/OrphanInstances.hs @@ -1,10 +1,9 @@ {-# LANGUAGE FlexibleContexts , FlexibleInstances - , OverlappingInstances , RecordWildCards + , ScopedTypeVariables , TemplateHaskell - , UndecidableInstances , UnicodeSyntax #-} {-# OPTIONS_GHC -fno-warn-orphans #-} @@ -12,6 +11,8 @@ module Network.HTTP.Lucu.OrphanInstances ( ) where +import Control.Applicative hiding (empty) +import Control.Monad import Data.Ascii (Ascii) import qualified Data.Ascii as A import Data.ByteString (ByteString) @@ -21,6 +22,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 @@ -30,8 +32,14 @@ import Language.Haskell.TH.Syntax import Prelude hiding (last, mapM, null, reverse) import Prelude.Unicode +instance Applicative Q where + {-# INLINE pure #-} + pure = return + {-# INLINE (<*>) #-} + (<*>) = ap + 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 +54,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 +79,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