[Haskell-cafe] retrieving arguments for functions from a
heterogenous list (HList)
Andrew U. Frank
frank at geoinfo.tuwien.ac.at
Thu Sep 10 13:01:29 EDT 2009
I have a number of functions which have some arguments and produce a single
result. all the arguments are in a heterogenous list and the results should
update the list. this appears somewhat similar to the keyword-argument
solution for functions proposed by oleg kiselyov in 2004.
i would like to have a method to convert the functions
f :: A -> B -> C
g:: A -> D -> C -> B (for example)
to
f' :: argTypes -> H -> H
g' :: argTypes -> H -> H
where H is a heterogenous list containing A, B, C, D (and others) and
argTypes is another heterogenous list containing the types of the arguments,
which are used to retrieve the data from the list (with .!!.) - the result has
the correct type and is updated in the list with .@@. .
naively this could be done by some functins fx (recursing over the list of
arguments) storing the last argument in the HList:
fx :: (HList l) => op -> HCons e l -> H -> H
fx op HNil uod = uod .@@. op
fx op (HCons a as) uod = fx (op arg) as uod
where arg = uod .!!. a
this code does not compile, because HNil and HCons do not match (they are
different data types, not a union type).
code that compiles looks like
class (HList l, HList k
, HUpdateAtHNat n e k k, HType2HNat e k n
, HLookupByHNat n k e
) => HCall e n f l k | l k -> n where
hcall :: f -> l -> k -> k -- not general
instance ( HNat n
, HUpdateAtHNat n e UoD UoD, HType2HNat e UoD n
, HLookupByHNat n UoD e
) => HCall e n e HNil UoD where
hcall opv HNil k = hcall0 opv k
instance (HCall e n f l UoD
, HLookupByHNat n UoD e, HType2HNat e n UoD
) => HCall e n (e -> f) (HCons a l) UoD where
hcall op (HCons a l) k = hcall (op arg) l k
where arg = hLookupByHNat n k
n = hType2HNat (toProxy arg) k :: n
hcall0 :: ( HUpdateAtHNat n f UoD UoD, HType2HNat f H n,
HCall e n f HNil UoD) => f -> H -> H
hcall0 op k = hUpdateAtHNat n (const op undefined) k `asTypeOf` k
where n = hType2HNat (toProxy op) k
where i factored out the terminating call, which is probably wrong.
i would like to use it as:
showPop4 :: (HList hNil,
HCall Population n (District -> Population) (hConst District hNil) UoD)
=> (hCons District hNil) -> UoD -> UoD
showPop4 arg uod = hcall showPop2 arg uod
unfortunately, calls to this function result in 'cannot deduce' compilation
error; it seems that some of the intermediate types are not known.
i appreciate any help!
andrew
More information about the Haskell-Cafe
mailing list