-Wall fixes
This commit is contained in:
parent
84211d4a0f
commit
92d65aaf49
7 changed files with 38 additions and 15 deletions
|
@ -16,7 +16,6 @@
|
||||||
module Servant.Client
|
module Servant.Client
|
||||||
( client
|
( client
|
||||||
, HasClient(..)
|
, HasClient(..)
|
||||||
, Client
|
|
||||||
, ServantError(..)
|
, ServantError(..)
|
||||||
, module Servant.Common.BaseUrl
|
, module Servant.Common.BaseUrl
|
||||||
) where
|
) where
|
||||||
|
|
|
@ -660,7 +660,11 @@ instance HasDocs Delete where
|
||||||
action' = action & response.respBody .~ []
|
action' = action & response.respBody .~ []
|
||||||
& response.respStatus .~ 204
|
& response.respStatus .~ 204
|
||||||
|
|
||||||
instance (ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts)
|
instance
|
||||||
|
#if MIN_VERSION_base(4,8,0)
|
||||||
|
{-# OVERLAPPABLe #-}
|
||||||
|
#endif
|
||||||
|
(ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts)
|
||||||
=> HasDocs (Get cts a) where
|
=> HasDocs (Get cts a) where
|
||||||
docsFor Proxy (endpoint, action) =
|
docsFor Proxy (endpoint, action) =
|
||||||
single endpoint' action'
|
single endpoint' action'
|
||||||
|
@ -671,7 +675,11 @@ instance (ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts)
|
||||||
t = Proxy :: Proxy cts
|
t = Proxy :: Proxy cts
|
||||||
p = Proxy :: Proxy a
|
p = Proxy :: Proxy a
|
||||||
|
|
||||||
instance (ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts
|
instance
|
||||||
|
#if MIN_VERSION_base(4,8,0)
|
||||||
|
{-# OVERLAPPING #-}
|
||||||
|
#endif
|
||||||
|
(ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts
|
||||||
, AllHeaderSamples ls , GetHeaders (HList ls) )
|
, AllHeaderSamples ls , GetHeaders (HList ls) )
|
||||||
=> HasDocs (Get cts (Headers ls a)) where
|
=> HasDocs (Get cts (Headers ls a)) where
|
||||||
docsFor Proxy (endpoint, action) =
|
docsFor Proxy (endpoint, action) =
|
||||||
|
@ -694,7 +702,11 @@ instance (KnownSymbol sym, HasDocs sublayout)
|
||||||
action' = over headers (|> headername) action
|
action' = over headers (|> headername) action
|
||||||
headername = pack $ symbolVal (Proxy :: Proxy sym)
|
headername = pack $ symbolVal (Proxy :: Proxy sym)
|
||||||
|
|
||||||
instance (ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts)
|
instance
|
||||||
|
#if MIN_VERSION_base(4,8,0)
|
||||||
|
{-# OVERLAPPABLE #-}
|
||||||
|
#endif
|
||||||
|
(ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts)
|
||||||
=> HasDocs (Post cts a) where
|
=> HasDocs (Post cts a) where
|
||||||
docsFor Proxy (endpoint, action) =
|
docsFor Proxy (endpoint, action) =
|
||||||
single endpoint' action'
|
single endpoint' action'
|
||||||
|
@ -706,7 +718,11 @@ instance (ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts)
|
||||||
t = Proxy :: Proxy cts
|
t = Proxy :: Proxy cts
|
||||||
p = Proxy :: Proxy a
|
p = Proxy :: Proxy a
|
||||||
|
|
||||||
instance (ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts
|
instance
|
||||||
|
#if MIN_VERSION_base(4,8,0)
|
||||||
|
{-# OVERLAPPING #-}
|
||||||
|
#endif
|
||||||
|
(ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts
|
||||||
, AllHeaderSamples ls , GetHeaders (HList ls) )
|
, AllHeaderSamples ls , GetHeaders (HList ls) )
|
||||||
=> HasDocs (Post cts (Headers ls a)) where
|
=> HasDocs (Post cts (Headers ls a)) where
|
||||||
docsFor Proxy (endpoint, action) =
|
docsFor Proxy (endpoint, action) =
|
||||||
|
@ -721,7 +737,11 @@ instance (ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts
|
||||||
t = Proxy :: Proxy cts
|
t = Proxy :: Proxy cts
|
||||||
p = Proxy :: Proxy a
|
p = Proxy :: Proxy a
|
||||||
|
|
||||||
instance (ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts)
|
instance
|
||||||
|
#if MIN_VERSION_base(4,8,0)
|
||||||
|
{-# OVERLAPPABLE #-}
|
||||||
|
#endif
|
||||||
|
(ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts)
|
||||||
=> HasDocs (Put cts a) where
|
=> HasDocs (Put cts a) where
|
||||||
docsFor Proxy (endpoint, action) =
|
docsFor Proxy (endpoint, action) =
|
||||||
single endpoint' action'
|
single endpoint' action'
|
||||||
|
@ -733,7 +753,11 @@ instance (ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts)
|
||||||
t = Proxy :: Proxy cts
|
t = Proxy :: Proxy cts
|
||||||
p = Proxy :: Proxy a
|
p = Proxy :: Proxy a
|
||||||
|
|
||||||
instance (ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts
|
instance
|
||||||
|
#if MIN_VERSION_base(4,8,0)
|
||||||
|
{-# OVERLAPPING #-}
|
||||||
|
#endif
|
||||||
|
(ToSample a b, IsNonEmpty cts, AllMimeRender cts b, SupportedTypes cts
|
||||||
, AllHeaderSamples ls , GetHeaders (HList ls) )
|
, AllHeaderSamples ls , GetHeaders (HList ls) )
|
||||||
=> HasDocs (Put cts (Headers ls a)) where
|
=> HasDocs (Put cts (Headers ls a)) where
|
||||||
docsFor Proxy (endpoint, action) =
|
docsFor Proxy (endpoint, action) =
|
||||||
|
|
|
@ -26,7 +26,7 @@ isGoodCookie = return . (== "good password")
|
||||||
data AuthProtected
|
data AuthProtected
|
||||||
|
|
||||||
instance HasServer rest => HasServer (AuthProtected :> rest) where
|
instance HasServer rest => HasServer (AuthProtected :> rest) where
|
||||||
type ServerT' (AuthProtected :> rest) m = ServerT' rest m
|
type ServerT (AuthProtected :> rest) m = ServerT rest m
|
||||||
|
|
||||||
route Proxy a request respond =
|
route Proxy a request respond =
|
||||||
case lookup "Cookie" (requestHeaders request) of
|
case lookup "Cookie" (requestHeaders request) of
|
||||||
|
|
|
@ -22,7 +22,7 @@ data Authorization (sym :: Symbol) a
|
||||||
|
|
||||||
instance (KnownSymbol sym, HasJQ sublayout)
|
instance (KnownSymbol sym, HasJQ sublayout)
|
||||||
=> HasJQ (Authorization sym a :> sublayout) where
|
=> HasJQ (Authorization sym a :> sublayout) where
|
||||||
type JQ' (Authorization sym a :> sublayout) = JQ' sublayout
|
type JQ (Authorization sym a :> sublayout) = JQ sublayout
|
||||||
|
|
||||||
jqueryFor Proxy req = jqueryFor (Proxy :: Proxy sublayout) $
|
jqueryFor Proxy req = jqueryFor (Proxy :: Proxy sublayout) $
|
||||||
req & reqHeaders <>~ [ ReplaceHeaderArg "Authorization" $
|
req & reqHeaders <>~ [ ReplaceHeaderArg "Authorization" $
|
||||||
|
@ -35,7 +35,7 @@ data MyLovelyHorse a
|
||||||
|
|
||||||
instance (HasJQ sublayout)
|
instance (HasJQ sublayout)
|
||||||
=> HasJQ (MyLovelyHorse a :> sublayout) where
|
=> HasJQ (MyLovelyHorse a :> sublayout) where
|
||||||
type JQ' (MyLovelyHorse a :> sublayout) = JQ' sublayout
|
type JQ (MyLovelyHorse a :> sublayout) = JQ sublayout
|
||||||
|
|
||||||
jqueryFor Proxy req = jqueryFor (Proxy :: Proxy sublayout) $
|
jqueryFor Proxy req = jqueryFor (Proxy :: Proxy sublayout) $
|
||||||
req & reqHeaders <>~ [ ReplaceHeaderArg "X-MyLovelyHorse" tpl ]
|
req & reqHeaders <>~ [ ReplaceHeaderArg "X-MyLovelyHorse" tpl ]
|
||||||
|
@ -47,7 +47,7 @@ data WhatsForDinner a
|
||||||
|
|
||||||
instance (HasJQ sublayout)
|
instance (HasJQ sublayout)
|
||||||
=> HasJQ (WhatsForDinner a :> sublayout) where
|
=> HasJQ (WhatsForDinner a :> sublayout) where
|
||||||
type JQ' (WhatsForDinner a :> sublayout) = JQ' sublayout
|
type JQ (WhatsForDinner a :> sublayout) = JQ sublayout
|
||||||
|
|
||||||
jqueryFor Proxy req = jqueryFor (Proxy :: Proxy sublayout) $
|
jqueryFor Proxy req = jqueryFor (Proxy :: Proxy sublayout) $
|
||||||
req & reqHeaders <>~ [ ReplaceHeaderArg "X-WhatsForDinner" tpl ]
|
req & reqHeaders <>~ [ ReplaceHeaderArg "X-WhatsForDinner" tpl ]
|
||||||
|
|
|
@ -20,7 +20,7 @@ library
|
||||||
exposed-modules: Servant.HTML.Lucid
|
exposed-modules: Servant.HTML.Lucid
|
||||||
-- other-modules:
|
-- other-modules:
|
||||||
-- other-extensions:
|
-- other-extensions:
|
||||||
build-depends: base >=4.7 && <4.8
|
build-depends: base >=4.7 && <5
|
||||||
, http-media
|
, http-media
|
||||||
, lucid
|
, lucid
|
||||||
, servant
|
, servant
|
||||||
|
|
|
@ -3,7 +3,6 @@
|
||||||
{-# LANGUAGE FlexibleInstances #-}
|
{-# LANGUAGE FlexibleInstances #-}
|
||||||
{-# LANGUAGE FunctionalDependencies #-}
|
{-# LANGUAGE FunctionalDependencies #-}
|
||||||
{-# LANGUAGE MultiParamTypeClasses #-}
|
{-# LANGUAGE MultiParamTypeClasses #-}
|
||||||
{-# LANGUAGE OverlappingInstances #-}
|
|
||||||
{-# LANGUAGE RankNTypes #-}
|
{-# LANGUAGE RankNTypes #-}
|
||||||
{-# LANGUAGE ScopedTypeVariables #-}
|
{-# LANGUAGE ScopedTypeVariables #-}
|
||||||
{-# LANGUAGE TypeFamilies #-}
|
{-# LANGUAGE TypeFamilies #-}
|
||||||
|
@ -11,7 +10,9 @@
|
||||||
{-# LANGUAGE UndecidableInstances #-}
|
{-# LANGUAGE UndecidableInstances #-}
|
||||||
module Servant.Server.Internal.Enter where
|
module Servant.Server.Internal.Enter where
|
||||||
|
|
||||||
|
#if !MIN_VERSION_base(4,8,0)
|
||||||
import Control.Applicative
|
import Control.Applicative
|
||||||
|
#endif
|
||||||
import qualified Control.Category as C
|
import qualified Control.Category as C
|
||||||
#if MIN_VERSION_mtl(2,2,1)
|
#if MIN_VERSION_mtl(2,2,1)
|
||||||
import Control.Monad.Except
|
import Control.Monad.Except
|
||||||
|
|
|
@ -54,7 +54,6 @@ module Servant.API (
|
||||||
-- | Type-safe internal URIs
|
-- | Type-safe internal URIs
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Data.Proxy (Proxy (..))
|
|
||||||
import Servant.API.Alternative ((:<|>) (..))
|
import Servant.API.Alternative ((:<|>) (..))
|
||||||
import Servant.API.Capture (Capture)
|
import Servant.API.Capture (Capture)
|
||||||
import Servant.API.ContentTypes (Accept (..), FormUrlEncoded,
|
import Servant.API.ContentTypes (Accept (..), FormUrlEncoded,
|
||||||
|
|
Loading…
Add table
Reference in a new issue