More Werror fixes

This commit is contained in:
Julian K. Arni 2016-03-19 10:08:48 +01:00
parent 3df1421678
commit fcb0a727b4
3 changed files with 5 additions and 6 deletions

View file

@ -23,7 +23,6 @@ module Servant.JS.Internal
, HasForeignType(..)
, GenerateList(..)
, NoTypes
, HeaderArg
, ArgType(..)
, HeaderArg(..)
, QueryArg(..)
@ -47,7 +46,7 @@ module Servant.JS.Internal
, Header
) where
import Control.Lens hiding (List)
import Control.Lens (makePrisms, makeLenses, Getter, (&), (<>~), (.~), (%~))
import qualified Data.CharSet as Set
import qualified Data.CharSet.Unicode.Category as Set
import Data.Monoid

View file

@ -3,7 +3,7 @@
module Servant.Server.Internal.ContextSpec (spec) where
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 Servant.API
@ -35,8 +35,8 @@ spec = do
show (Just cxt) `shouldBe` "Just ('a' :. True :. EmptyContext)"
it "works with operators" $ do
let cxt = (1 :. 'a' :. EmptyContext) :<|> ('b' :. True :. EmptyContext)
show cxt `shouldBe` "(1 :. 'a' :. EmptyContext) :<|> ('b' :. True :. EmptyContext)"
let cxt' = ((1 :: Int) :. 'a' :. EmptyContext) :<|> ('b' :. True :. EmptyContext)
show cxt' `shouldBe` "(1 :. 'a' :. EmptyContext) :<|> ('b' :. True :. EmptyContext)"
describe "descendIntoNamedContext" $ do
let cxt :: Context [Char, NamedContext "sub" '[Char]]

View file

@ -36,7 +36,7 @@ instance (HasContextEntry context String, HasServer subApi context) =>
subProxy :: Proxy subApi
subProxy = Proxy
inject context f = f (getContextEntry context)
inject ctx f = f (getContextEntry ctx)
data InjectIntoContext