summaryrefslogtreecommitdiff
path: root/ghc/lib/concurrent/Parallel.lhs
diff options
context:
space:
mode:
authorsimonpj <unknown>1996-12-19 18:36:20 +0000
committersimonpj <unknown>1996-12-19 18:36:20 +0000
commitbb521c6bba76f19474f12195b990b29eda66a4e8 (patch)
treefecb11771c7d9f25634e6bd5857c991686707b8d /ghc/lib/concurrent/Parallel.lhs
parentc3e7e772db4fbc7171de7b7e98d578ab9cff167c (diff)
downloadhaskell-bb521c6bba76f19474f12195b990b29eda66a4e8.tar.gz
[project @ 1996-12-19 18:35:23 by simonpj]
Adding and removing files
Diffstat (limited to 'ghc/lib/concurrent/Parallel.lhs')
-rw-r--r--ghc/lib/concurrent/Parallel.lhs32
1 files changed, 32 insertions, 0 deletions
diff --git a/ghc/lib/concurrent/Parallel.lhs b/ghc/lib/concurrent/Parallel.lhs
new file mode 100644
index 0000000000..79609ad209
--- /dev/null
+++ b/ghc/lib/concurrent/Parallel.lhs
@@ -0,0 +1,32 @@
+%
+% (c) The GRASP/AQUA Project, Glasgow University, 1995-1996
+%
+\section[Parallel]{Parallel Constructs}
+
+\begin{code}
+module Parallel (par, seq -- re-exported
+#if defined(__GRANSIM__)
+ , parGlobal, parLocal, parAt, parAtForNow
+#endif
+ ) where
+
+import ConcBase ( par )
+
+#if defined(__GRANSIM__)
+
+{-# INLINE parGlobal #-}
+parGlobal :: Int -> Int -> Int -> Int -> a -> b -> b
+parLocal :: Int -> Int -> Int -> Int -> a -> b -> b
+parAt :: Int -> Int -> Int -> Int -> a -> b -> c -> c
+parAtForNow :: Int -> Int -> Int -> Int -> a -> b -> c -> c
+
+parGlobal (I# w) (I# g) (I# s) (I# p) x y = case (parGlobal# x w g s p y) of { 0# -> parError; _ -> y }
+parLocal (I# w) (I# g) (I# s) (I# p) x y = case (parLocal# x w g s p y) of { 0# -> parError; _ -> y }
+
+parAt (I# w) (I# g) (I# s) (I# p) v x y = case (parAt# x v w g s p y) of { 0# -> parError; _ -> y }
+parAtForNow (I# w) (I# g) (I# s) (I# p) v x y = case (parAtForNow# x v w g s p y) of { 0# -> parError; _ -> y }
+
+#endif
+
+-- Maybe parIO and the like could be added here later.
+\end{code}