[commit: packages/directory] Mistuke-bump-win32-version-bounds, bgamari-patch-1, master: Deduce correct alignment in CTimeSpec using hsc2hs (d4b9980)

git at git.haskell.org git at git.haskell.org
Mon Apr 17 21:34:50 UTC 2017


Repository : ssh://git@git.haskell.org/directory

On branches: Mistuke-bump-win32-version-bounds,bgamari-patch-1,master
Link       : http://ghc.haskell.org/trac/ghc/changeset/d4b9980ad6d63e7ca7e712d25d861eb9f51a98cf/directory

>---------------------------------------------------------------

commit d4b9980ad6d63e7ca7e712d25d861eb9f51a98cf
Author: Phil Ruffwind <rf at rufflewind.com>
Date:   Sun Dec 4 14:17:20 2016 -0500

    Deduce correct alignment in CTimeSpec using hsc2hs
    
    Can't use #{alignment} because that was only added recently (GHC 8.0),
    so we have to resort to some trickery.


>---------------------------------------------------------------

d4b9980ad6d63e7ca7e712d25d861eb9f51a98cf
 System/Directory/Internal/C_utimensat.hsc | 8 +++++---
 System/Directory/Internal/utility.h       | 6 ++++++
 directory.cabal                           | 5 +++--
 3 files changed, 14 insertions(+), 5 deletions(-)

diff --git a/System/Directory/Internal/C_utimensat.hsc b/System/Directory/Internal/C_utimensat.hsc
index 23f844c..f10c659 100644
--- a/System/Directory/Internal/C_utimensat.hsc
+++ b/System/Directory/Internal/C_utimensat.hsc
@@ -10,6 +10,7 @@ module System.Directory.Internal.C_utimensat where
 #ifdef HAVE_SYS_STAT_H
 # include <sys/stat.h>
 #endif
+#include <System/Directory/Internal/utility.h>
 import Prelude ()
 import System.Directory.Internal.Prelude
 import Data.Time.Clock.POSIX (POSIXTime)
@@ -17,10 +18,11 @@ import Data.Time.Clock.POSIX (POSIXTime)
 data CTimeSpec = CTimeSpec EpochTime CLong
 
 instance Storable CTimeSpec where
-    sizeOf    _ = #size struct timespec
-    alignment _ = alignment (undefined :: CInt)
+    sizeOf    _ = #{size struct timespec}
+    -- workaround (hsc2hs for GHC < 8.0 doesn't support #{alignment ...})
+    alignment _ = #{size char[alignof(struct timespec)] }
     poke p (CTimeSpec sec nsec) = do
-      (#poke struct timespec, tv_sec ) p sec
+      (#poke struct timespec, tv_sec)  p sec
       (#poke struct timespec, tv_nsec) p nsec
     peek p = do
       sec  <- #{peek struct timespec, tv_sec } p
diff --git a/System/Directory/Internal/utility.h b/System/Directory/Internal/utility.h
new file mode 100644
index 0000000..cae92a4
--- /dev/null
+++ b/System/Directory/Internal/utility.h
@@ -0,0 +1,6 @@
+#if !defined alignof && __cplusplus < 201103L
+# ifdef STDC_HEADERS
+#  include <stddef.h>
+# endif
+# define alignof(x) offsetof(struct { char c; x m; }, m)
+#endif
diff --git a/directory.cabal b/directory.cabal
index c1bc655..7200487 100644
--- a/directory.cabal
+++ b/directory.cabal
@@ -21,12 +21,13 @@ extra-tmp-files:
     HsDirectoryConfig.h
 
 extra-source-files:
-    changelog.md
+    HsDirectoryConfig.h.in
     README.md
+    System/Directory/Internal/*.h
+    changelog.md
     configure
     configure.ac
     directory.buildinfo
-    HsDirectoryConfig.h.in
     tests/*.hs
     tests/util.inl
 



More information about the ghc-commits mailing list