cleanup after rebase

This commit is contained in:
Brandon Martin 2015-10-01 08:05:49 -06:00
parent 745ff985b6
commit 4ad911aca4
5 changed files with 19 additions and 10 deletions

View file

@ -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

View file

@ -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) :)

View file

@ -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

View file

@ -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)

View file

@ -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'