grpc-haskell-core: -Wall -Werror and fix warnings

This commit is contained in:
Joel Stanley 2021-06-29 11:02:49 -05:00
parent c76656f9c4
commit 179131a474
No known key found for this signature in database
GPG Key ID: F368244CDC80C97F
9 changed files with 11 additions and 15 deletions

View File

@ -68,7 +68,7 @@ library
, grpc/slice.h
build-tools: c2hs
default-language: Haskell2010
ghc-options: -Wall -fwarn-incomplete-patterns -fno-warn-unused-do-bind
ghc-options: -Wall -Werror -fwarn-incomplete-patterns -fno-warn-unused-do-bind
include-dirs: include
hs-source-dirs: src
default-extensions: CPP
@ -103,7 +103,7 @@ test-suite tests
LowLevelTests.Op,
UnsafeTests
default-language: Haskell2010
ghc-options: -Wall -fwarn-incomplete-patterns -fno-warn-unused-do-bind -g -threaded -rtsopts
ghc-options: -Wall -Werror -fwarn-incomplete-patterns -fno-warn-unused-do-bind -g -threaded -rtsopts
hs-source-dirs: tests
main-is: Properties.hs
type: exitcode-stdio-1.0

View File

@ -5,7 +5,7 @@
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE KindSignatures #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE NamedFieldPuns #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TypeFamilies #-}
@ -212,8 +212,8 @@ destroyClientCall cc = do
C.grpcCallUnref (unsafeCC cc)
destroyServerCall :: ServerCall a -> IO ()
destroyServerCall sc@ServerCall{ unsafeSC = c, .. } = do
destroyServerCall sc@ServerCall{ unsafeSC } = do
grpcDebug "destroyServerCall(R): entered."
debugServerCall sc
grpcDebug $ "Destroying server-side call object: " ++ show c
C.grpcCallUnref c
grpcDebug $ "Destroying server-side call object: " ++ show unsafeSC
C.grpcCallUnref unsafeSC

View File

@ -71,7 +71,7 @@ createCompletionQueue _ = do
-- Throws 'CallError' if 'grpcCallStartBatch' returns a non-OK code.
startBatch :: CompletionQueue -> C.Call -> C.OpArray -> Int -> C.Tag
-> IO (Either GRPCIOError ())
startBatch cq@CompletionQueue{..} call opArray opArraySize tag =
startBatch cq call opArray opArraySize tag =
withPermission Push cq $ fmap throwIfCallError $ do
grpcDebug $ "startBatch: calling grpc_call_start_batch with pointers: "
++ show call ++ " " ++ show opArray

View File

@ -104,7 +104,7 @@ withPermission op cq act = bracket acquire release $ \gotResource ->
-- 'serverRequestCall', this will block forever unless a timeout is given.
pluck :: CompletionQueue -> C.Tag -> Maybe TimeoutSeconds
-> IO (Either GRPCIOError ())
pluck cq@CompletionQueue{..} tag mwait = do
pluck cq tag mwait = do
grpcDebug $ "pluck: called with tag=" ++ show tag ++ ",mwait=" ++ show mwait
withPermission Pluck cq $ pluck' cq tag mwait

View File

@ -7,7 +7,6 @@ import Control.Exception (bracket)
import Control.Monad
import Data.ByteString (ByteString, useAsCString)
import Data.Semigroup (Semigroup)
import Foreign.C.String (CString, peekCString)
import Foreign.Marshal.Alloc (free)

View File

@ -12,7 +12,6 @@ import Data.Function (on)
import Data.ByteString (ByteString, useAsCString,
useAsCStringLen)
import Data.List (sortBy, groupBy)
import Data.Semigroup (Semigroup((<>)))
import qualified Data.SortedList as SL
import qualified Data.Map.Strict as M
import Data.Ord (comparing)

View File

@ -22,7 +22,6 @@ import Data.List (find)
import qualified Data.Map.Strict as M
import qualified Data.Set as S
import GHC.Exts (fromList, toList)
import Network.GRPC.Unsafe.ChannelArgs (Arg(..))
import Network.GRPC.LowLevel
import qualified Network.GRPC.LowLevel.Call.Unregistered as U
import qualified Network.GRPC.LowLevel.Client.Unregistered as U
@ -183,7 +182,7 @@ testSSL =
Nothing)
}
server = TestServer serverConf' $ \s -> do
r <- U.serverHandleNormalCall s mempty $ \U.ServerCall{..} body -> do
r <- U.serverHandleNormalCall s mempty $ \U.ServerCall{} body -> do
body @?= "hi"
return ("reply test", mempty, StatusOk, "")
r @?= Right ()
@ -282,7 +281,7 @@ testAuthMetadataTransfer =
serverProcessor)
}
server = TestServer serverConf' $ \s -> do
r <- U.serverHandleNormalCall s mempty $ \U.ServerCall{..} body -> do
r <- U.serverHandleNormalCall s mempty $ \U.ServerCall{} body -> do
body @?= "hi"
return ("reply test", mempty, StatusOk, "")
r @?= Right ()

View File

@ -27,7 +27,7 @@ testCancelFromServer =
testCase "Client/Server - client receives server cancellation" $
runSerialTest $ \grpc ->
withClientServerUnaryCall grpc $
\(Client {..}, Server {..}, ClientCall {..}, sc@ServerCall {..}) -> do
\(Client {..}, Server {}, ClientCall {..}, sc@ServerCall {}) -> do
serverCallCancel sc StatusPermissionDenied "TestStatus"
clientRes <- runOps unsafeCC clientCQ clientRecvOps
case clientRes of

View File

@ -20,7 +20,6 @@ import Network.GRPC.Unsafe.Slice
import Network.GRPC.Unsafe.Time
import System.Clock
import Test.QuickCheck.Gen
import qualified Test.QuickCheck.Property as QC
import Test.Tasty
import Test.Tasty.HUnit as HU (testCase, (@?=))
import Test.Tasty.QuickCheck as QC