[project @ 2001-09-08 21:42:07 by sof]
[ghc-hetmet.git] / ghc / lib / std / PrelPosix.hsc
index 7d69447..a2dfdd6 100644 (file)
@@ -1,16 +1,24 @@
-{-# OPTIONS -optc-DNON_POSIX_SOURCE #-}
+{-# OPTIONS -fno-implicit-prelude #-}
 
 -- ---------------------------------------------------------------------------
--- $Id: PrelPosix.hsc,v 1.1 2001/05/18 16:54:05 simonmar Exp $
+-- $Id: PrelPosix.hsc,v 1.13 2001/08/23 10:36:50 sewardj Exp $
 --
 -- POSIX support layer for the standard libraries
 --
+-- Non-posix compliant in order to support the following features:
+--     * S_ISSOCK (no sockets in POSIX)
 
 module PrelPosix where
 
+-- See above comment for non-Posixness reasons.
+-- #include "PosixSource.h"
+
 #include "HsStd.h"
 
-import Monad
+import PrelBase
+import PrelNum
+import PrelReal
+import PrelMaybe
 import PrelCString
 import PrelPtr
 import PrelWord
@@ -23,6 +31,7 @@ import PrelMarshalAlloc
 import PrelMarshalUtils
 import PrelBits
 import PrelIOBase
+import Monad
 
 
 -- ---------------------------------------------------------------------------
@@ -36,7 +45,10 @@ type CIno    = #type ino_t
 type CMode   = #type mode_t
 type COff    = #type off_t
 type CPid    = #type pid_t
-#ifndef mingw32_TARGET_OS
+
+#ifdef mingw32_TARGET_OS
+type CSsize  = #type size_t
+#else
 type CGid    = #type gid_t
 type CNlink  = #type nlink_t
 type CSsize  = #type ssize_t
@@ -81,17 +93,34 @@ fdType fd =
 ioe_unknownfiletype = IOError Nothing UnsupportedOperation "fdType"
                        "unknown file type" Nothing
 
-foreign import "s_isreg_wrap" s_isreg :: CMode -> Bool
-#def inline int s_isreg_wrap(m) { return S_ISREG(m); }
+foreign import "s_isreg_PrelPosix_wrap" unsafe s_isreg :: CMode -> Bool
+#def inline int s_isreg_PrelPosix_wrap(m) { return S_ISREG(m); }
+
+foreign import "s_isdir_PrelPosix_wrap" unsafe s_isdir :: CMode -> Bool
+#def inline int s_isdir_PrelPosix_wrap(m) { return S_ISDIR(m); }
 
-foreign import "s_isdir_wrap" s_isdir :: CMode -> Bool
-#def inline int s_isdir_wrap(m) { return S_ISDIR(m); }
+foreign import "s_isfifo_PrelPosix_wrap" unsafe s_isfifo :: CMode -> Bool
+#def inline int s_isfifo_PrelPosix_wrap(m) { return S_ISFIFO(m); }
 
-foreign import "s_isfifo_wrap" s_isfifo :: CMode -> Bool
-#def inline int s_isfifo_wrap(m) { return S_ISFIFO(m); }
+#ifndef mingw32_TARGET_OS
+foreign import "s_issock_PrelPosix_wrap" unsafe s_issock :: CMode -> Bool
+#def inline int s_issock_PrelPosix_wrap(m) { return S_ISSOCK(m); }
+#else
+s_issock :: CMode -> Bool
+s_issock cmode = False
+#endif
 
-foreign import "s_issock_wrap" s_issock :: CMode -> Bool
-#def inline int s_issock_wrap(m) { return S_ISSOCK(m); }
+-- It isn't clear whether ftruncate is POSIX or not (I've read several
+-- manpages and they seem to conflict), so we truncate using open/2.
+fileTruncate :: FilePath -> IO ()
+fileTruncate file = do
+  let flags = o_WRONLY .|. o_TRUNC
+  withCString file $ \file_cstr -> do
+    fd <- fromIntegral `liftM`
+           throwErrnoIfMinus1Retry "fileTruncate"
+               (c_open file_cstr (fromIntegral flags) 0o666)
+    c_close fd
+  return ()
 
 -- ---------------------------------------------------------------------------
 -- Terminal-related stuff
@@ -99,6 +128,8 @@ foreign import "s_issock_wrap" s_issock :: CMode -> Bool
 fdIsTTY :: Int -> IO Bool
 fdIsTTY fd = c_isatty (fromIntegral fd) >>= return.toBool
 
+#ifndef mingw32_TARGET_OS
+
 type Termios = ()
 
 setEcho :: Int -> Bool -> IO ()
@@ -133,13 +164,13 @@ setCooked fd cooked =
     (#poke struct termios, c_lflag) p_tios (new_c_lflag :: CTcflag)
 
     -- set VMIN & VTIME to 1/0 respectively
-    when cooked $
-        do let c_cc  = (#ptr struct termios, c_cc) p_tios
-               vmin  = c_cc `plusPtr` (#const VMIN)  :: Ptr Word8
+    when cooked $ do
+           let c_cc  = (#ptr struct termios, c_cc) p_tios
+               vmin  = c_cc `plusPtr` (#const VMIN)  :: Ptr Word8
                vtime = c_cc `plusPtr` (#const VTIME) :: Ptr Word8
            poke vmin  1
            poke vtime 0
-       
+
     tcSetAttr fd (#const TCSANOW) p_tios
 
 -- tcsetattr() when invoked by a background process causes the process
@@ -159,15 +190,37 @@ tcSetAttr fd options p_tios = do
         c_tcsetattr (fromIntegral fd) options p_tios
      c_sigprocmask (#const SIG_SETMASK) p_old_sigset nullPtr
 
+#else
+
+-- bogus defns for win32
+setCooked :: Int -> Bool -> IO ()
+setCooked fd cooked = return ()
+
+setEcho :: Int -> Bool -> IO ()
+setEcho fd on = return ()
+
+getEcho :: Int -> IO Bool
+getEcho fd = return False
+
+#endif
+
 -- ---------------------------------------------------------------------------
 -- Turning on non-blocking for a file descriptor
 
+#ifndef mingw32_TARGET_OS
+
 setNonBlockingFD fd = do
   flags <- throwErrnoIfMinus1Retry "setNonBlockingFD"
                 (fcntl_read (fromIntegral fd) (#const F_GETFL))
   throwErrnoIfMinus1Retry "setNonBlockingFD"
        (fcntl_write (fromIntegral fd) 
           (#const F_SETFL) (flags .|. #const O_NONBLOCK))
+#else
+
+-- bogus defns for win32
+setNonBlockingFD fd = return ()
+
+#endif
 
 -- -----------------------------------------------------------------------------
 -- foreign imports
@@ -193,13 +246,36 @@ o_RDWR      = (#const O_RDWR)        :: CInt
 o_APPEND    = (#const O_APPEND)           :: CInt
 o_CREAT     = (#const O_CREAT)    :: CInt
 o_EXCL     = (#const O_EXCL)      :: CInt
-o_NOCTTY    = (#const O_NOCTTY)           :: CInt
 o_TRUNC     = (#const O_TRUNC)    :: CInt
+
+#ifdef mingw32_TARGET_OS
+o_NOCTTY    = 0 :: CInt
+o_NONBLOCK  = 0 :: CInt
+#else
+o_NOCTTY    = (#const O_NOCTTY)           :: CInt
 o_NONBLOCK  = (#const O_NONBLOCK)  :: CInt
+#endif
+
+#ifdef HAVE_O_BINARY
+o_BINARY    = (#const O_BINARY)           :: CInt
+#endif
+
+foreign import "isatty" unsafe
+   c_isatty :: CInt -> IO CInt
 
 foreign import "close" unsafe
    c_close :: CInt -> IO CInt
 
+foreign import "lseek" unsafe
+   c_lseek :: CInt -> COff -> CInt -> IO COff
+
+foreign import "write" unsafe 
+   c_write :: CInt -> Ptr CChar -> CSize -> IO CSsize
+
+foreign import "read" unsafe 
+   c_read :: CInt -> Ptr CChar -> CSize -> IO CSsize
+
+#ifndef mingw32_TARGET_OS
 foreign import "fcntl" unsafe
    fcntl_read  :: CInt -> CInt -> IO CInt
 
@@ -209,17 +285,9 @@ foreign import "fcntl" unsafe
 foreign import "fork" unsafe
    fork :: IO CPid 
 
-foreign import "isatty" unsafe
-   c_isatty :: CInt -> IO CInt
-
-foreign import "lseek" unsafe
-   c_lseek :: CInt -> COff -> CInt -> IO COff
-
-foreign import "read" unsafe 
-   c_read :: CInt -> Ptr CChar -> CSize -> IO CSsize
-
-foreign import "sigemptyset" unsafe
+foreign import "sigemptyset_PrelPosix_wrap" unsafe
    c_sigemptyset :: Ptr CSigset -> IO ()
+#def inline void sigemptyset_PrelPosix_wrap(sigset_t *set) { sigemptyset(set); }
 
 foreign import "sigaddset" unsafe
    c_sigaddset :: Ptr CSigset -> CInt -> IO ()
@@ -233,9 +301,9 @@ foreign import "tcgetattr" unsafe
 foreign import "tcsetattr" unsafe
    c_tcsetattr :: CInt -> CInt -> Ptr Termios -> IO CInt
 
+foreign import "unlink" unsafe 
+   c_unlink :: CString -> IO CInt
+
 foreign import "waitpid" unsafe
    c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid
-
-foreign import "write" unsafe 
-   c_write :: CInt -> Ptr CChar -> CSize -> IO CSsize
-
+#endif