[Haskell-beginners] Polymorphism question from an OO-speaking
newbie
Jan Jakubuv
jakubuv at gmail.com
Mon May 4 12:23:59 EDT 2009
On Mon, May 04, 2009 at 10:34:09AM -0500, Joel Neely wrote:
> Short version: Is it possible/reasonable to define a single function
> that accepts a single string or a list of strings (in which case it
> maps the single-string "flavor" over the list)?
>
Hi Joel,
you are looking for type classes (http://haskell.org/tutorial/classes.html).
They allow you to use the same function name for different types. This is
called ``ad-hoc'' polymorphism and you can define different implementation
of the overloaded function for different types (which is your case). Haskell
also support ``parametric'' polymorphism which can be used when you have the
same implementation for different types (like the function `head` which
returns the first member of a list independently on the type of elements).
Try the following:
{-# OPTIONS -fglasgow-exts #-}
quoteS s = "\"" ++ s ++ "\""
quoteL l = map quoteS l
class Quatable q where
quote :: q -> q
instance Quatable String where
quote s = "\"" ++ s ++ "\""
instance Quatable [String] where
quote = map quote
Then you can use it as follows:
*Main> "Quux said " ++ quote "foo" ++ " loudly"
"Quux said \"foo\" loudly"
*Main> quote ["foo", "baz", "bletch"]
["\"foo\"","\"baz\"","\"bletch\""]
Don't forget the line `{-# OPTIONS -fglasgow-exts #-}` which enables some
features of GHC you need for this example (but not necessarily for all
examples using type classes). Alternatively you can use the line
{-# LANGUAGE TypeSynonymInstances,FlexibleInstances #-}
which lists necessary extensions explicitly.
Sincerely,
Jan.
--
Heriot-Watt University is a Scottish charity
registered under charity number SC000278.
More information about the Beginners
mailing list