
Folks, I'm having trouble creating a pickler for HLists and would appreciate a solution. The code for (HCons e HNil) works fine but I get an error trying to implement puHList for (HCons e l) where l is supposed to be (HCons e ...), i.e. another HList. Bar.hs:21:37: Couldn't match the rigid variable e' against PU e' `e' is bound by the instance declaration at Bar.hs:17:0 Expected type: HCons (PU e) l Inferred type: HCons e l In the first argument of puHList', namely l' In the second argument of pair', namely (puHList l)' Failed, modules loaded: none. ---- module Bar where import Data.Word import OOHaskell main = print "We are here!" class HList l => HLPU l where puHList :: HCons (PU e) l -> PU (HCons e l) instance HLPU HNil where puHList (HCons pe HNil) = wrap (\e -> HCons e HNil, \(HCons e HNil) -> e) pe instance HList l => HLPU (HCons e l) where puHList (HCons pe l) = wrap (\(a, b) -> HCons a b, \(HCons a b) -> (a, b)) (pair pe (puHList l)) newtype TourType = TourType TourType_ deriving (Show{-, Typeable-}) newtype AvgPot = AvgPot Word64 deriving (Show{-, Typeable-}) data TourType_ = TourNone | TourSingle | TourMulti | TourHeadsUpMulti deriving (Enum, Show{-, Typeable-}) --- Pickling data PU a = PU { appP :: (a, [Word8]) -> [Word8], appU :: [Word8] -> (a, [Word8]) } pickle :: PU a -> a -> [Word8] pickle p value = appP p (value, []) unpickle :: PU a -> [Word8] -> a unpickle p stream = fst (appU p stream) lift :: a -> PU a lift x = PU snd (\s -> (x, s)) sequ :: (b -> a) -> PU a -> (a -> PU b) -> PU b sequ f pa k = PU (\ (b, s) -> let a = f b pb = k a in appP pb (b, appP pa (a, s))) (\ s -> let (a, s') = appU pa s pb = k a in appU pb s') pair :: PU a -> PU b -> PU (a,b) pair pa pb = sequ fst pa (\ a -> sequ snd pb (\ b -> lift (a,b))) wrap :: (a -> b, b -> a) -> PU a -> PU b wrap (i, j) pa = sequ j pa (lift . i) Thanks, Joel -- http://wagerlabs.com/

On 10/11/05, Joel Reymont
Folks,
I'm having trouble creating a pickler for HLists and would appreciate a solution.
The code for (HCons e HNil) works fine but I get an error trying to implement puHList for (HCons e l) where l is supposed to be (HCons e ...), i.e. another HList.
Bar.hs:21:37: Couldn't match the rigid variable e' against PU e' `e' is bound by the instance declaration at Bar.hs:17:0
Expected type: HCons (PU e) l Inferred type: HCons e l In the first argument of puHList', namely l'
In the second argument of pair', namely (puHList l)'
Failed, modules loaded: none.
---- module Bar where
import Data.Word import OOHaskell
main = print "We are here!"
class HList l => HLPU l where puHList :: HCons (PU e) l -> PU (HCons e l)
instance HLPU HNil where puHList (HCons pe HNil) = wrap (\e -> HCons e HNil, \(HCons e HNil) -> e) pe
instance HList l => HLPU (HCons e l) where puHList (HCons pe l) = wrap (\(a, b) -> HCons a b, \(HCons a b) -> (a, b)) (pair pe (puHList l))
newtype TourType = TourType TourType_ deriving (Show{-, Typeable-}) newtype AvgPot = AvgPot Word64 deriving (Show{-, Typeable-})
data TourType_ = TourNone | TourSingle | TourMulti | TourHeadsUpMulti deriving (Enum, Show{-, Typeable-})
--- Pickling
data PU a = PU { appP :: (a, [Word8]) -> [Word8], appU :: [Word8] -> (a, [Word8]) }
pickle :: PU a -> a -> [Word8] pickle p value = appP p (value, [])
unpickle :: PU a -> [Word8] -> a unpickle p stream = fst (appU p stream)
lift :: a -> PU a lift x = PU snd (\s -> (x, s))
sequ :: (b -> a) -> PU a -> (a -> PU b) -> PU b sequ f pa k = PU (\ (b, s) -> let a = f b pb = k a in appP pb (b, appP pa (a, s))) (\ s -> let (a, s') = appU pa s pb = k a in appU pb s')
pair :: PU a -> PU b -> PU (a,b) pair pa pb = sequ fst pa (\ a -> sequ snd pb (\ b -> lift (a,b)))
wrap :: (a -> b, b -> a) -> PU a -> PU b wrap (i, j) pa = sequ j pa (lift . i)
Thanks, Joel
We came to this solution on IRC: {-# OPTIONS_GHC -fglasgow-exts #-} module Bar where --... class (HList l, HList p) => HLPU p l | p -> l, l -> p where puHList :: p -> PU l instance HLPU HNil HNil where puHList HNil = lift HNil instance (HList l, HLPU p l) => HLPU (HCons (PU e) p) (HCons e l) where puHList (HCons pe l) = wrap (\(a, b) -> HCons a b, \(HCons a b) -> (a, b)) (pair pe (puHList l)) --... The trick is to get the types to assert that not just the first element of the HList is a pickler/unpickler, but that the whole input HList is composed of them. - Cale

Credit goes to Cale: class (HList l, HList p) => HLPU p l | p -> l, l -> p where puHList :: p -> PU l instance HLPU HNil HNil where puHList HNil = lift HNil instance (HList l, HLPU p l) => HLPU (HCons (PU e) p) (HCons e l) where puHList (HCons pe l) = wrap (\(a, b) -> HCons a b, \(HCons a b) -> (a, b)) (pair pe (puHList l)) On Nov 10, 2005, at 2:04 PM, Joel Reymont wrote:
Folks,
I'm having trouble creating a pickler for HLists and would appreciate a solution.
The code for (HCons e HNil) works fine but I get an error trying to implement puHList for (HCons e l) where l is supposed to be (HCons e ...), i.e. another HList.
Bar.hs:21:37: Couldn't match the rigid variable e' against PU e' `e' is bound by the instance declaration at Bar.hs:17:0
Expected type: HCons (PU e) l Inferred type: HCons e l In the first argument of puHList', namely l'
In the second argument of pair', namely (puHList l)'
Failed, modules loaded: none.

This function is already in the HList library (well early versions anyway)... I dont think this is in the current distribution. Its a generic constructor wrapper. For example: hMarkAll Just hlist class HList l => HMarkAll c l m | c l -> m where hMarkAll :: (forall a . a -> c a) -> l -> m instance HMarkAll c HNil HNil where hMarkAll _ _ = HNil instance HMarkAll c l m => HMarkAll c (HCons e l) (HCons (c e) m) where hMarkAll c (HCons e l) = HCons (c e) (hMarkAll c l) Keean. Joel Reymont wrote:
Credit goes to Cale:
class (HList l, HList p) => HLPU p l | p -> l, l -> p where puHList :: p -> PU l
instance HLPU HNil HNil where puHList HNil = lift HNil
instance (HList l, HLPU p l) => HLPU (HCons (PU e) p) (HCons e l) where puHList (HCons pe l) = wrap (\(a, b) -> HCons a b, \(HCons a b) -> (a, b)) (pair pe (puHList l))
On Nov 10, 2005, at 2:04 PM, Joel Reymont wrote:
Folks,
I'm having trouble creating a pickler for HLists and would appreciate a solution.
The code for (HCons e HNil) works fine but I get an error trying to implement puHList for (HCons e l) where l is supposed to be (HCons e ...), i.e. another HList.
Bar.hs:21:37: Couldn't match the rigid variable e' against PU e' `e' is bound by the instance declaration at Bar.hs:17:0
Expected type: HCons (PU e) l Inferred type: HCons e l In the first argument of puHList', namely l'
In the second argument of pair', namely (puHList l)'
Failed, modules loaded: none.
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Keean, I sort of gave up on HList for the time being since I found easier ways to solve my problem. Mainly, I could not estimate the impact it would have on run-time performance of my code and GHC not being able to compile the code was not a good indication. Simon PJ fixed that error since. My idea was to, basically, create my own record sans labels. I wanted to specify picklers and default values for each field instead. I have over 250 records, though, and some have over 10 fields. There is a lot of sharing of fields between the records but I still think this is too much for GHC to handle. Can you venture a guess on runtime performance of such code? Thanks, Joel On Nov 22, 2005, at 4:07 PM, Keean Schupke wrote:
hMarkAll Just hlist
class HList l => HMarkAll c l m | c l -> m where hMarkAll :: (forall a . a -> c a) -> l -> m instance HMarkAll c HNil HNil where hMarkAll _ _ = HNil instance HMarkAll c l m => HMarkAll c (HCons e l) (HCons (c e) m) where hMarkAll c (HCons e l) = HCons (c e) (hMarkAll c l)

That all depends... In theory all the HList stuff happens at compile time, and what you are left with is normal function application... Of course compilers arn't that good yet, but as a reasonable idea, consider just that value level... Most of the extra work is the packing/unpacking of pairs "(,)". I have used HList for database schemas like the "Cow" example database (see attached) with no problems. The DB code includes code to generate the database from this "Schema" so is doesn't need to be entered twice, and it also typechecks the database against the schema in a one-way extensional manner on program start. The performance of the DB app is good, better than with scripting languages like perl/python, and type-safe. This code uses records made from HLists (see the paper for examples). Keean. Joel Reymont wrote:
Keean,
I sort of gave up on HList for the time being since I found easier ways to solve my problem.
Mainly, I could not estimate the impact it would have on run-time performance of my code and GHC not being able to compile the code was not a good indication. Simon PJ fixed that error since.
My idea was to, basically, create my own record sans labels. I wanted to specify picklers and default values for each field instead. I have over 250 records, though, and some have over 10 fields. There is a lot of sharing of fields between the records but I still think this is too much for GHC to handle.
Can you venture a guess on runtime performance of such code?
Thanks, Joel
On Nov 22, 2005, at 4:07 PM, Keean Schupke wrote:
hMarkAll Just hlist
class HList l => HMarkAll c l m | c l -> m where hMarkAll :: (forall a . a -> c a) -> l -> m instance HMarkAll c HNil HNil where hMarkAll _ _ = HNil instance HMarkAll c l m => HMarkAll c (HCons e l) (HCons (c e) m) where hMarkAll c (HCons e l) = HCons (c e) (hMarkAll c l)
participants (3)
-
Cale Gibbard
-
Joel Reymont
-
Keean Schupke