[commit: ghc] master: Unlit overlooked GHC/Conc/Sync.lhs (8e66365)

git at git.haskell.org git at git.haskell.org
Sat Nov 8 14:16:01 UTC 2014


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/8e66365b0046f78d4f3b24f2ba39171c633568fa/ghc

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

commit 8e66365b0046f78d4f3b24f2ba39171c633568fa
Author: Herbert Valerio Riedel <hvr at gnu.org>
Date:   Sat Nov 8 15:13:59 2014 +0100

    Unlit overlooked GHC/Conc/Sync.lhs
    
    This is a follow-up commit to df3b1d43cc862fe03f0724a9c0ac9e7cecdf4605


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

8e66365b0046f78d4f3b24f2ba39171c633568fa
 libraries/base/GHC/Conc/{Sync.lhs => Sync.hs} | 45 +++++++++------------------
 1 file changed, 14 insertions(+), 31 deletions(-)

diff --git a/libraries/base/GHC/Conc/Sync.lhs b/libraries/base/GHC/Conc/Sync.hs
similarity index 95%
rename from libraries/base/GHC/Conc/Sync.lhs
rename to libraries/base/GHC/Conc/Sync.hs
index da9f376..6d2e772 100644
--- a/libraries/base/GHC/Conc/Sync.lhs
+++ b/libraries/base/GHC/Conc/Sync.hs
@@ -1,4 +1,3 @@
-\begin{code}
 {-# LANGUAGE Unsafe #-}
 {-# LANGUAGE CPP
            , NoImplicitPrelude
@@ -118,15 +117,11 @@ import GHC.Show         ( Show(..), showString )
 import GHC.Weak
 
 infixr 0 `par`, `pseq`
-\end{code}
 
-%************************************************************************
-%*                                                                      *
-\subsection{@ThreadId@, @par@, and @fork@}
-%*                                                                      *
-%************************************************************************
+-----------------------------------------------------------------------------
+-- 'ThreadId', 'par', and 'fork'
+-----------------------------------------------------------------------------
 
-\begin{code}
 data ThreadId = ThreadId ThreadId# deriving( Typeable )
 -- ToDo: data ThreadId = ThreadId (Weak ThreadId#)
 -- But since ThreadId# is unlifted, the Weak type must use open
@@ -528,19 +523,15 @@ mkWeakThreadId :: ThreadId -> IO (Weak ThreadId)
 mkWeakThreadId t@(ThreadId t#) = IO $ \s ->
    case mkWeakNoFinalizer# t# t s of
       (# s1, w #) -> (# s1, Weak w #)
-\end{code}
 
 
-%************************************************************************
-%*                                                                      *
-\subsection[stm]{Transactional heap operations}
-%*                                                                      *
-%************************************************************************
+-----------------------------------------------------------------------------
+-- Transactional heap operations
+-----------------------------------------------------------------------------
 
-TVars are shared memory locations which support atomic memory
-transactions.
+-- TVars are shared memory locations which support atomic memory
+-- transactions.
 
-\begin{code}
 -- |A monad supporting atomic memory transactions.
 newtype STM a = STM (State# RealWorld -> (# State# RealWorld, a #))
                 deriving Typeable
@@ -733,11 +724,10 @@ writeTVar (TVar tvar#) val = STM $ \s1# ->
     case writeTVar# tvar# val s1# of
          s2# -> (# s2#, () #)
 
-\end{code}
-
-MVar utilities
+-----------------------------------------------------------------------------
+-- MVar utilities
+-----------------------------------------------------------------------------
 
-\begin{code}
 withMVar :: MVar a -> (a -> IO b) -> IO b
 withMVar m io =
   mask $ \restore -> do
@@ -755,15 +745,10 @@ modifyMVar_ m io =
             (\e -> do putMVar m a; throw e)
     putMVar m a'
     return ()
-\end{code}
-
-%************************************************************************
-%*                                                                      *
-\subsection{Thread waiting}
-%*                                                                      *
-%************************************************************************
 
-\begin{code}
+-----------------------------------------------------------------------------
+-- Thread waiting
+-----------------------------------------------------------------------------
 
 -- Machinery needed to ensureb that we only have one copy of certain
 -- CAFs in this module even when the base package is present twice, as
@@ -824,5 +809,3 @@ setUncaughtExceptionHandler = writeIORef uncaughtExceptionHandler
 
 getUncaughtExceptionHandler :: IO (SomeException -> IO ())
 getUncaughtExceptionHandler = readIORef uncaughtExceptionHandler
-
-\end{code}



More information about the ghc-commits mailing list