static constants -- ideas?
Jay Scott
jay at satirist.org
Fri Feb 29 14:06:46 EST 2008
Don Stewart dons at galois.com:
>jay:
>> Don Stewart dons at galois.com:
>> >jay:
>> >> I also have constants that are too large to compile. I am resigned to
>> >> loading them from data files--other solutions seem even worse.
>> ...
>> >> Data.Binary eases the irritation somewhat.
>> >
>> >Did you try bytestring literals (and maybe parsing them in-memory with
>> >Data.Binary)?
I finally squeezed enough time to try it, and it didn't work for me.
--
ghc Overflow.hs
[1 of 1] Compiling Overflow ( Overflow.hs, Overflow.o )
Overflow.hs:8:10:stack overflow: use +RTS -K<size> to increase it
--
where Overflow.hs is in the vicinity of 40M and looks like
--
{-# LANGUAGE OverloadedStrings #-}
module Overflow where
import qualified Data.ByteString.Lazy as S
bigData :: S.ByteString
bigData = "\0\0\0\0\0\5\67\195\0\0\0\0...
--
I didn't compress it, because Codec.Compression.GZip didn't compile for
me. It looked like a library change since 6.6 broke it.
Is there a handy string escaping function in the libraries somewhere? It
only took a minute to write one, and I spent longer than that looking,
so maybe it's the wrong question.... Surely it's in there somewhere, and
I'm just 2 dum 2 c.
Jay
More information about the Glasgow-haskell-users
mailing list