travis: enable -Wall -Werror

This commit is contained in:
Sönke Hahn 2016-04-18 18:07:23 +08:00
parent 555038cbf4
commit b26bbfccda
21 changed files with 30 additions and 31 deletions

View file

@ -46,15 +46,11 @@ library
, markdown-unlit >= 0.4
, http-client
default-language: Haskell2010
ghc-options: -Wall -Werror -pgmL markdown-unlit
-- to silence aeson-0.10 warnings:
ghc-options: -fno-warn-missing-methods
ghc-options: -fno-warn-name-shadowing
ghc-options: -Wall -pgmL markdown-unlit
test-suite spec
type: exitcode-stdio-1.0
ghc-options:
-Wall -fno-warn-name-shadowing -fno-warn-missing-signatures
ghc-options: -Wall
default-language: Haskell2010
hs-source-dirs: test
main-is: Spec.hs

View file

@ -31,3 +31,4 @@ library
hs-source-dirs: src
default-language: Haskell2010
include-dirs: include
ghc-options: -Wall

View file

@ -28,3 +28,4 @@ library
hs-source-dirs: src
default-language: Haskell2010
include-dirs: include
ghc-options: -Wall

View file

@ -60,8 +60,7 @@ library
test-suite spec
type: exitcode-stdio-1.0
ghc-options:
-Wall -fno-warn-name-shadowing -fno-warn-missing-signatures
ghc-options: -Wall
default-language: Haskell2010
hs-source-dirs: test
main-is: Spec.hs

View file

@ -28,7 +28,7 @@ import Control.Applicative ((<$>))
import Control.Arrow (left)
import Control.Concurrent (forkIO, killThread, ThreadId)
import Control.Exception (bracket)
import Control.Monad.Trans.Except (ExceptT, throwE, runExceptT)
import Control.Monad.Trans.Except (throwE, runExceptT)
import Data.Aeson
import qualified Data.ByteString.Lazy as BS
import Data.Char (chr, isPrint)

View file

@ -82,4 +82,3 @@ test-suite spec
, servant-docs
, string-conversions
default-language: Haskell2010

View file

@ -7,7 +7,8 @@
-- arbitrary programming languages.
module Servant.Foreign.Internal where
import Control.Lens hiding (cons, List)
import Control.Lens (makePrisms, makeLenses, Getter, (&), (<>~), (%~),
(.~))
#if !MIN_VERSION_base(4,8,0)
import Data.Monoid
#endif

View file

@ -55,7 +55,7 @@ library
executable counter
main-is: counter.hs
ghc-options: -O2 -Wall
ghc-options: -Wall
hs-source-dirs: examples
if flag(example)

View file

@ -46,7 +46,7 @@ module Servant.JS.Internal
, Header
) where
import Control.Lens hiding (List)
import Control.Lens ((^.))
import qualified Data.CharSet as Set
import qualified Data.CharSet.Unicode.Category as Set
import Data.Monoid

View file

@ -31,3 +31,4 @@ library
hs-source-dirs: src
default-language: Haskell2010
include-dirs: include
ghc-options: -Wall

View file

@ -2,6 +2,9 @@
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-unused-binds #-}
import Data.Aeson
import GHC.Generics
import Network.Wai.Handler.Warp

View file

@ -35,6 +35,7 @@ library
hs-source-dirs: src
default-language: Haskell2010
include-dirs: include
ghc-options: -Wall
executable mock-app
main-is: main.hs
@ -45,11 +46,11 @@ executable mock-app
buildable: True
else
buildable: False
ghc-options: -Wall
test-suite spec
type: exitcode-stdio-1.0
ghc-options:
-Wall -fno-warn-name-shadowing
ghc-options: -Wall
default-language: Haskell2010
hs-source-dirs: test
main-is: Spec.hs

View file

