[Haskell-cafe] Re: Pickling HList
Keean Schupke
k.schupke at imperial.ac.uk
Tue Nov 22 11:07:56 EST 2005
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.
>>
>
> --
> http://wagerlabs.com/
>
>
>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
More information about the Haskell-Cafe
mailing list