
#14741: High-memory usage during compilation using Template Haskell -------------------------------------+------------------------------------- Reporter: donatello | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.2.2 Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by donatello): No, compiling with `-O0` or `-O2` has no effect. I see that embedding a 3MB file takes over 2.5GB of RAM! I have updated the code to use only cabal and have managed to inline specific parts of `file-embed` (I am not very familiar with template haskell) - the problem still persists. Now I am only trying to embed a 3MB file (created by the Makefile). https://github.com/donatello/file-embed-exp Pasting some relevant bits of code here: == EmbedFile.hs {{{ {-# LANGUAGE TemplateHaskell #-} module EmbedFile (embedFile) where import qualified Data.ByteString as B import qualified Data.ByteString.Char8 as B8 import Data.ByteString.Unsafe (unsafePackAddressLen) import Language.Haskell.TH.Syntax (Exp (AppE, ListE, LitE, SigE, TupE, VarE), Lit (IntegerL, StringL, StringPrimL), Q, Quasi (qAddDependentFile), loc_filename, qLocation, runIO) import System.IO.Unsafe (unsafePerformIO) bsToExp :: B.ByteString -> Q Exp bsToExp bs = return $ VarE 'unsafePerformIO `AppE` (VarE 'unsafePackAddressLen `AppE` LitE (IntegerL $ fromIntegral $ B8.length bs) `AppE` LitE (StringPrimL $ B.unpack bs)) embedFile :: FilePath -> Q Exp embedFile fp = qAddDependentFile fp >> (runIO $ B.readFile fp) >>= bsToExp }}} == Static.hs {{{ {-# LANGUAGE TemplateHaskell #-} module Static ( embedList ) where import qualified Data.ByteString as B import System.IO (FilePath) import EmbedFile (embedFile) embedList :: [(FilePath, B.ByteString)] embedList = [("mypath", $(embedFile "build/3mb"))] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/14741#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler