[Haskell-cafe] Clean Dynamics and serializing code to disk

gwern0 at gmail.com gwern0 at gmail.com
Tue Dec 4 18:02:38 EST 2007


Hey everyone; recently I've been toying around with various methods of writing a shell and reading the academic literature on such things. The best prior art on the subject seems to be the ESTHER shell (see <http://citeseer.ist.psu.edu/689593.html>, <http://citeseer.ist.psu.edu/744494.html>, <ftp://ftp.cs.kun.nl/pub/Clean/papers/2003/vWeA2003-Esther.pdf>).

Now, ESTHER is a really cool looking shell, but it has two main problems for me:
1) Source doesn't seem to be available anywhere online
2) It's written in Clean and not Haskell

No problem. All the hard stuff is done, and there's like a good 50 pages of documentation, so how hard could it be? Clean is practically Haskell anyway.

But immediately I ran into a road-block:

 "The shell is built on top of Clean's hybrid static/dynamic type system and its dynamic I/O run-time support. It allows programmers to save any Clean expression, i.e a graph that can contain data, references to functions, and closures to disk. Clean expressions can be written to disk as a _dynamic_, which contains a representation of their (polymorphic) static type, while preserving sharing. Clean programs can load dynamics from disk and use run-time type pattern matching to reintegrate it into the statically-typed program."

The Data.Dynamic library seems to do everything as far as dynamic types and run-time pattern matching goes, but I haven't figured out how one could write Haskell expressions to disk, like Clean's system <http://www.st.cs.ru.nl/papers/2002/verm2002-LazyDynamicIO.ps.gz> apparently allows.

Does anyone know if there are any neat or tricky ways this could be done? Projects, extensions, whatever?

On #haskell, quicksilver did tell me of one neat way to serialize various stuff through Data.Binary by using ADTs along the lines of the following simple example:

--

module Main (main)
    where
import Data.Binary
data Math = Add | Subtract | Multiply
    deriving Show

eval :: (Num a) => Math -> a -> a -> a
eval f = case f of
           Add -> (+)
           Subtract -> (-)
           Multiply -> (*)

instance Binary Math where
      put Add = putWord8 0
      put Subtract = putWord8 1
      put Multiply = putWord8 2
      get = do tag_ <- getWord8
               case tag_ of
                 0 -> return Add
                 1 -> return Subtract
                 2 -> return Multiply


main = do encodeFile "tmp.s" [Add, Subtract, Multiply]
          a <- decodeFile "tmp.s"
          putStr $ show (a :: [Math])

--

Since from my Lisp days I know that code is data, it strikes me that one could probably somehow smuggle Haskell expressions via this route although I am not sure this is a good way to go or even how one would do it (to turn, say, a list of the chosen ADT back into real functions, you need the 'eval' function, but apparently eval can only produce functions of the same type - so you'd need to either create as many adts and instances as there are varieties of type signatures in Haskell '98 and the libraries, I guess, or somehow encode in a lambda calculus). Is that a route worth pursuing?

--
gwern
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 189 bytes
Desc: not available
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20071204/1d8dcb1b/attachment.bin


More information about the Haskell-Cafe mailing list