Dave Bayer wrote:
> What is the best way to embed an arbitrary file in a Haskell program?

I don't know the best way. I'd probably use FFI.

main.hs:
  {-# LANGUAGE ForeignFunctionInterface #-}
  module Main where
  
  import Foreign
  import Foreign.ForeignPtr
  import qualified Data.ByteString as B
  import qualified Data.ByteString.Internal as BI
  
  foreign import ccall "& hello" hello :: Ptr Word8
  foreign import ccall "& hello_size" helloSize :: Ptr Int
  
  main = do
      helloSize' <- peek helloSize
      hello' <- newForeignPtr_ hello
      let helloBS = BI.PS hello' 0 helloSize'
      B.putStr helloBS

hello.c:
  char hello[] = "Hello, world!\n";
  int hello_size = sizeof(hello);

Test:
  # ghc -O -o main main.hs hello.c -package bytestring
  # ./main 
  Hello, world!

The idea is then to use some existing tool that embeds binary
data in C programs.

Bertram
_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe

Reply via email to