[commit: packages/directory] master: Split Internal module to avoid #ifdef hell (f028566)
git at git.haskell.org
git at git.haskell.org
Fri Dec 18 09:51:17 UTC 2015
Repository : ssh://git@git.haskell.org/directory
On branch : master
Link : http://ghc.haskell.org/trac/ghc/changeset/f0285668fcbe4154f6b6f38af9b971c08df838fb/directory
>---------------------------------------------------------------
commit f0285668fcbe4154f6b6f38af9b971c08df838fb
Author: Phil Ruffwind <rf at rufflewind.com>
Date: Mon Jun 1 23:38:37 2015 -0400
Split Internal module to avoid #ifdef hell
>---------------------------------------------------------------
f0285668fcbe4154f6b6f38af9b971c08df838fb
System/Directory/Internal.hsc | 50 +++++-----------------
.../{Internal.hsc => Internal/C_utimensat.hsc} | 20 +++------
directory.cabal | 1 +
3 files changed, 16 insertions(+), 55 deletions(-)
diff --git a/System/Directory/Internal.hsc b/System/Directory/Internal.hsc
index e20187b..11bbfa8 100644
--- a/System/Directory/Internal.hsc
+++ b/System/Directory/Internal.hsc
@@ -1,53 +1,23 @@
-module System.Directory.Internal where
-
#include <HsDirectory.h>
#ifndef mingw32_HOST_OS
# include <HsUnixConfig.h>
#endif
+module System.Directory.Internal
+ ( module System.Directory.Internal
+
+#ifdef HAVE_UTIMENSAT
+ , module System.Directory.Internal.C_utimensat
+#endif
+
+) where
+
#ifdef HAVE_UTIMENSAT
-# include <fcntl.h>
-# include <sys/stat.h>
-import Data.Time.Clock.POSIX (POSIXTime)
-import Foreign
-import Foreign.C
-import System.Posix.Types
+import System.Directory.Internal.C_utimensat
#endif
-- | Filename extension for executable files (including the dot if any)
-- (usually @\"\"@ on POSIX systems and @\".exe\"@ on Windows or OS\/2).
exeExtension :: String
exeExtension = (#const_str EXE_EXTENSION)
-
-#ifdef HAVE_UTIMENSAT
-
-data CTimeSpec = CTimeSpec EpochTime CLong
-
-instance Storable CTimeSpec where
- sizeOf _ = #size struct timespec
- alignment _ = alignment (undefined :: CInt)
- poke p (CTimeSpec sec nsec) = do
- (#poke struct timespec, tv_sec ) p sec
- (#poke struct timespec, tv_nsec) p nsec
- peek p = do
- sec <- #{peek struct timespec, tv_sec } p
- nsec <- #{peek struct timespec, tv_nsec} p
- return (CTimeSpec sec nsec)
-
-c_AT_FDCWD :: Integral a => a
-c_AT_FDCWD = (#const AT_FDCWD)
-
-utimeOmit :: CTimeSpec
-utimeOmit = CTimeSpec (CTime 0) (#const UTIME_OMIT)
-
-toCTimeSpec :: POSIXTime -> CTimeSpec
-toCTimeSpec t = CTimeSpec (CTime sec) (truncate $ 10 ^ (9 :: Int) * frac)
- where
- (sec, frac) = if frac' < 0 then (sec' - 1, frac' + 1) else (sec', frac')
- (sec', frac') = properFraction (toRational t)
-
-foreign import ccall unsafe "utimensat" c_utimensat
- :: CInt -> CString -> Ptr CTimeSpec -> CInt -> IO CInt
-
-#endif // HAVE_UTIMENSAT
diff --git a/System/Directory/Internal.hsc b/System/Directory/Internal/C_utimensat.hsc
similarity index 75%
copy from System/Directory/Internal.hsc
copy to System/Directory/Internal/C_utimensat.hsc
index e20187b..7996f18 100644
--- a/System/Directory/Internal.hsc
+++ b/System/Directory/Internal/C_utimensat.hsc
@@ -1,26 +1,16 @@
-module System.Directory.Internal where
-
-#include <HsDirectory.h>
-
#ifndef mingw32_HOST_OS
# include <HsUnixConfig.h>
#endif
+#include <fcntl.h>
+#include <sys/stat.h>
+
+module System.Directory.Internal.C_utimensat where
#ifdef HAVE_UTIMENSAT
-# include <fcntl.h>
-# include <sys/stat.h>
import Data.Time.Clock.POSIX (POSIXTime)
import Foreign
import Foreign.C
import System.Posix.Types
-#endif
-
--- | Filename extension for executable files (including the dot if any)
--- (usually @\"\"@ on POSIX systems and @\".exe\"@ on Windows or OS\/2).
-exeExtension :: String
-exeExtension = (#const_str EXE_EXTENSION)
-
-#ifdef HAVE_UTIMENSAT
data CTimeSpec = CTimeSpec EpochTime CLong
@@ -50,4 +40,4 @@ toCTimeSpec t = CTimeSpec (CTime sec) (truncate $ 10 ^ (9 :: Int) * frac)
foreign import ccall unsafe "utimensat" c_utimensat
:: CInt -> CString -> Ptr CTimeSpec -> CInt -> IO CInt
-#endif // HAVE_UTIMENSAT
+#endif
diff --git a/directory.cabal b/directory.cabal
index 3ba045c..b4c1458 100644
--- a/directory.cabal
+++ b/directory.cabal
@@ -62,6 +62,7 @@ Library
System.Directory
other-modules:
System.Directory.Internal
+ System.Directory.Internal.C_utimensat
c-sources:
cbits/directory.c
More information about the ghc-commits
mailing list