[Git][ghc/ghc][master] winio: Fix unused variables warnings

Marge Bot gitlab at gitlab.haskell.org
Sat Oct 31 13:27:02 UTC 2020



 Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
cb1f755c by Tamar Christina at 2020-10-31T09:26:56-04:00
winio: Fix unused variables warnings

- - - - -


3 changed files:

- libraries/base/GHC/Event/Windows.hsc
- rts/win32/AsyncWinIO.c
- rts/win32/AsyncWinIO.h


Changes:

=====================================
libraries/base/GHC/Event/Windows.hsc
=====================================
@@ -289,8 +289,8 @@ foreign import ccall safe "registerIOCPHandle"
   registerIOCPHandle :: FFI.IOCP -> IO ()
 
 foreign import ccall safe "registerAlertableWait"
--- (bool has_timeout, DWORD mssec, uint64_t num_req, bool pending_service);
-  c_registerAlertableWait :: Bool -> DWORD -> Word64 -> Bool -> IO ()
+-- (bool has_timeout, DWORD mssec);
+  c_registerAlertableWait :: Bool -> DWORD  -> IO ()
 
 foreign import ccall safe "getOverlappedEntries"
   getOverlappedEntries :: Ptr DWORD -> IO (Ptr OVERLAPPED_ENTRY)
@@ -674,12 +674,11 @@ withOverlappedEx mgr fname h offset startCB completionCB = do
                              debugIO $ "-1.. " ++ show reqs1 ++ " requests queued after error."
                              completionCB' (fromIntegral nerr) 0
                         when (not threadedIOMgr) $
-                          do num_remaining <- outstandingRequests
-                             -- Run timeouts. This way if we canceled the last
+                          do -- Run timeouts. This way if we canceled the last
                              -- IO Request and have no timer events waiting we
                              -- can go into an unbounded alertable wait.
                              delay <- runExpiredTimeouts mgr
-                             registerAlertableWait delay num_remaining True
+                             registerAlertableWait delay
                         return $ IOFailed Nothing
         let runner = do debugIO $ (dbgMsg ":: waiting ") ++ " | "  ++ show lpol
                         res <- readIOPort signal `catch` cancel
@@ -1127,23 +1126,20 @@ processRemoteCompletion = do
     -- Process available completions
     _ <- processCompletion mngr n delay
 
-    num_left <- outstandingRequests
-
     -- Update and potentially wake up IO Manager
     -- This call will unblock the non-threaded I/O manager.  After this it is no
     -- longer safe to use `entries` nor `completed` as they can now be modified
     -- by the C thread.
-    registerAlertableWait delay num_left False
+    registerAlertableWait delay
 
     debugIO "processRemoteCompletion :: done ()"
     return ()
 
-registerAlertableWait :: Maybe Seconds -> Word64 -> Bool -> IO ()
-registerAlertableWait Nothing num_reqs pending_service =
-  c_registerAlertableWait False 0 num_reqs pending_service
-registerAlertableWait (Just delay) num_reqs pending_service =
+registerAlertableWait :: Maybe Seconds  -> IO ()
+registerAlertableWait Nothing =
+  c_registerAlertableWait False 0
+registerAlertableWait (Just delay) =
   c_registerAlertableWait True (secondsToMilliSeconds delay)
-                          num_reqs pending_service
 
 -- | Event loop for the Threaded I/O manager.  The one for the non-threaded
 -- I/O manager is in AsyncWinIO.c in the rts.


=====================================
rts/win32/AsyncWinIO.c
=====================================
@@ -322,17 +322,10 @@ void completeSynchronousRequest (void)
    * MSSEC is the maximum amount of time in milliseconds that an alertable wait
       should be done for before the haskell side requested to be notified of progress.
    * NUM_REQ is the total overall number of outstanding I/O requests.
-   * pending_service indicates that there might be still a outstanding service
-     request queued and therefore we shouldn't unblock the runner quite yet.
-
-   `pending_service` is needed in case we cancel an IO operation. We don't want this
-   to result in two processRemoteCompletion threads being queued. As this is both harder
-   to reason about and bad for performance. So we only reset outstanding_service_requests
-   if no service is pending.
 
    */
 
-void registerAlertableWait (bool has_timeout, DWORD mssec, uint64_t num_req, bool pending_service)
+void registerAlertableWait (bool has_timeout, DWORD mssec)
 {
   ASSERT(completionPortHandle != INVALID_HANDLE_VALUE);
   AcquireSRWLockExclusive (&wio_runner_lock);


=====================================
rts/win32/AsyncWinIO.h
=====================================
@@ -18,7 +18,7 @@ extern bool startupAsyncWinIO(void);
 extern void shutdownAsyncWinIO(bool wait_threads);
 extern void awaitAsyncRequests(bool wait);
 extern void registerIOCPHandle (HANDLE port);
-extern void registerAlertableWait (bool has_timeout, DWORD mssec, uint64_t num_req, bool service_pending);
+extern void registerAlertableWait (bool has_timeout, DWORD mssec);
 
 extern OVERLAPPED_ENTRY* getOverlappedEntries (uint32_t *num);
 extern void completeSynchronousRequest (void);



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cb1f755c6fb77f140aee11fdc7b4da04dd5dcd02

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/cb1f755c6fb77f140aee11fdc7b4da04dd5dcd02
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20201031/c17281e7/attachment-0001.html>


More information about the ghc-commits mailing list