How to use Data.Compact.Serialize

Christopher Done chrisdone at gmail.com
Wed Dec 19 10:31:28 UTC 2018


Hi,

On the docs for Data.Compact.Serialize it says:

http://hackage.haskell.org/package/compact-0.1.0.1/docs/Data-Compact-Serialize.html
> Our binary representation contains direct pointers to the info tables
> of objects in the region. This means that the info tables of the
> receiving process must be laid out in exactly the same way as from the
> original process; in practice, this means using static linking, using
> the exact same binary and turning off ASLR.

It seems to me that in order to use this module in any practical way
(i.e. write to file from one process, and then a later run of the
process reads it), you need to know a special way to build your binary
which isn't fully described here. What flags, for example, should be
passed to GHC to make this viable?

* Turning off ASLR on Linux is done by writing 0 to
  /proc/sys/kernel/randomize_va_space, which applies to all
  programs. That's not the most isolated way to deploy an app, but I
  discovered that you can set this per process here:
  https://askubuntu.com/a/507954
* To compile GHC programs statically, use -optl-static -optl-pthread.

So in total the example would be:

$ stack build compact
compact-0.1.0.1: download
compact-0.1.0.1: configure
compact-0.1.0.1: build
compact-0.1.0.1: copy/register

Example file from docs:

$ cat main.hs
{-# LANGUAGE TypeApplications #-}
import System.Environment
import Data.Compact
import Data.Compact.Serialize
main = do
  arg:_ <- getArgs
  case arg of
    "write" -> do
      orig_c <- compact ("I want to serialize this", True)
      writeCompact @(String, Bool) "somefile" orig_c
    "read" -> do
      res <- unsafeReadCompact @(String, Bool) "somefile"
      case res of
        Left err -> fail err
        Right c -> print (getCompact c)

Compiling statically:

$ stack ghc -- -optl-static -optl-pthread main.hs
[1 of 1] Compiling Main             ( main.hs, main.o )
Linking main ...
[...hundred more warnings like this ...]

Check that it's static:

$ ldd main
not a dynamic executable

Write the file:

$ setarch `uname -m` -R ./main write

Read the file:

$ setarch `uname -m` -R ./main read
("I want to serialize this",True)

Can a GHC dev confirm that this is the proper way to do this? If so,
I'll contribute this little example as documentation to the compact package.

Cheers


More information about the ghc-devs mailing list