[project @ 1997-10-21 20:38:32 by sof]
[ghc-hetmet.git] / ghc / lib / ghc / IOHandle.lhs
index a3f64ce..72f1fae 100644 (file)
@@ -8,23 +8,30 @@ This module defines Haskell {\em handles} and the basic operations
 which are supported for them.
 
 \begin{code}
+{-# OPTIONS -fno-implicit-prelude -#include "cbits/stgio.h" #-}
 #include "error.h"
 
-{-# OPTIONS -fno-implicit-prelude -#include "cbits/stgio.h" #-}
 
 module IOHandle where
 
 import ST
+import UnsafeST
 import STBase
 import ArrBase ( ByteArray(..) )
 import PrelRead        ( Read )
+import PrelList (span)
 import Ix
 import IOBase
 import PrelTup
 import PrelBase
 import GHC
-import Foreign  ( makeForeignObj, writeForeignObj )
-import PrelList (span)
+
+import Foreign  ( Addr, 
+#ifndef __PARALLEL_HASKELL__
+                  ForeignObj, makeForeignObj, writeForeignObj 
+#endif
+                 )
+
 #if defined(__CONCURRENT_HASKELL__)
 import ConcBase
 #endif
@@ -68,7 +75,7 @@ writeHandle h v = stToIO (writeVar h v)
 %*********************************************************
 
 \begin{code}
-#ifndef PAR
+#ifndef __PARALLEL_HASKELL__
 filePtr :: Handle__ -> ForeignObj
 #else
 filePtr :: Handle__ -> Addr
@@ -121,8 +128,8 @@ stdin = unsafePerformPrimIO (
     (case rc of
        0 -> new_handle ClosedHandle
        1 -> 
-#ifndef PAR
-            makeForeignObj (``stdin''::Addr) (``&freeStdChannel''::Addr) >>= \ fp ->
+#ifndef __PARALLEL_HASKELL__
+            makeForeignObj (``stdin''::Addr) (``&freeStdFile''::Addr) >>= \ fp ->
            new_handle (ReadHandle fp Nothing False)
 #else
            new_handle (ReadHandle ``stdin'' Nothing False)
@@ -140,8 +147,8 @@ stdout = unsafePerformPrimIO (
     (case rc of
        0 -> new_handle ClosedHandle
        1 -> 
-#ifndef PAR
-            makeForeignObj (``stdout''::Addr) (``&freeStdChannel''::Addr) >>= \ fp ->
+#ifndef __PARALLEL_HASKELL__
+            makeForeignObj (``stdout''::Addr) (``&freeStdFile''::Addr) >>= \ fp ->
            new_handle (WriteHandle fp Nothing False)
 #else
            new_handle (WriteHandle ``stdout'' Nothing False)
@@ -159,8 +166,8 @@ stderr = unsafePerformPrimIO (
     (case rc of
        0 -> new_handle ClosedHandle
        1 -> 
-#ifndef PAR
-            makeForeignObj (``stderr''::Addr) (``&freeStdChannel''::Addr) >>= \ fp ->
+#ifndef __PARALLEL_HASKELL__
+            makeForeignObj (``stderr''::Addr) (``&freeStdFile''::Addr) >>= \ fp ->
             new_handle (WriteHandle fp (Just NoBuffering) False)       
 #else
             new_handle (WriteHandle ``stderr'' (Just NoBuffering) False)       
@@ -189,7 +196,7 @@ openFile :: FilePath -> IOMode -> IO Handle
 openFile f m = 
     stToIO (_ccall_ openFile f m')                          >>= \ ptr ->
     if ptr /= ``NULL'' then
-#ifndef PAR
+#ifndef __PARALLEL_HASKELL__
         makeForeignObj ptr ((``&freeFile'')::Addr)   `thenIO_Prim` \ fp ->
         newHandle (htype fp Nothing False)
 #else
@@ -271,7 +278,7 @@ hClose handle =
                      to avoid closing the file object when the ForeignObj
                     is finalised.  -}
                 if rc == 0 then 
-#ifndef PAR
+#ifndef __PARALLEL_HASKELL__
                  -- Mark the foreign object data value as gone to the finaliser (freeFile())
                  writeForeignObj fp ``NULL''       `thenIO_Prim` \ () ->
 #endif
@@ -286,7 +293,7 @@ hClose handle =
          let fp = filePtr other in
           _ccall_ closeFile fp     `thenIO_Prim` \ rc ->
           if rc == 0 then 
-#ifndef PAR
+#ifndef __PARALLEL_HASKELL__
                  -- Mark the foreign object data
                  writeForeignObj fp ``NULL''       `thenIO_Prim` \ () ->
 #endif
@@ -462,7 +469,7 @@ hSetBuffering handle mode =
               BlockBuffering Nothing -> -2
               BlockBuffering (Just n) -> n
 
-#ifndef PAR
+#ifndef __PARALLEL_HASKELL__
     hcon :: Handle__ -> (ForeignObj -> (Maybe BufferMode) -> Bool -> Handle__)
 #else
     hcon :: Handle__ -> (Addr -> (Maybe BufferMode) -> Bool -> Handle__)
@@ -509,8 +516,6 @@ hFlush handle =
 \begin{code}
 data HandlePosn = HandlePosn Handle Int
 
-instance Eq HandlePosn{-partain-}
-
 data SeekMode    =  AbsoluteSeek | RelativeSeek | SeekFromEnd
                     deriving (Eq, Ord, Ix, Enum, Read, Show)
 \end{code}