1 {-# LANGUAGE Trustworthy #-}
2 {-# LANGUAGE CPP, NoImplicitPrelude, ForeignFunctionInterface #-}
3 {-# OPTIONS_HADDOCK hide #-}
5 -----------------------------------------------------------------------------
7 -- Module : System.Posix.Internals
8 -- Copyright : (c) The University of Glasgow, 1992-2002
9 -- License : see libraries/base/LICENSE
11 -- Maintainer : cvs-ghc@haskell.org
12 -- Stability : internal
13 -- Portability : non-portable (requires POSIX)
15 -- POSIX support layer for the standard libraries.
16 -- This library is built on *every* platform, including Win32.
18 -- Non-posix compliant in order to support the following features:
19 -- * S_ISSOCK (no sockets in POSIX)
21 -----------------------------------------------------------------------------
24 module System
.Posix
.Internals
where
27 #define HTYPE_TCFLAG_T
29 # include
"HsBaseConfig.h"
32 #if ! (defined
(mingw32_HOST_OS
) || defined
(__MINGW32__
))
35 import System
.Posix
.Types
43 #if !defined
(HTYPE_TCFLAG_T
)
44 import System
.IO.Error
47 #if __GLASGOW_HASKELL__
53 import GHC
.IO.Exception
55 #ifndef mingw32_HOST_OS
56 import {-# SOURCE #-} GHC
.IO.Encoding
(getFileSystemEncoding
)
57 import qualified GHC
.Foreign
as GHC
60 import Hugs
.Prelude
(IOException
(..), IOErrorType
(..))
61 import Hugs
.IO (IOMode(..))
63 import GHC
.IO.Device
-- yes, I know, but its portable, really!
65 import Control
.Exception
70 {-# CFILES cbits/PrelIOUtils.c cbits/consUtils.c #-}
74 -- ---------------------------------------------------------------------------
75 -- Debugging the base package
77 puts
:: String -> IO ()
78 puts s
= withCAStringLen
(s
++ "\n") $ \(p
, len
) -> do
79 -- In reality should be withCString, but assume ASCII to avoid loop
80 -- if this is called by GHC.Foreign
81 _
<- c_write
1 (castPtr p
) (fromIntegral len
)
85 -- ---------------------------------------------------------------------------
103 -- ---------------------------------------------------------------------------
104 -- stat()-related stuff
106 fdFileSize
:: FD
-> IO Integer
108 allocaBytes sizeof_stat
$ \ p_stat
-> do
109 throwErrnoIfMinus1Retry_
"fileSize" $
111 c_mode
<- st_mode p_stat
:: IO CMode
112 if not (s_isreg c_mode
)
115 c_size
<- st_size p_stat
116 return (fromIntegral c_size
)
118 fileType
:: FilePath -> IO IODeviceType
120 allocaBytes sizeof_stat
$ \ p_stat
-> do
121 withFilePath file
$ \p_file
-> do
122 throwErrnoIfMinus1Retry_
"fileType" $
126 -- NOTE: On Win32 platforms, this will only work with file descriptors
127 -- referring to file handles. i.e., it'll fail for socket FDs.
128 fdStat
:: FD
-> IO (IODeviceType
, CDev
, CIno
)
130 allocaBytes sizeof_stat
$ \ p_stat
-> do
131 throwErrnoIfMinus1Retry_
"fdType" $
133 ty
<- statGetType p_stat
138 fdType
:: FD
-> IO IODeviceType
139 fdType fd
= do (ty
,_
,_
) <- fdStat fd
; return ty
141 statGetType
:: Ptr CStat
-> IO IODeviceType
142 statGetType p_stat
= do
143 c_mode
<- st_mode p_stat
:: IO CMode
145 _ | s_isdir c_mode
-> return Directory
146 | s_isfifo c_mode || s_issock c_mode || s_ischr c_mode
148 | s_isreg c_mode
-> return RegularFile
149 -- Q: map char devices to RawDevice too?
150 | s_isblk c_mode
-> return RawDevice
151 |
otherwise -> ioError ioe_unknownfiletype
153 ioe_unknownfiletype
:: IOException
155 ioe_unknownfiletype
= IOError Nothing UnsupportedOperation
"fdType"
157 # if __GLASGOW_HASKELL__
162 ioe_unknownfiletype
= UserError
"fdType" "unknown file type"
165 fdGetMode
:: FD
-> IO IOMode
166 #if defined
(mingw32_HOST_OS
) || defined
(__MINGW32__
)
168 -- We don't have a way of finding out which flags are set on FDs
169 -- on Windows, so make a handle that thinks that anything goes.
173 flags
<- throwErrnoIfMinus1Retry
"fdGetMode"
174 (c_fcntl_read fd const_f_getfl
)
177 wH
= (flags
.&. o_WRONLY
) /= 0
178 aH
= (flags
.&. o_APPEND
) /= 0
179 rwH
= (flags
.&. o_RDWR
) /= 0
182 | wH
&& aH
= AppendMode
184 | rwH
= ReadWriteMode
185 |
otherwise = ReadMode
189 #ifdef mingw32_HOST_OS
190 withFilePath
:: FilePath -> (CWString
-> IO a
) -> IO a
191 withFilePath
= withCWString
193 peekFilePath
:: CWString
-> IO FilePath
194 peekFilePath
= peekCWString
197 withFilePath
:: FilePath -> (CString
-> IO a
) -> IO a
198 peekFilePath
:: CString
-> IO FilePath
199 peekFilePathLen
:: CStringLen
-> IO FilePath
201 #if __GLASGOW_HASKELL__
202 withFilePath fp f
= getFileSystemEncoding
>>= \enc
-> GHC
.withCString enc fp f
203 peekFilePath fp
= getFileSystemEncoding
>>= \enc
-> GHC
.peekCString enc fp
204 peekFilePathLen fp
= getFileSystemEncoding
>>= \enc
-> GHC
.peekCStringLen enc fp
206 withFilePath
= withCString
207 peekFilePath
= peekCString
208 peekFilePathLen
= peekCStringLen
213 -- ---------------------------------------------------------------------------
214 -- Terminal-related stuff
216 #if defined
(HTYPE_TCFLAG_T
)
218 setEcho
:: FD
-> Bool -> IO ()
220 tcSetAttr fd
$ \ p_tios
-> do
221 lflag
<- c_lflag p_tios
:: IO CTcflag
223 | on
= lflag
.|
. fromIntegral const_echo
224 |
otherwise = lflag
.&. complement
(fromIntegral const_echo
)
225 poke_c_lflag p_tios
(new_lflag
:: CTcflag
)
227 getEcho
:: FD
-> IO Bool
229 tcSetAttr fd
$ \ p_tios
-> do
230 lflag
<- c_lflag p_tios
:: IO CTcflag
231 return ((lflag
.&. fromIntegral const_echo
) /= 0)
233 setCooked
:: FD
-> Bool -> IO ()
234 setCooked fd cooked
=
235 tcSetAttr fd
$ \ p_tios
-> do
237 -- turn on/off ICANON
238 lflag
<- c_lflag p_tios
:: IO CTcflag
239 let new_lflag | cooked
= lflag
.|
. (fromIntegral const_icanon
)
240 |
otherwise = lflag
.&. complement
(fromIntegral const_icanon
)
241 poke_c_lflag p_tios
(new_lflag
:: CTcflag
)
243 -- set VMIN & VTIME to 1/0 respectively
244 when (not cooked
) $ do
245 c_cc
<- ptr_c_cc p_tios
246 let vmin
= (c_cc `plusPtr`
(fromIntegral const_vmin
)) :: Ptr Word8
247 vtime
= (c_cc `plusPtr`
(fromIntegral const_vtime
)) :: Ptr Word8
251 tcSetAttr
:: FD
-> (Ptr CTermios
-> IO a
) -> IO a
252 tcSetAttr fd fun
= do
253 allocaBytes sizeof_termios
$ \p_tios
-> do
254 throwErrnoIfMinus1Retry_
"tcSetAttr"
255 (c_tcgetattr fd p_tios
)
257 #ifdef __GLASGOW_HASKELL__
258 -- Save a copy of termios, if this is a standard file descriptor.
259 -- These terminal settings are restored in hs_exit().
261 p
<- get_saved_termios fd
262 when (p
== nullPtr
) $ do
263 saved_tios
<- mallocBytes sizeof_termios
264 copyBytes saved_tios p_tios sizeof_termios
265 set_saved_termios fd saved_tios
268 -- tcsetattr() when invoked by a background process causes the process
269 -- to be sent SIGTTOU regardless of whether the process has TOSTOP set
270 -- in its terminal flags (try it...). This function provides a
271 -- wrapper which temporarily blocks SIGTTOU around the call, making it
273 allocaBytes sizeof_sigset_t
$ \ p_sigset
-> do
274 allocaBytes sizeof_sigset_t
$ \ p_old_sigset
-> do
275 throwErrnoIfMinus1_
"sigemptyset" $
276 c_sigemptyset p_sigset
277 throwErrnoIfMinus1_
"sigaddset" $
278 c_sigaddset p_sigset const_sigttou
279 throwErrnoIfMinus1_
"sigprocmask" $
280 c_sigprocmask const_sig_block p_sigset p_old_sigset
281 r
<- fun p_tios
-- do the business
282 throwErrnoIfMinus1Retry_
"tcSetAttr" $
283 c_tcsetattr fd const_tcsanow p_tios
284 throwErrnoIfMinus1_
"sigprocmask" $
285 c_sigprocmask const_sig_setmask p_old_sigset nullPtr
288 #ifdef __GLASGOW_HASKELL__
289 foreign import ccall unsafe
"HsBase.h __hscore_get_saved_termios"
290 get_saved_termios
:: CInt
-> IO (Ptr CTermios
)
292 foreign import ccall unsafe
"HsBase.h __hscore_set_saved_termios"
293 set_saved_termios
:: CInt
-> (Ptr CTermios
) -> IO ()
298 -- 'raw' mode for Win32 means turn off 'line input' (=> buffering and
299 -- character translation for the console.) The Win32 API for doing
300 -- this is GetConsoleMode(), which also requires echoing to be disabled
301 -- when turning off 'line input' processing. Notice that turning off
302 -- 'line input' implies enter/return is reported as '\r' (and it won't
303 -- report that character until another character is input..odd.) This
304 -- latter feature doesn't sit too well with IO actions like IO.hGetLine..
305 -- consider yourself warned.
306 setCooked
:: FD
-> Bool -> IO ()
307 setCooked fd cooked
= do
308 x
<- set_console_buffering fd
(if cooked
then 1 else 0)
310 then ioError (ioe_unk_error
"setCooked" "failed to set buffering")
313 ioe_unk_error
:: String -> String -> IOException
314 ioe_unk_error loc msg
316 = ioeSetErrorString
(mkIOError OtherError loc Nothing Nothing
) msg
321 -- Note: echoing goes hand in hand with enabling 'line input' / raw-ness
322 -- for Win32 consoles, hence setEcho ends up being the inverse of setCooked.
323 setEcho
:: FD
-> Bool -> IO ()
325 x
<- set_console_echo fd
(if on
then 1 else 0)
327 then ioError (ioe_unk_error
"setEcho" "failed to set echoing")
330 getEcho
:: FD
-> IO Bool
332 r
<- get_console_echo fd
334 then ioError (ioe_unk_error
"getEcho" "failed to get echoing")
337 foreign import ccall unsafe
"consUtils.h set_console_buffering__"
338 set_console_buffering
:: CInt
-> CInt
-> IO CInt
340 foreign import ccall unsafe
"consUtils.h set_console_echo__"
341 set_console_echo
:: CInt
-> CInt
-> IO CInt
343 foreign import ccall unsafe
"consUtils.h get_console_echo__"
344 get_console_echo
:: CInt
-> IO CInt
346 foreign import ccall unsafe
"consUtils.h is_console__"
347 is_console
:: CInt
-> IO CInt
351 -- ---------------------------------------------------------------------------
352 -- Turning on non-blocking for a file descriptor
354 setNonBlockingFD
:: FD
-> Bool -> IO ()
355 #if !defined
(mingw32_HOST_OS
) && !defined
(__MINGW32__
)
356 setNonBlockingFD fd set
= do
357 flags
<- throwErrnoIfMinus1Retry
"setNonBlockingFD"
358 (c_fcntl_read fd const_f_getfl
)
359 let flags
' | set
= flags
.|
. o_NONBLOCK
360 |
otherwise = flags
.&. complement o_NONBLOCK
361 unless (flags
== flags
') $ do
362 -- An error when setting O_NONBLOCK isn't fatal: on some systems
363 -- there are certain file handles on which this will fail (eg. /dev/null
364 -- on FreeBSD) so we throw away the return code from fcntl_write.
365 _
<- c_fcntl_write fd const_f_setfl
(fromIntegral flags
')
369 -- bogus defns for win32
370 setNonBlockingFD _ _
= return ()
374 -- -----------------------------------------------------------------------------
375 -- Set close-on-exec for a file descriptor
377 #if !defined
(mingw32_HOST_OS
) && !defined
(__MINGW32__
)
378 setCloseOnExec
:: FD
-> IO ()
379 setCloseOnExec fd
= do
380 throwErrnoIfMinus1_
"setCloseOnExec" $
381 c_fcntl_write fd const_f_setfd const_fd_cloexec
384 -- -----------------------------------------------------------------------------
387 #if !defined
(mingw32_HOST_OS
) && !defined
(__MINGW32__
)
388 type CFilePath
= CString
390 type CFilePath
= CWString
393 foreign import ccall unsafe
"HsBase.h access"
394 c_access
:: CString
-> CInt
-> IO CInt
396 foreign import ccall unsafe
"HsBase.h chmod"
397 c_chmod
:: CString
-> CMode
-> IO CInt
399 foreign import ccall unsafe
"HsBase.h close"
400 c_close
:: CInt
-> IO CInt
402 foreign import ccall unsafe
"HsBase.h creat"
403 c_creat
:: CString
-> CMode
-> IO CInt
405 foreign import ccall unsafe
"HsBase.h dup"
406 c_dup
:: CInt
-> IO CInt
408 foreign import ccall unsafe
"HsBase.h dup2"
409 c_dup2
:: CInt
-> CInt
-> IO CInt
411 foreign import ccall unsafe
"HsBase.h __hscore_fstat"
412 c_fstat
:: CInt
-> Ptr CStat
-> IO CInt
414 foreign import ccall unsafe
"HsBase.h isatty"
415 c_isatty
:: CInt
-> IO CInt
417 #if defined
(mingw32_HOST_OS
) || defined
(__MINGW32__
)
418 foreign import ccall unsafe
"HsBase.h __hscore_lseek"
419 c_lseek
:: CInt
-> Int64
-> CInt
-> IO Int64
421 foreign import ccall unsafe
"HsBase.h __hscore_lseek"
422 c_lseek
:: CInt
-> COff
-> CInt
-> IO COff
425 foreign import ccall unsafe
"HsBase.h __hscore_lstat"
426 lstat
:: CFilePath
-> Ptr CStat
-> IO CInt
428 foreign import ccall unsafe
"HsBase.h __hscore_open"
429 c_open
:: CFilePath
-> CInt
-> CMode
-> IO CInt
431 foreign import ccall safe
"HsBase.h __hscore_open"
432 c_safe_open
:: CFilePath
-> CInt
-> CMode
-> IO CInt
434 foreign import ccall unsafe
"HsBase.h read"
435 c_read
:: CInt
-> Ptr Word8
-> CSize
-> IO CSsize
437 foreign import ccall safe
"HsBase.h read"
438 c_safe_read
:: CInt
-> Ptr Word8
-> CSize
-> IO CSsize
440 foreign import ccall unsafe
"HsBase.h __hscore_stat"
441 c_stat
:: CFilePath
-> Ptr CStat
-> IO CInt
443 foreign import ccall unsafe
"HsBase.h umask"
444 c_umask
:: CMode
-> IO CMode
446 foreign import ccall unsafe
"HsBase.h write"
447 c_write
:: CInt
-> Ptr Word8
-> CSize
-> IO CSsize
449 foreign import ccall safe
"HsBase.h write"
450 c_safe_write
:: CInt
-> Ptr Word8
-> CSize
-> IO CSsize
452 foreign import ccall unsafe
"HsBase.h __hscore_ftruncate"
453 c_ftruncate
:: CInt
-> COff
-> IO CInt
455 foreign import ccall unsafe
"HsBase.h unlink"
456 c_unlink
:: CString
-> IO CInt
458 foreign import ccall unsafe
"HsBase.h getpid"
461 #if !defined
(mingw32_HOST_OS
) && !defined
(__MINGW32__
)
462 foreign import ccall unsafe
"HsBase.h fcntl_read"
463 c_fcntl_read
:: CInt
-> CInt
-> IO CInt
465 foreign import ccall unsafe
"HsBase.h fcntl_write"
466 c_fcntl_write
:: CInt
-> CInt
-> CLong
-> IO CInt
468 foreign import ccall unsafe
"HsBase.h fcntl_lock"
469 c_fcntl_lock
:: CInt
-> CInt
-> Ptr CFLock
-> IO CInt
471 foreign import ccall unsafe
"HsBase.h fork"
474 foreign import ccall unsafe
"HsBase.h link"
475 c_link
:: CString
-> CString
-> IO CInt
477 foreign import ccall unsafe
"HsBase.h mkfifo"
478 c_mkfifo
:: CString
-> CMode
-> IO CInt
480 foreign import ccall unsafe
"HsBase.h pipe"
481 c_pipe
:: Ptr CInt
-> IO CInt
483 foreign import ccall unsafe
"HsBase.h __hscore_sigemptyset"
484 c_sigemptyset
:: Ptr CSigset
-> IO CInt
486 foreign import ccall unsafe
"HsBase.h __hscore_sigaddset"
487 c_sigaddset
:: Ptr CSigset
-> CInt
-> IO CInt
489 foreign import ccall unsafe
"HsBase.h sigprocmask"
490 c_sigprocmask
:: CInt
-> Ptr CSigset
-> Ptr CSigset
-> IO CInt
492 foreign import ccall unsafe
"HsBase.h tcgetattr"
493 c_tcgetattr
:: CInt
-> Ptr CTermios
-> IO CInt
495 foreign import ccall unsafe
"HsBase.h tcsetattr"
496 c_tcsetattr
:: CInt
-> CInt
-> Ptr CTermios
-> IO CInt
498 foreign import ccall unsafe
"HsBase.h __hscore_utime"
499 c_utime
:: CString
-> Ptr CUtimbuf
-> IO CInt
501 foreign import ccall unsafe
"HsBase.h waitpid"
502 c_waitpid
:: CPid
-> Ptr CInt
-> CInt
-> IO CPid
506 foreign import ccall unsafe
"HsBase.h __hscore_o_rdonly" o_RDONLY
:: CInt
507 foreign import ccall unsafe
"HsBase.h __hscore_o_wronly" o_WRONLY
:: CInt
508 foreign import ccall unsafe
"HsBase.h __hscore_o_rdwr" o_RDWR
:: CInt
509 foreign import ccall unsafe
"HsBase.h __hscore_o_append" o_APPEND
:: CInt
510 foreign import ccall unsafe
"HsBase.h __hscore_o_creat" o_CREAT
:: CInt
511 foreign import ccall unsafe
"HsBase.h __hscore_o_excl" o_EXCL
:: CInt
512 foreign import ccall unsafe
"HsBase.h __hscore_o_trunc" o_TRUNC
:: CInt
515 foreign import ccall unsafe
"HsBase.h __hscore_o_noctty" o_NOCTTY
:: CInt
516 foreign import ccall unsafe
"HsBase.h __hscore_o_nonblock" o_NONBLOCK
:: CInt
517 foreign import ccall unsafe
"HsBase.h __hscore_o_binary" o_BINARY
:: CInt
519 foreign import ccall unsafe
"HsBase.h __hscore_s_isreg" c_s_isreg
:: CMode
-> CInt
520 foreign import ccall unsafe
"HsBase.h __hscore_s_ischr" c_s_ischr
:: CMode
-> CInt
521 foreign import ccall unsafe
"HsBase.h __hscore_s_isblk" c_s_isblk
:: CMode
-> CInt
522 foreign import ccall unsafe
"HsBase.h __hscore_s_isdir" c_s_isdir
:: CMode
-> CInt
523 foreign import ccall unsafe
"HsBase.h __hscore_s_isfifo" c_s_isfifo
:: CMode
-> CInt
525 s_isreg
:: CMode
-> Bool
526 s_isreg cm
= c_s_isreg cm
/= 0
527 s_ischr
:: CMode
-> Bool
528 s_ischr cm
= c_s_ischr cm
/= 0
529 s_isblk
:: CMode
-> Bool
530 s_isblk cm
= c_s_isblk cm
/= 0
531 s_isdir
:: CMode
-> Bool
532 s_isdir cm
= c_s_isdir cm
/= 0
533 s_isfifo
:: CMode
-> Bool
534 s_isfifo cm
= c_s_isfifo cm
/= 0
536 foreign import ccall unsafe
"HsBase.h __hscore_sizeof_stat" sizeof_stat
:: Int
537 foreign import ccall unsafe
"HsBase.h __hscore_st_mtime" st_mtime
:: Ptr CStat
-> IO CTime
538 #ifdef mingw32_HOST_OS
539 foreign import ccall unsafe
"HsBase.h __hscore_st_size" st_size
:: Ptr CStat
-> IO Int64
541 foreign import ccall unsafe
"HsBase.h __hscore_st_size" st_size
:: Ptr CStat
-> IO COff
543 foreign import ccall unsafe
"HsBase.h __hscore_st_mode" st_mode
:: Ptr CStat
-> IO CMode
544 foreign import ccall unsafe
"HsBase.h __hscore_st_dev" st_dev
:: Ptr CStat
-> IO CDev
545 foreign import ccall unsafe
"HsBase.h __hscore_st_ino" st_ino
:: Ptr CStat
-> IO CIno
547 foreign import ccall unsafe
"HsBase.h __hscore_echo" const_echo
:: CInt
548 foreign import ccall unsafe
"HsBase.h __hscore_tcsanow" const_tcsanow
:: CInt
549 foreign import ccall unsafe
"HsBase.h __hscore_icanon" const_icanon
:: CInt
550 foreign import ccall unsafe
"HsBase.h __hscore_vmin" const_vmin
:: CInt
551 foreign import ccall unsafe
"HsBase.h __hscore_vtime" const_vtime
:: CInt
552 foreign import ccall unsafe
"HsBase.h __hscore_sigttou" const_sigttou
:: CInt
553 foreign import ccall unsafe
"HsBase.h __hscore_sig_block" const_sig_block
:: CInt
554 foreign import ccall unsafe
"HsBase.h __hscore_sig_setmask" const_sig_setmask
:: CInt
555 foreign import ccall unsafe
"HsBase.h __hscore_f_getfl" const_f_getfl
:: CInt
556 foreign import ccall unsafe
"HsBase.h __hscore_f_setfl" const_f_setfl
:: CInt
557 foreign import ccall unsafe
"HsBase.h __hscore_f_setfd" const_f_setfd
:: CInt
558 foreign import ccall unsafe
"HsBase.h __hscore_fd_cloexec" const_fd_cloexec
:: CLong
560 #if defined
(HTYPE_TCFLAG_T
)
561 foreign import ccall unsafe
"HsBase.h __hscore_sizeof_termios" sizeof_termios
:: Int
562 foreign import ccall unsafe
"HsBase.h __hscore_sizeof_sigset_t" sizeof_sigset_t
:: Int
564 foreign import ccall unsafe
"HsBase.h __hscore_lflag" c_lflag
:: Ptr CTermios
-> IO CTcflag
565 foreign import ccall unsafe
"HsBase.h __hscore_poke_lflag" poke_c_lflag
:: Ptr CTermios
-> CTcflag
-> IO ()
566 foreign import ccall unsafe
"HsBase.h __hscore_ptr_c_cc" ptr_c_cc
:: Ptr CTermios
-> IO (Ptr Word8
)
569 s_issock
:: CMode
-> Bool
570 #if !defined
(mingw32_HOST_OS
) && !defined
(__MINGW32__
)
571 s_issock cmode
= c_s_issock cmode
/= 0
572 foreign import ccall unsafe
"HsBase.h __hscore_s_issock" c_s_issock
:: CMode
-> CInt
577 foreign import ccall unsafe
"__hscore_bufsiz" dEFAULT_BUFFER_SIZE
:: Int
578 foreign import ccall unsafe
"__hscore_seek_cur" sEEK_CUR
:: CInt
579 foreign import ccall unsafe
"__hscore_seek_set" sEEK_SET
:: CInt
580 foreign import ccall unsafe
"__hscore_seek_end" sEEK_END
:: CInt