@ -94,8 +94,7 @@ executable greet
test-suite spec
type: exitcode-stdio-1.0
ghc-options:
-Wall -fno-warn-name-shadowing -fno-warn-missing-signatures
ghc-options: -Wall
default-language: Haskell2010
hs-source-dirs: test
main-is: Spec.hs
@ -147,5 +146,5 @@ test-suite doctests
main-is: test/Doctests.hs
buildable: True
default-language: Haskell2010
ghc-options: -threaded
ghc-options: -Wall -threaded
include-dirs: include

View file

@ -1,9 +1,9 @@
{-# LANGUAGE DataKinds #-}
{-# OPTIONS_GHC -fdefer-type-errors #-}
{-# OPTIONS_GHC -fdefer-type-errors -Wwarn #-}
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
@ -26,16 +26,17 @@ spec = do
shouldNotTypecheck x
context "Show instance" $ do
let cxt = 'a' :. True :. EmptyContext
it "has a Show instance" $ do
let cxt = 'a' :. True :. EmptyContext
show cxt `shouldBe` "'a' :. True :. EmptyContext"
context "bracketing" $ do
it "works" $ do
let cxt = 'a' :. True :. EmptyContext
show (Just cxt) `shouldBe` "Just ('a' :. True :. EmptyContext)"
it "works with operators" $ do
let cxt = (1 :. 'a' :. EmptyContext) :<|> ('b' :. True :. EmptyContext)
let cxt = ((1 :: Integer) :. 'a' :. EmptyContext) :<|> ('b' :. True :. EmptyContext)
show cxt `shouldBe` "(1 :. 'a' :. EmptyContext) :<|> ('b' :. True :. EmptyContext)"
describe "descendIntoNamedContext" $ do

View file

@ -5,7 +5,6 @@ module Servant.Server.Internal.EnterSpec where
import qualified Control.Category as C
import Control.Monad.Reader
import Control.Monad.Trans.Except
import Data.Proxy
import Servant.API
import Servant.Server

View file

@ -16,6 +16,7 @@ import Servant.API
import Servant.Server
import Servant.Server.Internal
spec :: Spec
spec = describe "Servant.Server.Internal.Router" $ do
routerSpec
distributivitySpec

View file

@ -11,7 +11,6 @@ module Servant.Server.StreamingSpec where
import Control.Concurrent
import Control.Exception hiding (Handler)
import Control.Monad.IO.Class
import Control.Monad.Trans.Except
import qualified Data.ByteString as Strict
import qualified Data.ByteString.Lazy as Lazy
import Network.HTTP.Types

View file

@ -5,7 +5,6 @@
module Servant.Server.UsingContextSpec where
import Control.Monad.Trans.Except
import Network.Wai
import Test.Hspec (Spec, describe, it)
import Test.Hspec.Wai

View file

@ -30,12 +30,12 @@ instance (HasContextEntry context String, HasServer subApi context) =>
String -> ServerT subApi m
route Proxy context delayed =
route subProxy context (fmap (inject context) delayed)
route subProxy context (fmap inject delayed)
where
subProxy :: Proxy subApi
subProxy = Proxy
inject context f = f (getContextEntry context)
inject f = f (getContextEntry context)
data InjectIntoContext

View file

@ -89,8 +89,7 @@ library
test-suite spec
type: exitcode-stdio-1.0
ghc-options:
-Wall -fno-warn-name-shadowing -fno-warn-missing-signatures
ghc-options: -Wall
default-language: Haskell2010
hs-source-dirs: test
main-is: Spec.hs
@ -122,5 +121,5 @@ test-suite doctests
main-is: test/Doctests.hs
buildable: True
default-language: Haskell2010
ghc-options: -threaded
ghc-options: -Wall -threaded
include-dirs: include

View file

@ -6,7 +6,7 @@ for package in $(cat sources.txt) doc/tutorial ; do
echo testing $package
pushd $package
tinc
cabal configure --enable-tests --disable-optimization
cabal configure --enable-tests --disable-optimization --ghc-options='-Werror'
cabal build
cabal test
popd