From 9a33fa7812aab6751575a9667ca661f0bcf090c3 Mon Sep 17 00:00:00 2001 From: Alp Mestanogullari Date: Mon, 9 Mar 2015 15:16:38 +0100 Subject: [PATCH 1/8] Canonicalize the API type to make sure that the following 'law' holds: Server (a :> (b :<|> c)) ~ Server (a :> b) :<|> Server (a :> c) --- src/Servant/Server.hs | 10 ++++-- src/Servant/Server/Internal.hs | 59 ++++++++++++++++---------------- src/Servant/Utils/StaticFiles.hs | 2 +- 3 files changed, 38 insertions(+), 33 deletions(-) diff --git a/src/Servant/Server.hs b/src/Servant/Server.hs index 0bec3370..7329fecc 100644 --- a/src/Servant/Server.hs +++ b/src/Servant/Server.hs @@ -1,4 +1,5 @@ {-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE OverloadedStrings #-} -- | This module lets you implement 'Server's for defined APIs. You'll @@ -12,11 +13,12 @@ module Servant.Server , -- * Handlers for all standard combinators HasServer(..) + , Server ) where import Data.Proxy (Proxy) import Network.Wai (Application) - +import Servant.API (Canonicalize) import Servant.Server.Internal @@ -42,5 +44,7 @@ import Servant.Server.Internal -- > -- > main :: IO () -- > main = Network.Wai.Handler.Warp.run 8080 app -serve :: HasServer layout => Proxy layout -> Server layout -> Application -serve p server = toApplication (route p server) +serve :: HasServer (Canonicalize layout) => Proxy layout -> Server layout -> Application +serve p server = toApplication (route (canonicalize p) server) + +type Server layout = Server' (Canonicalize layout) diff --git a/src/Servant/Server/Internal.hs b/src/Servant/Server/Internal.hs index 159560fa..a8e97687 100644 --- a/src/Servant/Server/Internal.hs +++ b/src/Servant/Server/Internal.hs @@ -160,10 +160,11 @@ processedPathInfo r = where pinfo = parsePathInfo r class HasServer layout where - type Server layout :: * - route :: Proxy layout -> Server layout -> RoutingApplication - + type Server' layout :: * + route :: Proxy layout -> Server' layout -> RoutingApplication +canonicalize :: Canonicalize layout ~ t => Proxy layout -> Proxy t +canonicalize Proxy = Proxy -- * Instances @@ -179,7 +180,7 @@ class HasServer layout where -- > where listAllBooks = ... -- > postBook book = ... instance (HasServer a, HasServer b) => HasServer (a :<|> b) where - type Server (a :<|> b) = Server a :<|> Server b + type Server' (a :<|> b) = Server' a :<|> Server' b route Proxy (a :<|> b) request respond = route pa a request $ \ mResponse -> if isMismatch mResponse @@ -212,8 +213,8 @@ captured _ = fromText instance (KnownSymbol capture, FromText a, HasServer sublayout) => HasServer (Capture capture a :> sublayout) where - type Server (Capture capture a :> sublayout) = - a -> Server sublayout + type Server' (Capture capture a :> sublayout) = + a -> Server' sublayout route Proxy subserver request respond = case processedPathInfo request of (first : rest) @@ -239,7 +240,7 @@ instance (KnownSymbol capture, FromText a, HasServer sublayout) -- painlessly error out if the conditions for a successful deletion -- are not met. instance HasServer Delete where - type Server Delete = EitherT (Int, String) IO () + type Server' Delete = EitherT (Int, String) IO () route Proxy action request respond | pathIsEmpty request && requestMethod request == methodDelete = do @@ -268,7 +269,7 @@ instance HasServer Delete where -- list. instance ( AllCTRender ctypes a ) => HasServer (Get ctypes a) where - type Server (Get ctypes a) = EitherT (Int, String) IO a + type Server' (Get ctypes a) = EitherT (Int, String) IO a route Proxy action request respond | pathIsEmpty request && requestMethod request == methodGet = do e <- runEitherT action @@ -308,8 +309,8 @@ instance ( AllCTRender ctypes a instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (Header sym a :> sublayout) where - type Server (Header sym a :> sublayout) = - Maybe a -> Server sublayout + type Server' (Header sym a :> sublayout) = + Maybe a -> Server' sublayout route Proxy subserver request respond = do let mheader = fromText . decodeUtf8 =<< lookup str (requestHeaders request) @@ -332,7 +333,7 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout) -- list. instance ( AllCTRender ctypes a ) => HasServer (Post ctypes a) where - type Server (Post ctypes a) = EitherT (Int, String) IO a + type Server' (Post ctypes a) = EitherT (Int, String) IO a route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPost = do @@ -365,7 +366,7 @@ instance ( AllCTRender ctypes a -- list. instance ( AllCTRender ctypes a ) => HasServer (Put ctypes a) where - type Server (Put ctypes a) = EitherT (Int, String) IO a + type Server' (Put ctypes a) = EitherT (Int, String) IO a route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPut = do @@ -398,7 +399,7 @@ instance ( AllCTRender ctypes a instance ( AllCTRender ctypes a , Typeable a , ToJSON a) => HasServer (Patch ctypes a) where - type Server (Patch ctypes a) = EitherT (Int, String) IO a + type Server' (Patch ctypes a) = EitherT (Int, String) IO a route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPost = do @@ -442,8 +443,8 @@ instance ( AllCTRender ctypes a instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (QueryParam sym a :> sublayout) where - type Server (QueryParam sym a :> sublayout) = - Maybe a -> Server sublayout + type Server' (QueryParam sym a :> sublayout) = + Maybe a -> Server' sublayout route Proxy subserver request respond = do let querytext = parseQueryText $ rawQueryString request @@ -480,8 +481,8 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout) instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (QueryParams sym a :> sublayout) where - type Server (QueryParams sym a :> sublayout) = - [a] -> Server sublayout + type Server' (QueryParams sym a :> sublayout) = + [a] -> Server' sublayout route Proxy subserver request respond = do let querytext = parseQueryText $ rawQueryString request @@ -513,8 +514,8 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout) instance (KnownSymbol sym, HasServer sublayout) => HasServer (QueryFlag sym :> sublayout) where - type Server (QueryFlag sym :> sublayout) = - Bool -> Server sublayout + type Server' (QueryFlag sym :> sublayout) = + Bool -> Server' sublayout route Proxy subserver request respond = do let querytext = parseQueryText $ rawQueryString request @@ -556,8 +557,8 @@ parseMatrixText = parseQueryText instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (MatrixParam sym a :> sublayout) where - type Server (MatrixParam sym a :> sublayout) = - Maybe a -> Server sublayout + type Server' (MatrixParam sym a :> sublayout) = + Maybe a -> Server' sublayout route Proxy subserver request respond = case parsePathInfo request of (first : _) @@ -594,8 +595,8 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout) instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (MatrixParams sym a :> sublayout) where - type Server (MatrixParams sym a :> sublayout) = - [a] -> Server sublayout + type Server' (MatrixParams sym a :> sublayout) = + [a] -> Server' sublayout route Proxy subserver request respond = case parsePathInfo request of (first : _) @@ -628,8 +629,8 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout) instance (KnownSymbol sym, HasServer sublayout) => HasServer (MatrixFlag sym :> sublayout) where - type Server (MatrixFlag sym :> sublayout) = - Bool -> Server sublayout + type Server' (MatrixFlag sym :> sublayout) = + Bool -> Server' sublayout route Proxy subserver request respond = case parsePathInfo request of (first : _) @@ -656,7 +657,7 @@ instance (KnownSymbol sym, HasServer sublayout) -- > server :: Server MyApi -- > server = serveDirectory "/var/www/images" instance HasServer Raw where - type Server Raw = Application + type Server' Raw = Application route Proxy rawApplication request respond = rawApplication request (respond . succeedWith) @@ -683,8 +684,8 @@ instance HasServer Raw where instance ( AllCTUnrender list a, HasServer sublayout ) => HasServer (ReqBody list a :> sublayout) where - type Server (ReqBody list a :> sublayout) = - a -> Server sublayout + type Server' (ReqBody list a :> sublayout) = + a -> Server' sublayout route Proxy subserver request respond = do -- See HTTP RFC 2616, section 7.2.1 @@ -703,7 +704,7 @@ instance ( AllCTUnrender list a, HasServer sublayout -- | Make sure the incoming request starts with @"/path"@, strip it and -- pass the rest of the request path to @sublayout@. instance (KnownSymbol path, HasServer sublayout) => HasServer (path :> sublayout) where - type Server (path :> sublayout) = Server sublayout + type Server' (path :> sublayout) = Server' sublayout route Proxy subserver request respond = case processedPathInfo request of (first : rest) | first == cs (symbolVal proxyPath) diff --git a/src/Servant/Utils/StaticFiles.hs b/src/Servant/Utils/StaticFiles.hs index 9cd5fdcc..07c51173 100644 --- a/src/Servant/Utils/StaticFiles.hs +++ b/src/Servant/Utils/StaticFiles.hs @@ -9,7 +9,7 @@ module Servant.Utils.StaticFiles ( import Filesystem.Path.CurrentOS (decodeString) import Network.Wai.Application.Static (staticApp, defaultFileServerSettings) import Servant.API.Raw (Raw) -import Servant.Server.Internal (Server) +import Servant.Server (Server) -- | Serve anything under the specified directory as a 'Raw' endpoint. -- From 5f7795f70f2dc96c2e40183c25e2b07f758ee79c Mon Sep 17 00:00:00 2001 From: Alp Mestanogullari Date: Mon, 9 Mar 2015 19:23:53 +0100 Subject: [PATCH 2/8] remove canonicalize, it's now in servant --- src/Servant/Server/Internal.hs | 3 --- 1 file changed, 3 deletions(-) diff --git a/src/Servant/Server/Internal.hs b/src/Servant/Server/Internal.hs index a8e97687..07da7df5 100644 --- a/src/Servant/Server/Internal.hs +++ b/src/Servant/Server/Internal.hs @@ -163,9 +163,6 @@ class HasServer layout where type Server' layout :: * route :: Proxy layout -> Server' layout -> RoutingApplication -canonicalize :: Canonicalize layout ~ t => Proxy layout -> Proxy t -canonicalize Proxy = Proxy - -- * Instances -- | A server for @a ':<|>' b@ first tries to match the request against the route From 8428e4bd7bda915161c0d144124139a1c2cd078e Mon Sep 17 00:00:00 2001 From: Alp Mestanogullari Date: Mon, 9 Mar 2015 19:59:25 +0100 Subject: [PATCH 3/8] fix dumb error --- src/Servant/Server.hs | 2 +- 1 file changed, 1 insertion(+), 1 deletion(-) diff --git a/src/Servant/Server.hs b/src/Servant/Server.hs index 7329fecc..c87befd4 100644 --- a/src/Servant/Server.hs +++ b/src/Servant/Server.hs @@ -18,7 +18,7 @@ module Servant.Server import Data.Proxy (Proxy) import Network.Wai (Application) -import Servant.API (Canonicalize) +import Servant.API (Canonicalize, canonicalize) import Servant.Server.Internal From f76c729a084fb5e4a8f1ff7cfbca207986200e7b Mon Sep 17 00:00:00 2001 From: Roland Schatz Date: Mon, 2 Mar 2015 22:23:56 +0100 Subject: [PATCH 4/8] Introduce `ServerT` to specify generic handlers. --- src/Servant/Server/Internal.hs | 69 +++++++++++++++++++++------------- 1 file changed, 42 insertions(+), 27 deletions(-) diff --git a/src/Servant/Server/Internal.hs b/src/Servant/Server/Internal.hs index 07da7df5..741ddc62 100644 --- a/src/Servant/Server/Internal.hs +++ b/src/Servant/Server/Internal.hs @@ -160,9 +160,12 @@ processedPathInfo r = where pinfo = parsePathInfo r class HasServer layout where - type Server' layout :: * + type ServerT layout (m :: * -> *) :: * route :: Proxy layout -> Server' layout -> RoutingApplication +type Server' layout = ServerT layout (EitherT (Int, String) IO) + + -- * Instances -- | A server for @a ':<|>' b@ first tries to match the request against the route @@ -177,7 +180,9 @@ class HasServer layout where -- > where listAllBooks = ... -- > postBook book = ... instance (HasServer a, HasServer b) => HasServer (a :<|> b) where - type Server' (a :<|> b) = Server' a :<|> Server' b + + type ServerT (a :<|> b) m = ServerT a m :<|> ServerT b m + route Proxy (a :<|> b) request respond = route pa a request $ \ mResponse -> if isMismatch mResponse @@ -210,8 +215,8 @@ captured _ = fromText instance (KnownSymbol capture, FromText a, HasServer sublayout) => HasServer (Capture capture a :> sublayout) where - type Server' (Capture capture a :> sublayout) = - a -> Server' sublayout + type ServerT (Capture capture a :> sublayout) m = + a -> ServerT sublayout m route Proxy subserver request respond = case processedPathInfo request of (first : rest) @@ -237,7 +242,8 @@ instance (KnownSymbol capture, FromText a, HasServer sublayout) -- painlessly error out if the conditions for a successful deletion -- are not met. instance HasServer Delete where - type Server' Delete = EitherT (Int, String) IO () + + type ServerT Delete m = m () route Proxy action request respond | pathIsEmpty request && requestMethod request == methodDelete = do @@ -266,7 +272,9 @@ instance HasServer Delete where -- list. instance ( AllCTRender ctypes a ) => HasServer (Get ctypes a) where - type Server' (Get ctypes a) = EitherT (Int, String) IO a + + type ServerT (Get ctypes a) m = m a + route Proxy action request respond | pathIsEmpty request && requestMethod request == methodGet = do e <- runEitherT action @@ -306,8 +314,8 @@ instance ( AllCTRender ctypes a instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (Header sym a :> sublayout) where - type Server' (Header sym a :> sublayout) = - Maybe a -> Server' sublayout + type ServerT (Header sym a :> sublayout) m = + Maybe a -> ServerT sublayout m route Proxy subserver request respond = do let mheader = fromText . decodeUtf8 =<< lookup str (requestHeaders request) @@ -330,7 +338,8 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout) -- list. instance ( AllCTRender ctypes a ) => HasServer (Post ctypes a) where - type Server' (Post ctypes a) = EitherT (Int, String) IO a + + type ServerT (Post ctypes a) m = m a route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPost = do @@ -363,7 +372,8 @@ instance ( AllCTRender ctypes a -- list. instance ( AllCTRender ctypes a ) => HasServer (Put ctypes a) where - type Server' (Put ctypes a) = EitherT (Int, String) IO a + + type ServerT (Put ctypes a) m = m a route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPut = do @@ -396,7 +406,8 @@ instance ( AllCTRender ctypes a instance ( AllCTRender ctypes a , Typeable a , ToJSON a) => HasServer (Patch ctypes a) where - type Server' (Patch ctypes a) = EitherT (Int, String) IO a + + type ServerT (Patch ctypes a) m = m a route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPost = do @@ -440,8 +451,8 @@ instance ( AllCTRender ctypes a instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (QueryParam sym a :> sublayout) where - type Server' (QueryParam sym a :> sublayout) = - Maybe a -> Server' sublayout + type ServerT (QueryParam sym a :> sublayout) m = + Maybe a -> ServerT sublayout m route Proxy subserver request respond = do let querytext = parseQueryText $ rawQueryString request @@ -478,8 +489,8 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout) instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (QueryParams sym a :> sublayout) where - type Server' (QueryParams sym a :> sublayout) = - [a] -> Server' sublayout + type ServerT (QueryParams sym a :> sublayout) m = + [a] -> ServerT sublayout m route Proxy subserver request respond = do let querytext = parseQueryText $ rawQueryString request @@ -511,8 +522,8 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout) instance (KnownSymbol sym, HasServer sublayout) => HasServer (QueryFlag sym :> sublayout) where - type Server' (QueryFlag sym :> sublayout) = - Bool -> Server' sublayout + type ServerT (QueryFlag sym :> sublayout) m = + Bool -> ServerT sublayout m route Proxy subserver request respond = do let querytext = parseQueryText $ rawQueryString request @@ -554,8 +565,8 @@ parseMatrixText = parseQueryText instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (MatrixParam sym a :> sublayout) where - type Server' (MatrixParam sym a :> sublayout) = - Maybe a -> Server' sublayout + type ServerT (MatrixParam sym a :> sublayout) m = + Maybe a -> ServerT sublayout m route Proxy subserver request respond = case parsePathInfo request of (first : _) @@ -592,8 +603,8 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout) instance (KnownSymbol sym, FromText a, HasServer sublayout) => HasServer (MatrixParams sym a :> sublayout) where - type Server' (MatrixParams sym a :> sublayout) = - [a] -> Server' sublayout + type ServerT (MatrixParams sym a :> sublayout) m = + [a] -> ServerT sublayout m route Proxy subserver request respond = case parsePathInfo request of (first : _) @@ -626,8 +637,8 @@ instance (KnownSymbol sym, FromText a, HasServer sublayout) instance (KnownSymbol sym, HasServer sublayout) => HasServer (MatrixFlag sym :> sublayout) where - type Server' (MatrixFlag sym :> sublayout) = - Bool -> Server' sublayout + type ServerT (MatrixFlag sym :> sublayout) m = + Bool -> ServerT sublayout m route Proxy subserver request respond = case parsePathInfo request of (first : _) @@ -654,7 +665,9 @@ instance (KnownSymbol sym, HasServer sublayout) -- > server :: Server MyApi -- > server = serveDirectory "/var/www/images" instance HasServer Raw where - type Server' Raw = Application + + type ServerT Raw m = Application + route Proxy rawApplication request respond = rawApplication request (respond . succeedWith) @@ -681,8 +694,8 @@ instance HasServer Raw where instance ( AllCTUnrender list a, HasServer sublayout ) => HasServer (ReqBody list a :> sublayout) where - type Server' (ReqBody list a :> sublayout) = - a -> Server' sublayout + type ServerT (ReqBody list a :> sublayout) m = + a -> ServerT sublayout m route Proxy subserver request respond = do -- See HTTP RFC 2616, section 7.2.1 @@ -701,7 +714,9 @@ instance ( AllCTUnrender list a, HasServer sublayout -- | Make sure the incoming request starts with @"/path"@, strip it and -- pass the rest of the request path to @sublayout@. instance (KnownSymbol path, HasServer sublayout) => HasServer (path :> sublayout) where - type Server' (path :> sublayout) = Server' sublayout + + type ServerT (path :> sublayout) m = ServerT sublayout m + route Proxy subserver request respond = case processedPathInfo request of (first : rest) | first == cs (symbolVal proxyPath) From bd9d476679dd54340616a639770153be0ef40e10 Mon Sep 17 00:00:00 2001 From: "Julian K. Arni" Date: Tue, 10 Mar 2015 23:07:24 +0100 Subject: [PATCH 5/8] CHANGELOG update for PR #21. --- CHANGELOG.md | 1 + 1 file changed, 1 insertion(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index f45412af..6a0b3e47 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -4,6 +4,7 @@ * Add support for the `Patch` combinator * Support for `Accept`/`Content-type` headers and for the content-type aware combinators in *servant-0.3* * Export `toApplication` from `Servant.Server` (https://github.com/haskell-servant/servant-server/pull/29) +* Support other Monads than just `EitherT (Int, String) IO` (https://github.com/haskell-servant/servant-server/pull/21) 0.2.4 ----- From 837099d12d956095cd72324701aa4c1b34ef7222 Mon Sep 17 00:00:00 2001 From: Alp Mestanogullari Date: Mon, 9 Mar 2015 15:16:38 +0100 Subject: [PATCH 6/8] Canonicalize the API type to make sure that the following 'law' holds: Server (a :> (b :<|> c)) ~ Server (a :> b) :<|> Server (a :> c) --- src/Servant/Server/Internal.hs | 3 +-- 1 file changed, 1 insertion(+), 2 deletions(-) diff --git a/src/Servant/Server/Internal.hs b/src/Servant/Server/Internal.hs index 741ddc62..3b53efc9 100644 --- a/src/Servant/Server/Internal.hs +++ b/src/Servant/Server/Internal.hs @@ -165,7 +165,6 @@ class HasServer layout where type Server' layout = ServerT layout (EitherT (Int, String) IO) - -- * Instances -- | A server for @a ':<|>' b@ first tries to match the request against the route @@ -184,7 +183,7 @@ instance (HasServer a, HasServer b) => HasServer (a :<|> b) where type ServerT (a :<|> b) m = ServerT a m :<|> ServerT b m route Proxy (a :<|> b) request respond = - route pa a request $ \ mResponse -> + route pa a request $ \mResponse -> if isMismatch mResponse then route pb b request $ \mResponse' -> respond (mResponse <> mResponse') else respond mResponse From c1ed47b35f94d9ca84ba402d24a2056b4269f106 Mon Sep 17 00:00:00 2001 From: Alp Mestanogullari Date: Wed, 11 Mar 2015 12:19:14 +0100 Subject: [PATCH 7/8] add changelog entry --- CHANGELOG.md | 1 + 1 file changed, 1 insertion(+) diff --git a/CHANGELOG.md b/CHANGELOG.md index 6a0b3e47..8246c2ba 100644 --- a/CHANGELOG.md +++ b/CHANGELOG.md @@ -5,6 +5,7 @@ * Support for `Accept`/`Content-type` headers and for the content-type aware combinators in *servant-0.3* * Export `toApplication` from `Servant.Server` (https://github.com/haskell-servant/servant-server/pull/29) * Support other Monads than just `EitherT (Int, String) IO` (https://github.com/haskell-servant/servant-server/pull/21) +* Canonicalize API types before generating the handler typesy 0.2.4 ----- From bf637865cd234f9809cc8c4862ed851d55aade6f Mon Sep 17 00:00:00 2001 From: Alp Mestanogullari Date: Sun, 19 Apr 2015 12:06:31 +0200 Subject: [PATCH 8/8] fix inconsistencies from rebase --- src/Servant/Server/Internal.hs | 16 ++++++++-------- 1 file changed, 8 insertions(+), 8 deletions(-) diff --git a/src/Servant/Server/Internal.hs b/src/Servant/Server/Internal.hs index 66bb422f..6c509fe8 100644 --- a/src/Servant/Server/Internal.hs +++ b/src/Servant/Server/Internal.hs @@ -303,7 +303,7 @@ instance ( AllCTRender ctypes a -- '()' ==> 204 No Content instance HasServer (Get ctypes ()) where - type ServerT (Get ctypes ()) m = m () + type ServerT' (Get ctypes ()) m = m () route Proxy action request respond | pathIsEmpty request && requestMethod request == methodGet = do e <- runEitherT action @@ -317,7 +317,7 @@ instance HasServer (Get ctypes ()) where -- Add response headers instance ( AllCTRender ctypes v ) => HasServer (Get ctypes (Headers h v)) where - type ServerT (Get ctypes (Headers h v)) m = m (Headers h v) + type ServerT' (Get ctypes (Headers h v)) m = m (Headers h v) route Proxy action request respond | pathIsEmpty request && requestMethod request == methodGet = do e <- runEitherT action @@ -402,7 +402,7 @@ instance ( AllCTRender ctypes a | otherwise = respond $ failWith NotFound instance HasServer (Post ctypes ()) where - type ServerT (Post ctypes ()) m = m () + type ServerT' (Post ctypes ()) m = m () route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPost = do e <- runEitherT action @@ -416,7 +416,7 @@ instance HasServer (Post ctypes ()) where -- Add response headers instance ( AllCTRender ctypes v ) => HasServer (Post ctypes (Headers h v)) where - type ServerT (Post ctypes (Headers h v)) m = m (Headers h v) + type ServerT' (Post ctypes (Headers h v)) m = m (Headers h v) route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPost = do e <- runEitherT action @@ -469,7 +469,7 @@ instance ( AllCTRender ctypes a | otherwise = respond $ failWith NotFound instance HasServer (Put ctypes ()) where - type ServerT (Put ctypes ()) m = m () + type ServerT' (Put ctypes ()) m = m () route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPut = do e <- runEitherT action @@ -483,7 +483,7 @@ instance HasServer (Put ctypes ()) where -- Add response headers instance ( AllCTRender ctypes v ) => HasServer (Put ctypes (Headers h v)) where - type ServerT (Put ctypes (Headers h v)) m = m (Headers h v) + type ServerT' (Put ctypes (Headers h v)) m = m (Headers h v) route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPut = do e <- runEitherT action @@ -533,7 +533,7 @@ instance ( AllCTRender ctypes a | otherwise = respond $ failWith NotFound instance HasServer (Patch ctypes ()) where - type ServerT (Patch ctypes ()) m = m () + type ServerT' (Patch ctypes ()) m = m () route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPatch = do e <- runEitherT action @@ -547,7 +547,7 @@ instance HasServer (Patch ctypes ()) where -- Add response headers instance ( AllCTRender ctypes v ) => HasServer (Patch ctypes (Headers h v)) where - type ServerT (Patch ctypes (Headers h v)) m = m (Headers h v) + type ServerT' (Patch ctypes (Headers h v)) m = m (Headers h v) route Proxy action request respond | pathIsEmpty request && requestMethod request == methodPatch = do e <- runEitherT action