{-# OPTIONS_GHC -fglasgow-exts #-} {-# LANGUAGE ForeignFunctionInterface #-} module System.Posix where import Foreign.Ptr ( Ptr, castPtr, plusPtr ) import Foreign.Storable ( peek, poke, sizeOf ) import Foreign.C.Types ( CInt, CUInt, CULong, CTime ) import Foreign.C.String ( CString, withCString ) import Foreign.Marshal.Alloc ( allocaBytes ) import System.Posix.Types ( EpochTime ) import System.IO ( Handle ) foreign import ccall "sys/utime.h _utime" c_utime :: CString -> Ptr a -> IO CInt setFileTimes :: FilePath -> EpochTime -> EpochTime -> IO () setFileTimes path atime mtime = path `withCString` \s -> do allocaBytes 8 $ \p -> do poke (castPtr p :: Ptr CTime) (atime) poke (castPtr (plusPtr p 4) :: Ptr CTime) (mtime) c_utime s p return () foreign import ccall "time" c_ctime :: Ptr CTime -> IO CInt epochTime :: IO EpochTime epochTime = do allocaBytes (sizeOf (undefined :: CTime)) $ \p -> do c_ctime p t <- peek p :: IO CTime return t foreign import stdcall "winbase.h SleepEx" c_SleepEx :: CULong -> CUInt -> IO CInt sleep :: Integer -> IO CInt sleep n = c_SleepEx (1000 * fromIntegral n) 1 handleToFd :: Handle -> IO Int handleToFd _ = fail "handleToFd not supported!"