Poor man Haskell serialisation using TH, was: Re: [Haskell-cafe] Haskell serialisation

Pasqualino 'Titto' Assini tittoassini at gmail.com
Thu Jun 21 11:35:47 EDT 2007


Hi Bulat,

I was thinking of something like this (warning: I have never used TH before):

> {-# OPTIONS -fth #-}
> module SerialiseTest where
> import Language.Haskell.TH

We have an application whose state is a function Int->Int.

We want to be able to serialise this state so that, for example, we might 
transfer it to a remote location.

To do so we preserve both the state and its Template Haskell representation:
 
> type State = (Int -> Int,ExpQ)

This is the initial state:

> initState :: State
> initState =  (id,[|id|])  

The state is modified by composition with the existing state:

> modifyState (f,e) (nf,ne) = (nf . f , [| $(ne) . $(e) |] )   

Some examples of state changing operations:

> op1 state = modifyState state ((+4),[|(+4)|])
> op2 state = modifyState state ((*2),[|(*2)|])

By the way, there must be a way of writing in TH a macro that avoids these 
repetitions of the same function so that we just write $(ser (*2)) rather 
then ((*2),[|(*2)|]).

> main = do

Now a little test, we start with our initial state:
 
>          let st0 = initState

Apply a couple of operations:

>          let st1 = op1 st0
>          let st2 = op2 st1 

Let's see what we got:

>          let (f2,e2) = st2
>          printCode e2
>          putStrLn . show $ f2 5
>          where printCode ast = runQ ast >>= putStrLn . pprint

This prints:

(GHC.Num.* 2) GHC.Base.. ((GHC.Num.+ 4) GHC.Base.. GHC.Base.id)
18

So, the state is both applicable and serialisable (on the receiving side we 
should naturally have an interpreter for the TH representation).

Not very efficient, but it kind of works :-)

Best,

      titto

On Thursday 21 June 2007 13:27:07 Bulat Ziganshin wrote:
> Hello Pasqualino,
>
> Thursday, June 21, 2007, 3:55:35 PM, you wrote:
> > I wonder: would it be possible to use the compile time reflection
> > facilities of TH to write a 'serialise' function, keeping the TH AST so
> > that it can be used at run-time?
>
> yes. but you will need to find any functions used in definition - i.e.
> it should be either fixed set of hard-encoded functions or some sort
> of dynamic binding a-la hs-plugin




More information about the Haskell-Cafe mailing list