Removal of #include <HsFFI.h> from template-hsc.h breaks largefile support on 32bit Linux

Simon Marlow marlowsd at gmail.com
Thu Feb 16 13:25:36 CET 2012


On 15/02/2012 12:31, Eugene Crosser wrote:
> Hello all,
>
> I am new here, but I want to report what I suspect may be a problem.
>
> I ran into it while using some third-party package from hackage on a
> 32bit Linux with ghc 7.4.1. I discovered that off_t fields in the .hsc
> files in the package where interpreted as 32bit words. I suspected that
> 64bit offsets should be used because even 32bit Linux has "largefile"
> support with 64bit offsets.
>
> I found that earlier versions of hsc2hs included HsFFI.h into the
> generated C code, and HsFFI.h in turn indirectly includes ghcautoconf.h
> which has
>
> #define _FILE_OFFSET_BITS 64
>
> in it. So, if I build the .hsc files like this:
>
> hsc2hs -i HsFFI.h filename.hsc
>
> then off_t is 64bit and 64bit file manipulation syscalls are used. I did
> not check it but I think that earlier versions of hsc2hs where creating
> largefile-aware version of the code by default, because HsFFI.h was
> included in the code by default.
>
> This is a simple test program:
>
> ==== checktypes.hsc ====
> -- run like this: hsc2hs checktypes.hsc&&  runhaskell checktypes.hs
> module Main where
> #include<sys/types.h>
> main = do
>    putStrLn $ show (#size off_t)
> ========================
>
> $ hsc2hs checktypes.hsc&&  runhaskell checktypes.hs
> 4
> $ hsc2hs -i HsFFI.h checktypes.hsc&&  runhaskell checktypes.hs
> 8
>
> As I understand, this situation means that while the ghc itself and
> haskell programs compiled by it are largefile-capable, any third party
> modules that contain .hsc files are not. If I am right, this is probably
> not a good thing.
>
> Please can some guru take a look at this issue?

Guru at your service :-)

We discovered this during the 7.4 cycle:

   http://hackage.haskell.org/trac/ghc/ticket/2897#comment:12

Packages that were relying on `HsFFI.h` to define `_FILE_OFFSET_BITS` 
should no longer do this, instead they should use an appropriate 
autoconf script or some other method.  See the `unix` package for an 
example of how to do this.  It was really a mistake that it worked before.

Cheers,
	Simon



>
> See also:
> http://www.haskell.org/pipermail/glasgow-haskell-users/2009-February/016606.html
> http://www.haskell.org/pipermail/cvs-ghc/2011-September/065848.html
>
> Thanks,
>
> Eugene
>
>
>
>
> _______________________________________________
> Glasgow-haskell-users mailing list
> Glasgow-haskell-users at haskell.org
> http://www.haskell.org/mailman/listinfo/glasgow-haskell-users




More information about the Glasgow-haskell-users mailing list