
On 10/13/08, Andrew Coppin wrote:
Cool. Is there any progress on getting GHC to *not* freak out when you ask it to compile a CAF containing several hundred KB of string literal? :-}
Yes and no. There's dons' compiled-constants pkg which has a solution: http://code.haskell.org/~dons/code/compiled-constants/ And the code below would do all the haskell-side work for importing the data from C, but I'm not aware of a way to have ghc not freak out if it has to compile a huge amount of static data. ------------------------------------------------------------------------------- {-# LANGUAGE TemplateHaskell #-} module FromC (fromC) where import GHC.Ptr(Ptr(Ptr)) import Foreign.C.Types(CChar) import System.IO.Unsafe(unsafePerformIO) import Data.ByteString.Unsafe(unsafePackAddressLen) import Data.ByteString(ByteString) import Language.Haskell.TH.Syntax import Language.Haskell.TH.Lib -- | -- If in asdf.c == @unsigned char stuff[1024] = {42,.....,19};@, then -- -- > $(fromC "./asdf.c" "stuff" "dat") --- -- will produce: -- -- > foreign import ccall unsafe "&" stuff :: Ptr CChar -- > dat :: ByteString -- > dat = unsafePerformIO (case stuff of -- > Ptr addr_0 -> unsafePackAddressLen 1024 addr_0) -- fromC :: FilePath -> String -> Int -> String -> Q [Dec] fromC cfile cvar bytes hsvar = do let hsname = mkName hsvar t <- [t|ByteString|] e <- [|unsafePerformIO (case $(varE . mkName $ cvar) of Ptr addr -> unsafePackAddressLen bytes addr) |] return [ ForeignD (ImportF CCall Unsafe "&" (mkName cvar) (AppT (ConT ''Ptr) (ConT ''CChar))) , SigD hsname t , ValD (VarP hsname) (NormalB e) []] -------------------------------------------------------------------------------