Repository : ssh://darcs.haskell.org//srv/darcs/packages/base

On branch  : master

http://hackage.haskell.org/trac/ghc/changeset/f27a5d2ced7feffad94576ff5904c329f20ebfd9

>---------------------------------------------------------------

commit f27a5d2ced7feffad94576ff5904c329f20ebfd9
Author: Simon Marlow <[email protected]>
Date:   Tue Dec 6 15:09:20 2011 +0000

    add setNumCapabilities :: Int -> IO ()
    
    {- |
    Set the number of Haskell threads that can run truly simultaneously
    (on separate physical processors) at any given time.
    
    GHC notes: in the current implementation, the value may only be
    /increased/, not decreased, by calling 'setNumCapabilities'.  The
    initial value is given by the @+RTS -N@ flag, and the current value
    may be obtained using 'getNumCapabilities'.
    -}

>---------------------------------------------------------------

 GHC/Conc.lhs      |    1 +
 GHC/Conc/Sync.lhs |   16 ++++++++++++++++
 2 files changed, 17 insertions(+), 0 deletions(-)

diff --git a/GHC/Conc.lhs b/GHC/Conc.lhs
index 40ea539..cc6845a 100644
--- a/GHC/Conc.lhs
+++ b/GHC/Conc.lhs
@@ -39,6 +39,7 @@ module GHC.Conc
         , forkOnWithUnmask
         , numCapabilities -- :: Int
         , getNumCapabilities -- :: IO Int
+        , setNumCapabilities -- :: Int -> IO ()
         , numSparks       -- :: IO Int
         , childHandler  -- :: Exception -> IO ()
         , myThreadId    -- :: IO ThreadId
diff --git a/GHC/Conc/Sync.lhs b/GHC/Conc/Sync.lhs
index 521277d..fb81e27 100644
--- a/GHC/Conc/Sync.lhs
+++ b/GHC/Conc/Sync.lhs
@@ -49,6 +49,7 @@ module GHC.Conc.Sync
         , forkOnWithUnmask
         , numCapabilities -- :: Int
         , getNumCapabilities -- :: IO Int
+        , setNumCapabilities -- :: Int -> IO ()
         , numSparks      -- :: IO Int
         , childHandler  -- :: Exception -> IO ()
         , myThreadId    -- :: IO ThreadId
@@ -300,6 +301,21 @@ getNumCapabilities = do
    n <- peek n_capabilities
    return (fromIntegral n)
 
+{- |
+Set the number of Haskell threads that can run truly simultaneously
+(on separate physical processors) at any given time.
+
+GHC notes: in the current implementation, the value may only be
+/increased/, not decreased, by calling 'setNumCapabilities'.  The
+initial value is given by the @+RTS -N@ flag, and the current value
+may be obtained using 'getNumCapabilities'.
+-}
+setNumCapabilities :: Int -> IO ()
+setNumCapabilities i = c_setNumCapabilities (fromIntegral i)
+
+foreign import ccall safe "setNumCapabilities"
+  c_setNumCapabilities :: CUInt -> IO ()
+
 -- | Returns the number of sparks currently in the local spark pool
 numSparks :: IO Int
 numSparks = IO $ \s -> case numSparks# s of (# s', n #) -> (# s', I# n #)



_______________________________________________
Cvs-libraries mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-libraries

Reply via email to