[Haskell-cafe] overloading functions

Tom Ellis tom-lists-haskell-cafe-2017 at jaguarpaw.co.uk
Thu Jan 10 17:51:51 UTC 2019


On Thu, Jan 10, 2019 at 04:23:49PM +0100, Damien Mattei wrote:
> Le 10/01/2019 15:27, Tom Ellis a écrit :
> > On Thu, Jan 10, 2019 at 12:34:04PM +0100, Damien Mattei wrote:
> >> i have this definition:
> >>
> >> {-# LANGUAGE FlexibleInstances #-}
> >>
> >> class ConcatenateMaybeString a where
> >>   cms :: Maybe String -> a -> Maybe String
> >>
> >>
> >> instance  ConcatenateMaybeString (Maybe String) where
> >>      cms mf ms =
> >>        mf >>= (\f ->
> >>             ms >>= (\s ->
> >>                       return (f ++ s)))
> >>
> >>
> >>
> >> instance  ConcatenateMaybeString String where
> >>      cms mf s =
> >>        mf >>= (\f -> return (f ++ s))
> > 
> > Trying to simulate overloading like this is ultimately going to lead to more
> > frustration than benefit.  I strongly suggest you just define two different
> > functions.
> 
> those functions could be seen as a "style exercise" , for me,coming from
> untyped languages such as Scheme or LisP it's Haskell which is a
> frustration :-)

I think you're going to get significantly more frustrated with Haskell if
you try to learn it like this by yourself rather than by working through
some widely approved teaching resource.  Of course, how you spend your time
is up to you, but if you're frustrated with Haskell then trying to make it
up as you go along is only going to worsen the feeling!


More information about the Haskell-Cafe mailing list