From 4ad911aca4e0b1fb8b57f05ea0235a76fe06e146 Mon Sep 17 00:00:00 2001 From: Brandon Martin Date: Thu, 1 Oct 2015 08:05:49 -0600 Subject: [PATCH] cleanup after rebase --- servant-docs/src/Servant/Docs/Internal.hs | 2 +- servant-foreign/src/Servant/Foreign.hs | 4 ++-- .../src/Servant/Server/Internal/Enter.hs | 19 ++++++++++++++----- .../src/Servant/Utils/StaticFiles.hs | 2 +- .../test/Servant/Server/Internal/EnterSpec.hs | 2 +- 5 files changed, 19 insertions(+), 10 deletions(-) diff --git a/servant-docs/src/Servant/Docs/Internal.hs b/servant-docs/src/Servant/Docs/Internal.hs index 37eb5c90..6ea9b2db 100644 --- a/servant-docs/src/Servant/Docs/Internal.hs +++ b/servant-docs/src/Servant/Docs/Internal.hs @@ -941,7 +941,7 @@ instance (KnownSymbol sym, {- ToParam (MatrixFlag sym), -} HasDocs sublayout) symP = Proxy :: Proxy sym instance HasDocs (Raw m a) where - docsFor _proxy (endpoint, action) = + docsFor _proxy (endpoint, action) _ = single endpoint action -- TODO: We use 'AllMimeRender' here because we need to be able to show the diff --git a/servant-foreign/src/Servant/Foreign.hs b/servant-foreign/src/Servant/Foreign.hs index 6cd72b84..75714d1e 100644 --- a/servant-foreign/src/Servant/Foreign.hs +++ b/servant-foreign/src/Servant/Foreign.hs @@ -276,8 +276,8 @@ instance (KnownSymbol sym, HasForeign sublayout) where str = symbolVal (Proxy :: Proxy sym) -instance HasForeign Raw where - type Foreign Raw = Method -> Req +instance HasForeign (Raw m a) where + type Foreign (Raw m a) = Method -> Req foreignFor Proxy req method = req & funcName %~ ((toLower <$> method) :) diff --git a/servant-server/src/Servant/Server/Internal/Enter.hs b/servant-server/src/Servant/Server/Internal/Enter.hs index a754704d..da4194a8 100644 --- a/servant-server/src/Servant/Server/Internal/Enter.hs +++ b/servant-server/src/Servant/Server/Internal/Enter.hs @@ -8,7 +8,9 @@ {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE UndecidableInstances #-} +#if !MIN_VERSION_base(4,8,0) {-# LANGUAGE OverlappingInstances #-} +#endif module Servant.Server.Internal.Enter where #if !MIN_VERSION_base(4,8,0) @@ -51,12 +53,19 @@ instance C.Category (:~>) where id = Nat id Nat f . Nat g = Nat (f . g) +instance +#if MIN_VERSION_base(4,8,0) + {-# OVERLAPPING #-} +#endif + Enter (m a) (m :~> n) (n a) where + enter (Nat f) = f -instance Enter (m a) (m :~> n) (n a) where - enter (Nat f) = f - -instance (Raw m' ~ m, Raw n' ~ n) => Enter (m a) (m' :~> n') (n a) where - enter _ (Raw a) = Raw a +instance +#if MIN_VERSION_base(4,8,0) + {-# OVERLAPPABLE #-} +#endif + (Raw m' ~ m, Raw n' ~ n) => Enter (m a) (m' :~> n') (n a) where + enter _ (Raw a) = Raw a -- | Like `lift`. liftNat :: (Control.Monad.Morph.MonadTrans t, Monad m) => m :~> t m diff --git a/servant-server/src/Servant/Utils/StaticFiles.hs b/servant-server/src/Servant/Utils/StaticFiles.hs index 3ac9a09b..b0fe1a5c 100644 --- a/servant-server/src/Servant/Utils/StaticFiles.hs +++ b/servant-server/src/Servant/Utils/StaticFiles.hs @@ -12,7 +12,7 @@ import Network.Wai.Application.Static (defaultFileServerSettings, staticApp) import Network.Wai (Application) import Servant.API.Raw (Raw(..)) -import Servant.Server (Server) +import Servant.Server (ServerT) import System.FilePath (addTrailingPathSeparator) #if !MIN_VERSION_wai_app_static(3,1,0) import Filesystem.Path.CurrentOS (decodeString) diff --git a/servant-server/test/Servant/Server/Internal/EnterSpec.hs b/servant-server/test/Servant/Server/Internal/EnterSpec.hs index a6895163..5659c028 100644 --- a/servant-server/test/Servant/Server/Internal/EnterSpec.hs +++ b/servant-server/test/Servant/Server/Internal/EnterSpec.hs @@ -28,7 +28,7 @@ type ReaderAPI' = "ep1" :> Get '[JSON] String :<|> "ep2" :> Get '[JSON] String readerServera' :: Reader String String :<|> Reader String String readerServera' = ask :<|> ask -x :: Reader String :~> EitherT ServantErr IO +x :: Reader String :~> ExceptT ServantErr IO x = (generalizeNat C.. (runReaderTNat "hi")) mainServer' :: Server ReaderAPI' mainServer' = enter x readerServera'