aboutsummaryrefslogtreecommitdiff
path: root/Utility/Touch
diff options
context:
space:
mode:
authorGravatar Joey Hess <joeyh@joeyh.name>2016-02-15 11:47:33 -0400
committerGravatar Joey Hess <joeyh@joeyh.name>2016-02-15 11:47:33 -0400
commitcd8e2e4eeb70d22f9a7daa375474d80aa188574b (patch)
tree6b3f01c14a5b64e40c15210d3baf916825a47dcb /Utility/Touch
parent98a2b312fd0297dcb09f6efdc3bd2e3b05b6dfc0 (diff)
move old ghc compat code into separate module; eliminate WITH_CLIBS
This avoids hsc2hs being run except when building for the old version of ghc. Should speed up builds.
Diffstat (limited to 'Utility/Touch')
-rw-r--r--Utility/Touch/Old.hsc123
1 files changed, 123 insertions, 0 deletions
diff --git a/Utility/Touch/Old.hsc b/Utility/Touch/Old.hsc
new file mode 100644
index 000000000..5345285f4
--- /dev/null
+++ b/Utility/Touch/Old.hsc
@@ -0,0 +1,123 @@
+{- Compatability interface for old version of unix, to be removed eventally.
+ -
+ - Copyright 2011 Joey Hess <id@joeyh.name>
+ -
+ - License: BSD-2-clause
+ -}
+
+{-# LANGUAGE ForeignFunctionInterface, CPP #-}
+
+module Utility.Touch.Old (
+ TimeSpec(..),
+ touchBoth,
+ touch
+) where
+
+#include <sys/types.h>
+#include <sys/stat.h>
+#include <fcntl.h>
+#include <sys/time.h>
+
+#ifndef _BSD_SOURCE
+#define _BSD_SOURCE
+#endif
+
+#if (defined UTIME_OMIT && defined UTIME_NOW && defined AT_FDCWD && defined AT_SYMLINK_NOFOLLOW)
+#define use_utimensat 1
+
+import Utility.FileSystemEncoding
+
+import Control.Monad (when)
+import Foreign
+#endif
+
+import Foreign.C
+
+newtype TimeSpec = TimeSpec CTime
+
+touchBoth :: FilePath -> TimeSpec -> TimeSpec -> Bool -> IO ()
+
+touch :: FilePath -> TimeSpec -> Bool -> IO ()
+touch file mtime = touchBoth file mtime mtime
+
+#ifdef use_utimensat
+
+at_fdcwd :: CInt
+at_fdcwd = #const AT_FDCWD
+
+at_symlink_nofollow :: CInt
+at_symlink_nofollow = #const AT_SYMLINK_NOFOLLOW
+
+instance Storable TimeSpec where
+ -- use the larger alignment of the two types in the struct
+ alignment _ = max sec_alignment nsec_alignment
+ where
+ sec_alignment = alignment (1::CTime)
+ nsec_alignment = alignment (1::CLong)
+ sizeOf _ = #{size struct timespec}
+ peek ptr = do
+ sec <- #{peek struct timespec, tv_sec} ptr
+ return $ TimeSpec sec
+ poke ptr (TimeSpec sec) = do
+ #{poke struct timespec, tv_sec} ptr sec
+ #{poke struct timespec, tv_nsec} ptr (0 :: CLong)
+
+{- While its interface is beastly, utimensat is in recent
+ POSIX standards, unlike lutimes. -}
+foreign import ccall "utimensat"
+ c_utimensat :: CInt -> CString -> Ptr TimeSpec -> CInt -> IO CInt
+
+touchBoth file atime mtime follow =
+ allocaArray 2 $ \ptr ->
+ withFilePath file $ \f -> do
+ pokeArray ptr [atime, mtime]
+ r <- c_utimensat at_fdcwd f ptr flags
+ when (r /= 0) $ throwErrno "touchBoth"
+ where
+ flags
+ | follow = 0
+ | otherwise = at_symlink_nofollow
+
+#else
+#if 0
+{- Using lutimes is needed for BSD.
+ -
+ - TODO: test if lutimes is available. May have to do it in configure.
+ - TODO: TimeSpec uses a CTime, while tv_sec is a CLong. It is implementation
+ - dependent whether these are the same; need to find a cast that works.
+ - (Without the cast it works on linux i386, but
+ - maybe not elsewhere.)
+ -}
+
+instance Storable TimeSpec where
+ alignment _ = alignment (1::CLong)
+ sizeOf _ = #{size struct timeval}
+ peek ptr = do
+ sec <- #{peek struct timeval, tv_sec} ptr
+ return $ TimeSpec sec
+ poke ptr (TimeSpec sec) = do
+ #{poke struct timeval, tv_sec} ptr sec
+ #{poke struct timeval, tv_usec} ptr (0 :: CLong)
+
+foreign import ccall "utimes"
+ c_utimes :: CString -> Ptr TimeSpec -> IO CInt
+foreign import ccall "lutimes"
+ c_lutimes :: CString -> Ptr TimeSpec -> IO CInt
+
+touchBoth file atime mtime follow =
+ allocaArray 2 $ \ptr ->
+ withFilePath file $ \f -> do
+ pokeArray ptr [atime, mtime]
+ r <- syscall f ptr
+ when (r /= 0) $
+ throwErrno "touchBoth"
+ where
+ syscall
+ | follow = c_lutimes
+ | otherwise = c_utimes
+
+#else
+#warning "utimensat and lutimes not available; building without symlink timestamp preservation support"
+touchBoth _ _ _ _ = return ()
+#endif
+#endif