Skip to content
Snippets Groups Projects
Commit 7fd3a472 authored by Ryan Scott's avatar Ryan Scott
Browse files

Adapt to forkOn#'s new type

parent 3b96c7f8
No related branches found
No related tags found
No related merge requests found
diff --git a/Control/Concurrent/Async.hs b/Control/Concurrent/Async.hs diff --git a/Control/Concurrent/Async.hs b/Control/Concurrent/Async.hs
index 064a262..f962a61 100644 index 064a262..16c772c 100644
--- a/Control/Concurrent/Async.hs --- a/Control/Concurrent/Async.hs
+++ b/Control/Concurrent/Async.hs +++ b/Control/Concurrent/Async.hs
@@ -959,7 +959,13 @@ tryAll = try @@ -959,9 +959,21 @@ tryAll = try
{-# INLINE rawForkIO #-} {-# INLINE rawForkIO #-}
rawForkIO :: IO () -> IO ThreadId rawForkIO :: IO () -> IO ThreadId
rawForkIO action = IO $ \ s -> rawForkIO action = IO $ \ s ->
...@@ -17,3 +17,12 @@ index 064a262..f962a61 100644 ...@@ -17,3 +17,12 @@ index 064a262..f962a61 100644
{-# INLINE rawForkOn #-} {-# INLINE rawForkOn #-}
rawForkOn :: Int -> IO () -> IO ThreadId rawForkOn :: Int -> IO () -> IO ThreadId
rawForkOn (I# cpu) action = IO $ \ s ->
- case (forkOn# cpu action s) of (# s1, tid #) -> (# s1, ThreadId tid #)
+ case (forkOn# cpu
+#if __GLASGOW_HASKELL__ >= 903
+ (unIO action)
+#else
+ action
+#endif
+ s) of (# s1, tid #) -> (# s1, ThreadId tid #)
diff --git a/Control/Concurrent/Async/Pool/Async.hs b/Control/Concurrent/Async/Pool/Async.hs diff --git a/Control/Concurrent/Async/Pool/Async.hs b/Control/Concurrent/Async/Pool/Async.hs
index be4e7c0..dda2ea4 100644 index be4e7c0..7d189d1 100644
--- a/Control/Concurrent/Async/Pool/Async.hs --- a/Control/Concurrent/Async/Pool/Async.hs
+++ b/Control/Concurrent/Async/Pool/Async.hs +++ b/Control/Concurrent/Async/Pool/Async.hs
@@ -711,7 +711,13 @@ tryAll = try @@ -711,9 +711,21 @@ tryAll = try
{-# INLINE rawForkIO #-} {-# INLINE rawForkIO #-}
rawForkIO :: IO () -> IO ThreadId rawForkIO :: IO () -> IO ThreadId
rawForkIO action = IO $ \ s -> rawForkIO action = IO $ \ s ->
...@@ -17,3 +17,12 @@ index be4e7c0..dda2ea4 100644 ...@@ -17,3 +17,12 @@ index be4e7c0..dda2ea4 100644
{-# INLINE rawForkOn #-} {-# INLINE rawForkOn #-}
rawForkOn :: Int -> IO () -> IO ThreadId rawForkOn :: Int -> IO () -> IO ThreadId
rawForkOn (I# cpu) action = IO $ \ s ->
- case (forkOn# cpu action s) of (# s1, tid #) -> (# s1, ThreadId tid #)
+ case (forkOn# cpu
+#if __GLASGOW_HASKELL__ >= 903
+ (unIO action)
+#else
+ action
+#endif
+ s) of (# s1, tid #) -> (# s1, ThreadId tid #)
diff --git a/vendor/Control/Concurrent/Async.hs b/vendor/Control/Concurrent/Async.hs diff --git a/vendor/Control/Concurrent/Async.hs b/vendor/Control/Concurrent/Async.hs
index 81c3e69..d11e944 100644 index 81c3e69..199c5bd 100644
--- a/vendor/Control/Concurrent/Async.hs --- a/vendor/Control/Concurrent/Async.hs
+++ b/vendor/Control/Concurrent/Async.hs +++ b/vendor/Control/Concurrent/Async.hs
@@ -862,7 +862,13 @@ tryAll = try @@ -862,9 +862,21 @@ tryAll = try
{-# INLINE rawForkIO #-} {-# INLINE rawForkIO #-}
rawForkIO :: IO () -> IO ThreadId rawForkIO :: IO () -> IO ThreadId
rawForkIO action = IO $ \ s -> rawForkIO action = IO $ \ s ->
...@@ -17,3 +17,12 @@ index 81c3e69..d11e944 100644 ...@@ -17,3 +17,12 @@ index 81c3e69..d11e944 100644
{-# INLINE rawForkOn #-} {-# INLINE rawForkOn #-}
rawForkOn :: Int -> IO () -> IO ThreadId rawForkOn :: Int -> IO () -> IO ThreadId
rawForkOn (I# cpu) action = IO $ \ s ->
- case (forkOn# cpu action s) of (# s1, tid #) -> (# s1, ThreadId tid #)
+ case (forkOn# cpu
+#if __GLASGOW_HASKELL__ >= 903
+ (unIO action)
+#else
+ action
+#endif
+ s) of (# s1, tid #) -> (# s1, ThreadId tid #)
...@@ -12,10 +12,10 @@ index f0a3585..79b71b1 100644 ...@@ -12,10 +12,10 @@ index f0a3585..79b71b1 100644
import GHC.IO.Exception import GHC.IO.Exception
import Control.Exception import Control.Exception
diff --git a/hspec-core/vendor/Control/Concurrent/Async.hs b/hspec-core/vendor/Control/Concurrent/Async.hs diff --git a/hspec-core/vendor/Control/Concurrent/Async.hs b/hspec-core/vendor/Control/Concurrent/Async.hs
index d968934..c552c11 100644 index d968934..4aa8c90 100644
--- a/hspec-core/vendor/Control/Concurrent/Async.hs --- a/hspec-core/vendor/Control/Concurrent/Async.hs
+++ b/hspec-core/vendor/Control/Concurrent/Async.hs +++ b/hspec-core/vendor/Control/Concurrent/Async.hs
@@ -862,7 +862,13 @@ tryAll = try @@ -862,9 +862,21 @@ tryAll = try
{-# INLINE rawForkIO #-} {-# INLINE rawForkIO #-}
rawForkIO :: IO () -> IO ThreadId rawForkIO :: IO () -> IO ThreadId
rawForkIO action = IO $ \ s -> rawForkIO action = IO $ \ s ->
...@@ -30,6 +30,15 @@ index d968934..c552c11 100644 ...@@ -30,6 +30,15 @@ index d968934..c552c11 100644
{-# INLINE rawForkOn #-} {-# INLINE rawForkOn #-}
rawForkOn :: Int -> IO () -> IO ThreadId rawForkOn :: Int -> IO () -> IO ThreadId
rawForkOn (I# cpu) action = IO $ \ s ->
- case (forkOn# cpu action s) of (# s1, tid #) -> (# s1, ThreadId tid #)
+ case (forkOn# cpu
+#if __GLASGOW_HASKELL__ >= 903
+ (unIO action)
+#else
+ action
+#endif
+ s) of (# s1, tid #) -> (# s1, ThreadId tid #)
diff --git a/hspec-discover/src/Test/Hspec/Discover/Run.hs b/hspec-discover/src/Test/Hspec/Discover/Run.hs diff --git a/hspec-discover/src/Test/Hspec/Discover/Run.hs b/hspec-discover/src/Test/Hspec/Discover/Run.hs
index f95879b..2f87b9e 100644 index f95879b..2f87b9e 100644
--- a/hspec-discover/src/Test/Hspec/Discover/Run.hs --- a/hspec-discover/src/Test/Hspec/Discover/Run.hs
......
diff --git a/Control/Concurrent/Raw.hs b/Control/Concurrent/Raw.hs diff --git a/Control/Concurrent/Raw.hs b/Control/Concurrent/Raw.hs
index 58dbf8e..02b7c69 100644 index 58dbf8e..729bd2c 100644
--- a/Control/Concurrent/Raw.hs --- a/Control/Concurrent/Raw.hs
+++ b/Control/Concurrent/Raw.hs +++ b/Control/Concurrent/Raw.hs
@@ -1,3 +1,4 @@ @@ -1,3 +1,4 @@
...@@ -7,7 +7,7 @@ index 58dbf8e..02b7c69 100644 ...@@ -7,7 +7,7 @@ index 58dbf8e..02b7c69 100644
{-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples #-} {-# LANGUAGE NoImplicitPrelude, MagicHash, UnboxedTuples #-}
module Control.Concurrent.Raw ( rawForkIO, rawForkOn ) where module Control.Concurrent.Raw ( rawForkIO, rawForkOn ) where
@@ -7,13 +8,23 @@ import GHC.IO ( IO(IO) ) @@ -7,15 +8,31 @@ import GHC.IO ( IO(IO) )
import GHC.Exts ( Int(I#), fork#, forkOn# ) import GHC.Exts ( Int(I#), fork#, forkOn# )
import GHC.Conc ( ThreadId(ThreadId) ) import GHC.Conc ( ThreadId(ThreadId) )
...@@ -32,3 +32,12 @@ index 58dbf8e..02b7c69 100644 ...@@ -32,3 +32,12 @@ index 58dbf8e..02b7c69 100644
{-# INLINE rawForkOn #-} {-# INLINE rawForkOn #-}
rawForkOn :: Int -> IO () -> IO ThreadId rawForkOn :: Int -> IO () -> IO ThreadId
rawForkOn (I# cpu) action = IO $ \s ->
- case (forkOn# cpu action s) of (# s1, tid #) -> (# s1, ThreadId tid #)
+ case (forkOn# cpu
+#if __GLASGOW_HASKELL__ >= 903
+ (unIO action)
+#else
+ action
+#endif
+ s) of (# s1, tid #) -> (# s1, ThreadId tid #)
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment