Skip to content
Snippets Groups Projects
Commit 24bb1c55 authored by sof's avatar sof
Browse files

[project @ 1997-10-21 20:39:15 by sof]

Parallel Haskell changes(hwloidl)
parent 5d927828
No related merge requests found
......@@ -6,7 +6,7 @@
\begin{code}
module Parallel (par, seq -- re-exported
#if defined(__GRANSIM__)
, parGlobal, parLocal, parAt, parAtForNow
, parGlobal, parLocal, parAt, parAtAbs, parAtRel, parAtForNow
#endif
) where
......@@ -15,18 +15,27 @@ import ConcBase ( par )
#if defined(__GRANSIM__)
import PrelBase
import GHCerr ( parError )
import GHC ( parGlobal#, parLocal#, parAt#, parAtForNow# )
import GHC ( parGlobal#, parLocal#, parAt#, parAtAbs#, parAtRel#, parAtForNow# )
{-# INLINE parGlobal #-}
{-# INLINE parLocal #-}
{-# INLINE parAt #-}
{-# INLINE parAtAbs #-}
{-# INLINE parAtRel #-}
{-# INLINE parAtForNow #-}
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
parAtAbs :: Int -> Int -> Int -> Int -> Int -> a -> b -> b
parAtRel :: Int -> Int -> Int -> Int -> Int -> a -> b -> b
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 }
parAtAbs (I# w) (I# g) (I# s) (I# p) (I# q) x y = case (parAtAbs# x q w g s p y) of { 0# -> parError; _ -> y }
parAtRel (I# w) (I# g) (I# s) (I# p) (I# q) x y = case (parAtRel# x q 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
......
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