[Haskell-cafe] Client-extensible heterogeneous types (Duck-typed
variadic functions?)
Jacek Generowicz
jacek.generowicz at cern.ch
Thu Oct 14 05:26:35 EDT 2010
On 2010 Oct 14, at 09:54, Joachim Breitner wrote:
> Hi,
>
> Am Donnerstag, den 14.10.2010, 09:34 +0200 schrieb Jacek Generowicz:
>> Another example:
>>
>> Let's say I need an Int -> String. Both
>>
>> (fnA2 :: Banana -> String) . (fnA1:: Int -> Banana)
>>
>> and
>>
>> (fnB2 :: Onion -> String) . (fnB1 :: Int -> Onion)
>>
>> will do. So please allow me to store (fnA1, fnA2) and (fnB1, fnB2) in
>> the same place. The program can tell that it can combine them with
>> (.)
>> because the type of
>>
>> let (fn1, fn2) = pair in fn2 . fn1
>>
>> is always
>>
>> Int -> String.
>
> This is possible:
>
> {-# LANGUAGE ExistentialQuantification #-}
Existential Quantification yet again!
I see that its status in Haskell Prime is "None". Anybody care to
hazard a guess as to the odds of its acceptance?
Which implementations support it today ?
> data SplitFun a b = forall x. SplitFun (a -> x, x -> b)
>
> splitFuns :: [SplitFun Int String]
> splitFuns = [SplitFun (\n -> replicate n "hi", concat)
> ,SplitFun (show, id)]
And x might be a function type (with any number of arguments), so we
get some variadicity for free! I hadn't thought of that. That's
brilliant.
> main = mapM_ putStrLn $ map (\(SplitFun (f1,f2)) -> f2 (f1 2))
> splitFuns
>
> This prints:
> *Main> main
> hihi
> 2
Brilliant. Thanks.
More information about the Haskell-Cafe
mailing list