static constants -- ideas?

Jay Scott jay at satirist.org
Fri Feb 29 13:26:31 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)?
>> 
>> That didn't occur to me, since neither of my large constants includes
>> strings.... I think you're suggesting that each constant could appear in
>> the source as a long bytestring and be deserialized into the data
>> structure. If that works, it should improve the startup time, but it's
>> still not as nice as simply compiling it straight up.
>> 
>> I'll try it.
>
>Here's an example, which stores a Data.Map in a gzip-compressed
>bytestring literal (a C
>string literal in the compiled code). The Map is reconstructed on
>startup.
>
>    {-# LANGUAGE OverloadedStrings #-}
>
>    import Data.Binary
>    import qualified Data.Map as M
>    import qualified Data.ByteString.Char8 as S
>    import Data.ByteString.Lazy
>    import Codec.Compression.GZip
>
>    --
>    -- this is a gzip compressed literal bytestring, storing a binary-
>encoded Data.Map
>    --
>    mytable =
>        "\US\139\b\NUL\NUL\NUL\NUL\NUL\NUL\ETXEN\219\SO\194 \f\197\224
>\188\196\CAN\227\US\224\171~\NAKc\GS4ce\161`\178\191\215(\176\190\180\167
>\231\210\n\241\171\203\191\ti\157\217\149\249< \ENQ\214\&9>\202\162\179a
>\132X\233\ESC=\231\215\164\SYN\157\DC2D\226*\146\174o\t\167\DLE\209\"i_
>\240\193\129\199<W\250nC\CAN\212\CAN\162J\160\141C\178\133\216;\\@4\144-W
>\203\209x\205\140\166\RS\163\237]9f\170\143\ACK\163g\223\STX\184\&7\rH
>\222\FSW\130\&7D\197\NUL\164\&0U\193\186\t\186o\228\180~\NUL\a6\249\137#
>\SOH\NUL\NUL"
>
>    main = print =<< M.lookup "ghc" m
>        where
>            -- build the table from the bytestring:
>            m :: M.Map String (Maybe String)
>            m = decode . decompress . fromChunks . return $ mytable
>
>Running it:
>
>    $ ./A
>    Just "dinosaur!"
>
>:)
>
>Important to use a bytestring, since that gets compiled to a C string
>literal (and not messed
>with by the simplifier).
>
>-- Don
>




More information about the Glasgow-haskell-users mailing list