More Werror fixes
This commit is contained in:
parent
3df1421678
commit
fcb0a727b4
3 changed files with 5 additions and 6 deletions
|
@ -23,7 +23,6 @@ module Servant.JS.Internal
|
||||||
, HasForeignType(..)
|
, HasForeignType(..)
|
||||||
, GenerateList(..)
|
, GenerateList(..)
|
||||||
, NoTypes
|
, NoTypes
|
||||||
, HeaderArg
|
|
||||||
, ArgType(..)
|
, ArgType(..)
|
||||||
, HeaderArg(..)
|
, HeaderArg(..)
|
||||||
, QueryArg(..)
|
, QueryArg(..)
|
||||||
|
@ -47,7 +46,7 @@ module Servant.JS.Internal
|
||||||
, Header
|
, Header
|
||||||
) where
|
) where
|
||||||
|
|
||||||
import Control.Lens hiding (List)
|
import Control.Lens (makePrisms, makeLenses, Getter, (&), (<>~), (.~), (%~))
|
||||||
import qualified Data.CharSet as Set
|
import qualified Data.CharSet as Set
|
||||||
import qualified Data.CharSet.Unicode.Category as Set
|
import qualified Data.CharSet.Unicode.Category as Set
|
||||||
import Data.Monoid
|
import Data.Monoid
|
||||||
|
|
|
@ -3,7 +3,7 @@
|
||||||
module Servant.Server.Internal.ContextSpec (spec) where
|
module Servant.Server.Internal.ContextSpec (spec) where
|
||||||
|
|
||||||
import Data.Proxy (Proxy (..))
|
import Data.Proxy (Proxy (..))
|
||||||
import Test.Hspec (Spec, describe, it, shouldBe, pending, context)
|
import Test.Hspec (Spec, describe, it, shouldBe, context)
|
||||||
import Test.ShouldNotTypecheck (shouldNotTypecheck)
|
import Test.ShouldNotTypecheck (shouldNotTypecheck)
|
||||||
|
|
||||||
import Servant.API
|
import Servant.API
|
||||||
|
@ -35,8 +35,8 @@ spec = do
|
||||||
show (Just cxt) `shouldBe` "Just ('a' :. True :. EmptyContext)"
|
show (Just cxt) `shouldBe` "Just ('a' :. True :. EmptyContext)"
|
||||||
|
|
||||||
it "works with operators" $ do
|
it "works with operators" $ do
|
||||||
let cxt = (1 :. 'a' :. EmptyContext) :<|> ('b' :. True :. EmptyContext)
|
let cxt' = ((1 :: Int) :. 'a' :. EmptyContext) :<|> ('b' :. True :. EmptyContext)
|
||||||
show cxt `shouldBe` "(1 :. 'a' :. EmptyContext) :<|> ('b' :. True :. EmptyContext)"
|
show cxt' `shouldBe` "(1 :. 'a' :. EmptyContext) :<|> ('b' :. True :. EmptyContext)"
|
||||||
|
|
||||||
describe "descendIntoNamedContext" $ do
|
describe "descendIntoNamedContext" $ do
|
||||||
let cxt :: Context [Char, NamedContext "sub" '[Char]]
|
let cxt :: Context [Char, NamedContext "sub" '[Char]]
|
||||||
|
|
|
@ -36,7 +36,7 @@ instance (HasContextEntry context String, HasServer subApi context) =>
|
||||||
subProxy :: Proxy subApi
|
subProxy :: Proxy subApi
|
||||||
subProxy = Proxy
|
subProxy = Proxy
|
||||||
|
|
||||||
inject context f = f (getContextEntry context)
|
inject ctx f = f (getContextEntry ctx)
|
||||||
|
|
||||||
data InjectIntoContext
|
data InjectIntoContext
|
||||||
|
|
||||||
|
|
Loading…
Reference in a new issue