[Haskell-cafe] Client-extensible heterogeneous types
(Duck-typed variadic functions?)
Joachim Breitner
mail at joachim-breitner.de
Thu Oct 14 03:54:50 EDT 2010
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 #-}
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)]
main = mapM_ putStrLn $ map (\(SplitFun (f1,f2)) -> f2 (f1 2)) splitFuns
This prints:
*Main> main
hihi
2
Greetings,
Joachim
--
Joachim "nomeata" Breitner
mail: mail at joachim-breitner.de | ICQ# 74513189 | GPG-Key: 4743206C
JID: nomeata at joachim-breitner.de | http://www.joachim-breitner.de/
Debian Developer: nomeata at debian.org
-------------- next part --------------
A non-text attachment was scrubbed...
Name: not available
Type: application/pgp-signature
Size: 198 bytes
Desc: This is a digitally signed message part
Url : http://www.haskell.org/pipermail/haskell-cafe/attachments/20101014/5cfcf126/attachment.bin
More information about the Haskell-Cafe
mailing list