
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.
Hello Tom, 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 :-) it's not 2 function but more that are necessary because arguments and their corresponding types could be in any order, if i define different functions i will have 3 functions with different names: cms1::String -> Maybe String -> Maybe String cms2::Maybe String -> String -> Maybe String cms3::Maybe String -> Maybe String -> Maybe String i prefer to have a single overloaded operator like this : class ConcatenateMaybeString a b where (+%+) :: a -> b -> Maybe String instance ConcatenateMaybeString (Maybe String) (Maybe String) where (+%+) mf ms = mf >>= (\f -> ms >>= (\s -> return (f ++ s))) instance ConcatenateMaybeString (Maybe String) String where (+%+) mf s = mf >>= (\f -> return (f ++ s)) instance ConcatenateMaybeString String (Maybe String) where (+%+) f ms = ms >>= (\s -> return (f ++ s)) usable like this: f +%+ ("." :: String) +%+ s if i did not need OverloadedStrings i could even simply wrote: f +%+ "." +%+ s