Remove Control.Parallel*, now in package parallel
[haskell-directory.git] / System / Posix / Internals.hs
index 943b58f..e03c5dd 100644 (file)
@@ -1,4 +1,4 @@
-{-# OPTIONS -fno-implicit-prelude #-}
+{-# OPTIONS_GHC -fno-implicit-prelude #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -8,7 +8,7 @@
 -- 
 -- Maintainer  :  cvs-ghc@haskell.org
 -- Stability   :  internal
--- Portability :  non-portable
+-- Portability :  non-portable (requires POSIX)
 --
 -- POSIX support layer for the standard libraries.
 -- This library is built on *every* platform, including Win32.
@@ -21,7 +21,6 @@
 -- #hide
 module System.Posix.Internals where
 
-#include "ghcconfig.h"
 #include "HsBaseConfig.h"
 
 import Control.Monad
@@ -45,8 +44,7 @@ import System.IO
 #ifdef __HUGS__
 import Hugs.Prelude (IOException(..), IOErrorType(..))
 
-{-# CBITS PrelIOUtils.c dirUtils.c consUtils.c #-}
-ioException = ioError
+{-# CFILES cbits/PrelIOUtils.c cbits/dirUtils.c cbits/consUtils.c #-}
 #endif
 
 -- ---------------------------------------------------------------------------
@@ -68,17 +66,17 @@ type CUtimbuf   = ()
 type CUtsname   = ()
 
 #ifndef __GLASGOW_HASKELL__
-type FD = Int
+type FD = CInt
 #endif
 
 -- ---------------------------------------------------------------------------
 -- stat()-related stuff
 
-fdFileSize :: Int -> IO Integer
+fdFileSize :: FD -> IO Integer
 fdFileSize fd = 
   allocaBytes sizeof_stat $ \ p_stat -> do
     throwErrnoIfMinus1Retry "fileSize" $
-       c_fstat (fromIntegral fd) p_stat
+       c_fstat fd p_stat
     c_mode <- st_mode p_stat :: IO CMode 
     if not (s_isreg c_mode)
        then return (-1)
@@ -86,7 +84,7 @@ fdFileSize fd =
     c_size <- st_size p_stat :: IO COff
     return (fromIntegral c_size)
 
-data FDType  = Directory | Stream | RegularFile
+data FDType  = Directory | Stream | RegularFile | RawDevice
               deriving (Eq)
 
 fileType :: FilePath -> IO FDType
@@ -99,11 +97,11 @@ fileType file =
 
 -- NOTE: On Win32 platforms, this will only work with file descriptors
 -- referring to file handles. i.e., it'll fail for socket FDs.
-fdType :: Int -> IO FDType
+fdType :: FD -> IO FDType
 fdType fd = 
   allocaBytes sizeof_stat $ \ p_stat -> do
     throwErrnoIfMinus1Retry "fdType" $
-       c_fstat (fromIntegral fd) p_stat
+       c_fstat fd p_stat
     statGetType p_stat
 
 statGetType p_stat = do
@@ -113,25 +111,15 @@ statGetType p_stat = do
         | s_isfifo c_mode || s_issock c_mode || s_ischr  c_mode
                                -> return Stream
        | s_isreg c_mode        -> return RegularFile
+        -- Q: map char devices to RawDevice too?
+       | s_isblk c_mode        -> return RawDevice
        | otherwise             -> ioError ioe_unknownfiletype
     
 
 ioe_unknownfiletype = IOError Nothing UnsupportedOperation "fdType"
                        "unknown file type" Nothing
 
--- 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 ()
-
-#if defined(mingw32_TARGET_OS) || defined(__MINGW32__)
+#if __GLASGOW_HASKELL__ && (defined(mingw32_HOST_OS) || defined(__MINGW32__))
 closeFd :: Bool -> CInt -> IO CInt
 closeFd isStream fd 
   | isStream  = c_closesocket fd
@@ -141,17 +129,17 @@ foreign import stdcall unsafe "HsBase.h closesocket"
    c_closesocket :: CInt -> IO CInt
 #endif
 
-fdGetMode :: Int -> IO IOMode
+fdGetMode :: FD -> IO IOMode
 fdGetMode fd = do
-#if defined(mingw32_TARGET_OS) || defined(__MINGW32__)
+#if defined(mingw32_HOST_OS) || defined(__MINGW32__)
     -- XXX: this code is *BROKEN*, _setmode only deals with O_TEXT/O_BINARY
     flags1 <- throwErrnoIfMinus1Retry "fdGetMode" 
-                (c__setmode (fromIntegral fd) (fromIntegral o_WRONLY))
+                (c__setmode fd (fromIntegral o_WRONLY))
     flags  <- throwErrnoIfMinus1Retry "fdGetMode" 
-                (c__setmode (fromIntegral fd) (fromIntegral flags1))
+                (c__setmode fd (fromIntegral flags1))
 #else
     flags <- throwErrnoIfMinus1Retry "fdGetMode" 
-               (c_fcntl_read (fromIntegral fd) const_f_getfl)
+               (c_fcntl_read fd const_f_getfl)
 #endif
     let
        wH  = (flags .&. o_WRONLY) /= 0
@@ -169,12 +157,12 @@ fdGetMode fd = do
 -- ---------------------------------------------------------------------------
 -- Terminal-related stuff
 
-fdIsTTY :: Int -> IO Bool
-fdIsTTY fd = c_isatty (fromIntegral fd) >>= return.toBool
+fdIsTTY :: FD -> IO Bool
+fdIsTTY fd = c_isatty fd >>= return.toBool
 
 #if defined(HTYPE_TCFLAG_T)
 
-setEcho :: Int -> Bool -> IO ()
+setEcho :: FD -> Bool -> IO ()
 setEcho fd on = do
   tcSetAttr fd $ \ p_tios -> do
     c_lflag <- c_lflag p_tios :: IO CTcflag
@@ -183,13 +171,13 @@ setEcho fd on = do
         | otherwise = c_lflag .&. complement (fromIntegral const_echo)
     poke_c_lflag p_tios (new_c_lflag :: CTcflag)
 
-getEcho :: Int -> IO Bool
+getEcho :: FD -> IO Bool
 getEcho fd = do
   tcSetAttr fd $ \ p_tios -> do
     c_lflag <- c_lflag p_tios :: IO CTcflag
     return ((c_lflag .&. fromIntegral const_echo) /= 0)
 
-setCooked :: Int -> Bool -> IO ()
+setCooked :: FD -> Bool -> IO ()
 setCooked fd cooked = 
   tcSetAttr fd $ \ p_tios -> do
 
@@ -211,7 +199,7 @@ tcSetAttr :: FD -> (Ptr CTermios -> IO a) -> IO a
 tcSetAttr fd fun = do
      allocaBytes sizeof_termios  $ \p_tios -> do
        throwErrnoIfMinus1Retry "tcSetAttr"
-          (c_tcgetattr (fromIntegral fd) p_tios)
+          (c_tcgetattr fd p_tios)
 
 #ifdef __GLASGOW_HASKELL__
        -- Save a copy of termios, if this is a standard file descriptor.
@@ -236,16 +224,16 @@ tcSetAttr fd fun = do
             c_sigprocmask const_sig_block p_sigset p_old_sigset
             r <- fun p_tios  -- do the business
             throwErrnoIfMinus1Retry_ "tcSetAttr" $
-                c_tcsetattr (fromIntegral fd) const_tcsanow p_tios
+                c_tcsetattr fd const_tcsanow p_tios
             c_sigprocmask const_sig_setmask p_old_sigset nullPtr
             return r
 
 #ifdef __GLASGOW_HASKELL__
 foreign import ccall unsafe "HsBase.h __hscore_get_saved_termios"
-   get_saved_termios :: Int -> IO (Ptr CTermios)
+   get_saved_termios :: CInt -> IO (Ptr CTermios)
 
 foreign import ccall unsafe "HsBase.h __hscore_set_saved_termios"
-   set_saved_termios :: Int -> (Ptr CTermios) -> IO ()
+   set_saved_termios :: CInt -> (Ptr CTermios) -> IO ()
 #endif
 
 #else
@@ -258,11 +246,11 @@ foreign import ccall unsafe "HsBase.h __hscore_set_saved_termios"
 -- report that character until another character is input..odd.) This
 -- latter feature doesn't sit too well with IO actions like IO.hGetLine..
 -- consider yourself warned.
-setCooked :: Int -> Bool -> IO ()
+setCooked :: FD -> Bool -> IO ()
 setCooked fd cooked = do
-  x <- set_console_buffering (fromIntegral fd) (if cooked then 1 else 0)
+  x <- set_console_buffering fd (if cooked then 1 else 0)
   if (x /= 0)
-   then ioException (ioe_unk_error "setCooked" "failed to set buffering")
+   then ioError (ioe_unk_error "setCooked" "failed to set buffering")
    else return ()
 
 ioe_unk_error loc msg 
@@ -270,18 +258,18 @@ ioe_unk_error loc msg
 
 -- Note: echoing goes hand in hand with enabling 'line input' / raw-ness
 -- for Win32 consoles, hence setEcho ends up being the inverse of setCooked.
-setEcho :: Int -> Bool -> IO ()
+setEcho :: FD -> Bool -> IO ()
 setEcho fd on = do
-  x <- set_console_echo (fromIntegral fd) (if on then 1 else 0)
+  x <- set_console_echo fd (if on then 1 else 0)
   if (x /= 0)
-   then ioException (ioe_unk_error "setEcho" "failed to set echoing")
+   then ioError (ioe_unk_error "setEcho" "failed to set echoing")
    else return ()
 
-getEcho :: Int -> IO Bool
+getEcho :: FD -> IO Bool
 getEcho fd = do
-  r <- get_console_echo (fromIntegral fd)
+  r <- get_console_echo fd
   if (r == (-1))
-   then ioException (ioe_unk_error "getEcho" "failed to get echoing")
+   then ioError (ioe_unk_error "getEcho" "failed to get echoing")
    else return (r == 1)
 
 foreign import ccall unsafe "consUtils.h set_console_buffering__"
@@ -298,16 +286,16 @@ foreign import ccall unsafe "consUtils.h get_console_echo__"
 -- ---------------------------------------------------------------------------
 -- Turning on non-blocking for a file descriptor
 
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
 
 setNonBlockingFD fd = do
   flags <- throwErrnoIfMinus1Retry "setNonBlockingFD"
-                (c_fcntl_read (fromIntegral fd) const_f_getfl)
+                (c_fcntl_read fd const_f_getfl)
   -- An error when setting O_NONBLOCK isn't fatal: on some systems 
   -- there are certain file handles on which this will fail (eg. /dev/null
   -- on FreeBSD) so we throw away the return code from fcntl_write.
   unless (testBit flags (fromIntegral o_NONBLOCK)) $ do
-    c_fcntl_write (fromIntegral fd) const_f_setfl (flags .|. o_NONBLOCK)
+    c_fcntl_write fd const_f_setfl (fromIntegral (flags .|. o_NONBLOCK))
     return ()
 #else
 
@@ -320,7 +308,7 @@ setNonBlockingFD fd = return ()
 -- foreign imports
 
 foreign import ccall unsafe "HsBase.h access"
-   c_access :: CString -> CMode -> IO CInt
+   c_access :: CString -> CInt -> IO CInt
 
 foreign import ccall unsafe "HsBase.h chmod"
    c_chmod :: CString -> CMode -> IO CInt
@@ -347,7 +335,7 @@ foreign import ccall unsafe "HsBase.h __hscore_fstat"
    c_fstat :: CInt -> Ptr CStat -> IO CInt
 
 foreign import ccall unsafe "HsBase.h getcwd"
-   c_getcwd   :: Ptr CChar -> CInt -> IO (Ptr CChar)
+   c_getcwd   :: Ptr CChar -> CSize -> IO (Ptr CChar)
 
 foreign import ccall unsafe "HsBase.h isatty"
    c_isatty :: CInt -> IO CInt
@@ -388,15 +376,21 @@ foreign import ccall unsafe "HsBase.h umask"
 foreign import ccall unsafe "HsBase.h write" 
    c_write :: CInt -> Ptr CChar -> CSize -> IO CSsize
 
+foreign import ccall unsafe "HsBase.h __hscore_ftruncate"
+   c_ftruncate :: CInt -> COff -> IO CInt
+
 foreign import ccall unsafe "HsBase.h unlink"
    c_unlink :: CString -> IO CInt
 
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
+foreign import ccall unsafe "HsBase.h getpid"
+   c_getpid :: IO CPid
+
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
 foreign import ccall unsafe "HsBase.h fcntl"
    c_fcntl_read  :: CInt -> CInt -> IO CInt
 
 foreign import ccall unsafe "HsBase.h fcntl"
-   c_fcntl_write :: CInt -> CInt -> CInt -> IO CInt
+   c_fcntl_write :: CInt -> CInt -> CLong -> IO CInt
 
 foreign import ccall unsafe "HsBase.h fcntl"
    c_fcntl_lock  :: CInt -> CInt -> Ptr CFLock -> IO CInt
@@ -404,9 +398,6 @@ foreign import ccall unsafe "HsBase.h fcntl"
 foreign import ccall unsafe "HsBase.h fork"
    c_fork :: IO CPid 
 
-foreign import ccall unsafe "HsBase.h getpid"
-   c_getpid :: IO CPid
-
 foreign import ccall unsafe "HsBase.h link"
    c_link :: CString -> CString -> IO CInt
 
@@ -432,7 +423,7 @@ foreign import ccall unsafe "HsBase.h tcsetattr"
    c_tcsetattr :: CInt -> CInt -> Ptr CTermios -> IO CInt
 
 foreign import ccall unsafe "HsBase.h utime"
-   c_utime :: CString -> Ptr CUtimbuf -> IO CMode
+   c_utime :: CString -> Ptr CUtimbuf -> IO CInt
 
 foreign import ccall unsafe "HsBase.h waitpid"
    c_waitpid :: CPid -> Ptr CInt -> CInt -> IO CPid
@@ -475,11 +466,22 @@ foreign import ccall unsafe "HsBase.h __hscore_o_noctty"   o_NOCTTY   :: CInt
 foreign import ccall unsafe "HsBase.h __hscore_o_nonblock" o_NONBLOCK :: CInt
 foreign import ccall unsafe "HsBase.h __hscore_o_binary"   o_BINARY   :: CInt
 
-foreign import ccall unsafe "HsBase.h __hscore_s_isreg"  s_isreg  :: CMode -> Bool
-foreign import ccall unsafe "HsBase.h __hscore_s_ischr"  s_ischr  :: CMode -> Bool
-foreign import ccall unsafe "HsBase.h __hscore_s_isblk"  s_isblk  :: CMode -> Bool
-foreign import ccall unsafe "HsBase.h __hscore_s_isdir"  s_isdir  :: CMode -> Bool
-foreign import ccall unsafe "HsBase.h __hscore_s_isfifo" s_isfifo :: CMode -> Bool
+foreign import ccall unsafe "HsBase.h __hscore_s_isreg"  c_s_isreg  :: CMode -> CInt
+foreign import ccall unsafe "HsBase.h __hscore_s_ischr"  c_s_ischr  :: CMode -> CInt
+foreign import ccall unsafe "HsBase.h __hscore_s_isblk"  c_s_isblk  :: CMode -> CInt
+foreign import ccall unsafe "HsBase.h __hscore_s_isdir"  c_s_isdir  :: CMode -> CInt
+foreign import ccall unsafe "HsBase.h __hscore_s_isfifo" c_s_isfifo :: CMode -> CInt
+
+s_isreg  :: CMode -> Bool
+s_isreg cm = c_s_isreg cm /= 0
+s_ischr  :: CMode -> Bool
+s_ischr cm = c_s_ischr cm /= 0
+s_isblk  :: CMode -> Bool
+s_isblk cm = c_s_isblk cm /= 0
+s_isdir  :: CMode -> Bool
+s_isdir cm = c_s_isdir cm /= 0
+s_isfifo :: CMode -> Bool
+s_isfifo cm = c_s_isfifo cm /= 0
 
 foreign import ccall unsafe "HsBase.h __hscore_sizeof_stat" sizeof_stat :: Int
 foreign import ccall unsafe "HsBase.h __hscore_st_mtime" st_mtime :: Ptr CStat -> IO CTime
@@ -506,8 +508,10 @@ foreign import ccall unsafe "HsBase.h __hscore_poke_lflag" poke_c_lflag :: Ptr C
 foreign import ccall unsafe "HsBase.h __hscore_ptr_c_cc" ptr_c_cc  :: Ptr CTermios -> IO (Ptr Word8)
 #endif
 
-#if !defined(mingw32_TARGET_OS) && !defined(__MINGW32__)
-foreign import ccall unsafe "HsBase.h __hscore_s_issock" s_issock :: CMode -> Bool
+#if !defined(mingw32_HOST_OS) && !defined(__MINGW32__)
+foreign import ccall unsafe "HsBase.h __hscore_s_issock" c_s_issock :: CMode -> CInt
+s_issock :: CMode -> Bool
+s_issock cmode = c_s_issock cmode /= 0
 #else
 s_issock :: CMode -> Bool
 s_issock cmode = False