... and here is the code I am giving up on for today: Serialization of HLists. Questions below.
{-# OPTIONS -fglasgow-exts #-} {-# OPTIONS -fallow-undecidable-instances #-} {-# OPTIONS -fallow-overlapping-instances #-} module Foo where import Char import List import Monad import Permutation import HListPrelude -- [1] http://web.engr.oregonstate.edu/~erwig/pfp/ -- Serializable is like Show, but -- (a) it carries explicit type information, and -- (b) it allows for serializing IORefs etc. class Serializable s where serialize :: s -> IO String deSerialize :: String -> IO s instance Serializable Int where serialize = return . ("Int::" ++) . show deSerialize s | isPrefixOf "Int::" s = return . (read :: String -> Int) . drop 5 $ s instance Serializable Char where serialize = return . ("Char::" ++) . show deSerialize s | isPrefixOf "Char::" s = return . (read :: String -> Char) . drop 6 $ s -- SList is a list of heterogenous serializable elements... class HList l => SList l instance SList HNil instance (Serializable s, SList ss) => SList (HCons s ss) -- ... so it should be possible to write instantiate Serializable, right?: instance (SList s, HMapOut Serialize s (IO String)) => Serializable s where serialize = liftM show . (sequence :: [IO String] -> IO [String]) . hMapOut Serialize deSerialize = error "Not yet. (I am not even done with serialize yet.)" -- Seems we need the trick from the paper that oleg pointed out to me earlier in this thread: data Serialize = Serialize instance (Serializable s) => Apply Serialize s (IO String) where apply _ = serialize -- Example: slist = HCons (1 :: Int) (HCons ('c' :: Char) HNil) test1 = serialize slist -- (This is where -fallow-overlapping-instances helps. There is a -- section in [1] on how to get rid of it, which I haven't read yet.) test2 :: IO (HCons Int (HCons Char HNil)) test2 = test1 >>= deSerialize Two questions: (1) Do you see any reasons why it should be impossible in principle to write deSerialize for the SList instance of Serializable? (I think the answer is "it's possible to write it, but you need to add quite some type information by hand".) (2) The problem with test2 is that I need to know its precise object-level type, ie which types occur at which positions in the SList. I am pretty sure this is a restriction I have to live with. Please tell me I am wrong. (-: (I think my application will make it possible for ghc to infer the type, which is fixed at compile time anyways, so it's not a severe restriction.) (3) (bonus question :) Who wants to write deSerialize for SLists for me? And another one: Why do I need to list the HMapOut instance in the context of the instance declaration of Serializable for SLists? (It's not a big deal, but I can't see why it can't be inferred automatically from the rest of the code.) Possibly back with another issue of my HList diary tomorrow. (Please tell me if you find this interesting or if you would like me to stop being so verbose.) cheers, Matthias
signature.asc
Description: Digital signature
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe