{-# LINE 1 "System/Posix/Unistd.hsc" #-}{-# LANGUAGE CApiFFI #-}{-# LANGUAGE NondecreasingIndentation #-}{-# LANGUAGE Safe #-}------------------------------------------------------------------------------- |-- Module : System.Posix.Unistd-- Copyright : (c) The University of Glasgow 2002-- License : BSD-style (see the file libraries/base/LICENSE)---- Maintainer : libraries@haskell.org-- Stability : provisional-- Portability : non-portable (requires POSIX)---- POSIX miscellaneous stuff, mostly from unistd.h-------------------------------------------------------------------------------moduleSystem.Posix.Unistd(-- * System environmentSystemID (..),getSystemID ,SysVar (..),getSysVar ,-- * Sleepingsleep ,usleep ,nanosleep ,-- * File synchronisationfileSynchronise ,fileSynchroniseDataOnly ,{-
 ToDo from unistd.h:
 confstr,
 lots of sysconf variables
 -- use Network.BSD
 gethostid, gethostname
 -- should be in System.Posix.Files?
 pathconf, fpathconf,
 -- System.Posix.Signals
 ualarm,
 -- System.Posix.IO
 read, write,
 -- should be in System.Posix.User?
 getEffectiveUserName,
-})whereimportForeign.C.ErrorimportForeign.C.String(peekCString)importForeign.C.TypesimportForeignimportSystem.Posix.TypesimportSystem.Posix.Internals{-# LINE 68 "System/Posix/Unistd.hsc" #-}-- ------------------------------------------------------------------------------- System environment (uname())dataSystemID =SystemID {SystemID -> String
systemName ::String,SystemID -> String
nodeName ::String,SystemID -> String
release ::String,SystemID -> String
version ::String,SystemID -> String
machine ::String}getSystemID ::IOSystemID getSystemID :: IO SystemID
getSystemID =doInt -> (Ptr CUtsname -> IO SystemID) -> IO SystemID
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes(Int
390)((Ptr CUtsname -> IO SystemID) -> IO SystemID)
-> (Ptr CUtsname -> IO SystemID) -> IO SystemID
forall a b. (a -> b) -> a -> b
$\Ptr CUtsname
p_sid ->do{-# LINE 83 "System/Posix/Unistd.hsc" #-}throwErrnoIfMinus1_"getSystemID"(c_unamep_sid)sysN<-peekCString(((\hsc_ptr->hsc_ptr`plusPtr`0))p_sid){-# LINE 85 "System/Posix/Unistd.hsc" #-}node<-peekCString(((\hsc_ptr->hsc_ptr`plusPtr`65))p_sid){-# LINE 86 "System/Posix/Unistd.hsc" #-}rel<-peekCString(((\hsc_ptr->hsc_ptr`plusPtr`130))p_sid){-# LINE 87 "System/Posix/Unistd.hsc" #-}ver<-peekCString(((\hsc_ptr->hsc_ptr`plusPtr`195))p_sid){-# LINE 88 "System/Posix/Unistd.hsc" #-}mach<-peekCString(((\hsc_ptr->hsc_ptr`plusPtr`260))p_sid){-# LINE 89 "System/Posix/Unistd.hsc" #-}return(SystemID{systemName=sysN,nodeName=node,release=rel,version=ver,machine=mach})foreignimportccallunsafe"uname"c_uname ::PtrCUtsname->IOCInt-- ------------------------------------------------------------------------------- sleeping-- | Sleep for the specified duration (in seconds). Returns the time remaining-- (if the sleep was interrupted by a signal, for example).---- /GHC Note/: 'Control.Concurrent.threadDelay' is a better choice. Since GHC-- uses signals for its internal clock, a call to 'sleep' will usually be-- interrupted immediately. That makes 'sleep' unusable in a program compiled-- with GHC, unless the RTS timer is disabled (with @+RTS -V0@). Furthermore,-- without the @-threaded@ option, 'sleep' will block all other user threads.-- Even with the @-threaded@ option, 'sleep' requires a full OS thread to-- itself. 'Control.Concurrent.threadDelay' has none of these shortcomings.--sleep ::Int->IOIntsleep :: Int -> IO Int
sleep Int
0=Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
returnInt
0sleep Int
secs =doCUInt
r <-CUInt -> IO CUInt
c_sleep (Int -> CUInt
forall a b. (Integral a, Num b) => a -> b
fromIntegralInt
secs );Int -> IO Int
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return(CUInt -> Int
forall a b. (Integral a, Num b) => a -> b
fromIntegralCUInt
r ){-# WARNINGsleep"This function has several shortcomings (see documentation). Please consider using Control.Concurrent.threadDelay instead."#-}foreignimportccallsafe"sleep"c_sleep ::CUInt->IOCUInt-- | Sleep for the specified duration (in microseconds).---- /GHC Note/: 'Control.Concurrent.threadDelay' is a better choice.-- Without the @-threaded@ option, 'usleep' will block all other user-- threads. Even with the @-threaded@ option, 'usleep' requires a-- full OS thread to itself. 'Control.Concurrent.threadDelay' has-- neither of these shortcomings.--usleep ::Int->IO(){-# LINE 132 "System/Posix/Unistd.hsc" #-}usleepusecs=nanosleep(fromIntegralusecs*1000){-# LINE 149 "System/Posix/Unistd.hsc" #-}-- | Sleep for the specified duration (in nanoseconds)---- /GHC Note/: the comment for 'usleep' also applies here.nanosleep ::Integer->IO(){-# LINE 158 "System/Posix/Unistd.hsc" #-}nanosleep :: Integer -> IO ()
nanosleep Integer
0=() -> IO ()
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return()nanosleep Integer
nsecs =doInt -> (Ptr CTimeSpec -> IO ()) -> IO ()
forall a b. Int -> (Ptr a -> IO b) -> IO b
allocaBytes(Int
16)((Ptr CTimeSpec -> IO ()) -> IO ())
-> (Ptr CTimeSpec -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$\Ptr CTimeSpec
pts1 ->do{-# LINE 161 "System/Posix/Unistd.hsc" #-}allocaBytes(16)$\pts2->do{-# LINE 162 "System/Posix/Unistd.hsc" #-}let(tv_sec0,tv_nsec0)=nsecs`divMod`1000000000letlooptv_sectv_nsec=do((\hsc_ptr->pokeByteOffhsc_ptr0))pts1tv_sec{-# LINE 166 "System/Posix/Unistd.hsc" #-}((\hsc_ptr->pokeByteOffhsc_ptr8))pts1tv_nsec{-# LINE 167 "System/Posix/Unistd.hsc" #-}res<-c_nanosleeppts1pts2ifres==0thenreturn()elsedoerrno<-getErrnoiferrno==eINTRthendotv_sec'<-((\hsc_ptr->peekByteOffhsc_ptr0))pts2{-# LINE 174 "System/Posix/Unistd.hsc" #-}tv_nsec'<-((\hsc_ptr->peekByteOffhsc_ptr8))pts2{-# LINE 175 "System/Posix/Unistd.hsc" #-}looptv_sec'tv_nsec'elsethrowErrno"nanosleep"loop(fromIntegraltv_sec0::CTime)(fromIntegraltv_nsec0::CTime)data{-# CTYPE"struct timespec"#-}CTimeSpec foreignimportcapisafe"HsUnix.h nanosleep"c_nanosleep ::PtrCTimeSpec ->PtrCTimeSpec ->IOCInt{-# LINE 184 "System/Posix/Unistd.hsc" #-}-- ------------------------------------------------------------------------------- System variablesdataSysVar =ArgumentLimit |ChildLimit |ClockTick |GroupLimit |OpenFileLimit |PosixVersion |HasSavedIDs |HasJobControl -- ToDo: lots moregetSysVar ::SysVar ->IOIntegergetSysVar :: SysVar -> IO Integer
getSysVar SysVar
v =caseSysVar
v ofSysVar
ArgumentLimit ->CInt -> IO Integer
sysconf (CInt
0){-# LINE 202 "System/Posix/Unistd.hsc" #-}ChildLimit->sysconf(1){-# LINE 203 "System/Posix/Unistd.hsc" #-}ClockTick->sysconf(2){-# LINE 204 "System/Posix/Unistd.hsc" #-}GroupLimit->sysconf(3){-# LINE 205 "System/Posix/Unistd.hsc" #-}OpenFileLimit->sysconf(4){-# LINE 206 "System/Posix/Unistd.hsc" #-}PosixVersion->sysconf(29){-# LINE 207 "System/Posix/Unistd.hsc" #-}HasSavedIDs->sysconf(8){-# LINE 208 "System/Posix/Unistd.hsc" #-}HasJobControl->sysconf(7){-# LINE 209 "System/Posix/Unistd.hsc" #-}sysconf ::CInt->IOIntegersysconf :: CInt -> IO Integer
sysconf CInt
n =doCLong
r <-String -> IO CLong -> IO CLong
forall a. (Eq a, Num a) => String -> IO a -> IO a
throwErrnoIfMinus1String
"getSysVar"(CInt -> IO CLong
c_sysconf CInt
n )Integer -> IO Integer
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return(CLong -> Integer
forall a b. (Integral a, Num b) => a -> b
fromIntegralCLong
r )foreignimportccallunsafe"sysconf"c_sysconf ::CInt->IOCLong-- ------------------------------------------------------------------------------- File synchronization-- | Performs @fsync(2)@ operation on file-descriptor.---- Throws 'IOError' (\"unsupported operation\") if platform does not-- provide @fsync(2)@ (use @#if HAVE_FSYNC@ CPP guard to-- detect availability).---- @since 2.7.1.0fileSynchronise ::Fd->IO(){-# LINE 230 "System/Posix/Unistd.hsc" #-}fileSynchronisefd=dothrowErrnoIfMinus1_"fileSynchronise"(c_fsyncfd)foreignimportcapisafe"unistd.h fsync"c_fsync ::Fd->IOCInt{-# LINE 241 "System/Posix/Unistd.hsc" #-}-- | Performs @fdatasync(2)@ operation on file-descriptor.---- Throws 'IOError' (\"unsupported operation\") if platform does not-- provide @fdatasync(2)@ (use @#if HAVE_FDATASYNC@ CPP guard to-- detect availability).---- @since 2.7.1.0fileSynchroniseDataOnly ::Fd->IO(){-# LINE 251 "System/Posix/Unistd.hsc" #-}fileSynchroniseDataOnlyfd=dothrowErrnoIfMinus1_"fileSynchroniseDataOnly"(c_fdatasyncfd)foreignimportcapisafe"unistd.h fdatasync"c_fdatasync ::Fd->IOCInt{-# LINE 262 "System/Posix/Unistd.hsc" #-}

AltStyle によって変換されたページ (->オリジナル) /