From cc35bcbaa168201f817e3f443c8730af6c70bb3f Mon Sep 17 00:00:00 2001
From: sof <unknown>
Date: Fri, 14 Mar 1997 05:19:03 +0000
Subject: [PATCH] [project @ 1997-03-14 05:19:02 by sof] Import changes

---
 ghc/lib/concurrent/Merge.lhs    | 6 ++++--
 ghc/lib/concurrent/Parallel.lhs | 3 +++
 2 files changed, 7 insertions(+), 2 deletions(-)

diff --git a/ghc/lib/concurrent/Merge.lhs b/ghc/lib/concurrent/Merge.lhs
index 322d2aa2d108..f95678edd1c2 100644
--- a/ghc/lib/concurrent/Merge.lhs
+++ b/ghc/lib/concurrent/Merge.lhs
@@ -15,7 +15,9 @@ module Merge
 	) where
 
 import Semaphore
-
+import ConcBase
+import STBase  ( unsafeInterleavePrimIO )
+import IOBase
 
 max_buff_size = 1
 
@@ -64,7 +66,7 @@ suckIO branches_running buff@(tail_list,e) vs
 		unsafeInterleavePrimIO ( ioToPrimIO $
 			takeMVar next_node  >>= \ x ->
 			signalQSem e	    >>
-			return x)	    `stThen` \ next_node_val ->
+			return x)	    `thenIO_Prim` \ next_node_val ->
 		putMVar node (x:next_node_val)   >>
 		putMVar tail_list next_node 	 >>
 		suckIO branches_running buff xs
diff --git a/ghc/lib/concurrent/Parallel.lhs b/ghc/lib/concurrent/Parallel.lhs
index 79609ad209b9..2c068e646276 100644
--- a/ghc/lib/concurrent/Parallel.lhs
+++ b/ghc/lib/concurrent/Parallel.lhs
@@ -13,6 +13,9 @@ module Parallel (par, seq -- re-exported
 import ConcBase	( par )
 
 #if defined(__GRANSIM__)
+import PrelBase
+import GHCerr   ( parError )
+import GHC      ( parGlobal#, parLocal#, parAt#, parAtForNow# )
 
 {-# INLINE parGlobal #-}
 parGlobal   :: Int -> Int -> Int -> Int -> a -> b -> b
-- 
GitLab