diff --git a/ghc/docs/libraries/libs.sgml b/ghc/docs/libraries/libs.sgml
index 7ce5045157bab4423fd73bdabc8bf57e6edf9d18..4f8b49e15732e7d5a17876baadc28a078c1eca65 100644
--- a/ghc/docs/libraries/libs.sgml
+++ b/ghc/docs/libraries/libs.sgml
@@ -510,7 +510,8 @@ redistribute their implementation of this module.
 module Concurrent where
 
 data ThreadId    -- thread identifiers
-instance Eq ThreadId
+instance Eq  ThreadId
+instance Ord ThreadId
 
 forkIO           :: IO () -> IO ThreadId
 killThread       :: ThreadId -> IO ()
@@ -530,7 +531,7 @@ writeChan        :: Chan a -> a -> IO ()
 readChan         :: Chan a -> IO a
 dupChan          :: Chan a -> IO (Chan a)
 unReadChan       :: Chan a -> a -> IO ()
-readChanContents :: Chan a -> IO [a]
+getChanContents  :: Chan a -> IO [a]
 writeList2Chan   :: Chan a -> [a] -> IO ()
                       
 data CVar a       -- one element channels
@@ -584,10 +585,10 @@ Hugs does not provide the functions <tt/mergeIO/ or <tt/nmergeIO/ since these
 require preemptive multitasking.
 
 <item>
-<tt/killThread/ has not been implemented yet on either system.
-The plan is that <tt/killThread/ will raise an IO exception in the
-killed thread which it can catch --- perhaps allowing it to kill its
-children before exiting.
+Thread identities and <tt/killThread/ has not been implemented yet on
+either system. The plan is that <tt/killThread/ will raise an IO
+exception in the killed thread which it can catch --- perhaps allowing -->
+--it to kill its children before exiting.
 
 <item>
 The <tt/Ord/ instance for <tt/ThreadId/s provides an arbitrary total ordering