[Haskell-cafe] Functions with generic return types

Luke Palmer lrpalmer at gmail.com
Mon Jan 12 21:48:05 EST 2009


On Mon, Jan 12, 2009 at 5:56 PM, Stephen Hicks <sdh33 at cornell.edu> wrote:

> -- This instance definition is broken...
> instance (Monad m,Pick (a,b) c) => Pick (m a,m b) (m c) where
>    pick (ma,mb) = do { a <- ma; b <- mb; return $ pick (a,b) }


First, and I know these types of comments are generally unwanted, but I
recommend you *not do this*.  You are only making pain for yourself later.
Haskell is not good at this type of ad-hoc polymorphism (partially because
it does not play well with inference).  I.e. whyever you think you need this
machinery, I suggest you spend some time rethinking why this is really
necessary.

Okay, now to explain this instance.

An instance Pick (a,b) c is just a function (a,b) -> c.  So this instance
reduces to the possibility of writing a function:

monadify :: ((a,b) -> c) -> ((m a, m b) -> m c)

Which is only implementable by executing both actions m a and m b (because
you need both an a and a b to pass to c).  Consider what would happen if a
pick function looked at the contents of its argument?  e.g. maybe someone
writes:

instance Pick (Int,Int) Int where
    pick (x,y) = min x y

Then you would have to know the actual values to decide what to return, thus
both actions must be executed.

One thing I always like to do when I'm writing typeclasses is write the
proof term library first (i.e. explicit dictionary passing) and then start
turning those into typeclasses.  This practice helps to weed out impossible
ideas (eg. if you can't do what you want by explicitly passing dictionaries,
how is the compiler going to infer the dictionaries for you?), and also to
make more transparent what terms are being constructed.

As an example, you might start:

type PickD a b = a -> b

leftTuple :: PickD (a,b) a
leftTuple = fst
rightTuple :: PickD (a,b) b
rightTuple = snd
func :: PickD (a,b) c -> PickD (d -> a, d -> b) (d -> c)
func p (f,g) x = p (f x, g x)

...

And do this for each of your proposed instances.  Then do an example use
case, using these functions explicitly, and try to envisage an algorithm
which might pick the functions for you.  Then it will be much more obvious
if it is possible to typeclassify these, and if so, how.

Luke


>
> foo :: Pick (String,Int) t => String -> t
> foo = pick (id :: String -> String, length :: String -> Int)
>
> toStr :: String -> IO String
> toStr s = putStrLn "str" >> return s
> toInt :: String -> IO Int
> toInt s = putStrLn "int" >> return (length s)
>
> bar :: Pick (String,Int) t => String -> IO t
> bar = pick (toStr,toInt)
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090112/3872bd40/attachment.htm


More information about the Haskell-Cafe mailing list