overloading functions

Hi, 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)) when i use it on : f `cms` ("." ::String) `cms` s it works but not on this: f `cms` "." `cms` s "." is too ambigious to compile: *Main> :load UpdateSidonie [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted ) UpdateSidonie.hs:373:43: error: • Ambiguous type variable ‘a0’ arising from a use of ‘cms’ prevents the constraint ‘(ConcatenateMaybeString a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance ConcatenateMaybeString (Maybe String) -- Defined at UpdateSidonie.hs:169:11 instance ConcatenateMaybeString String -- Defined at UpdateSidonie.hs:177:11 • In the first argument of ‘cms’, namely ‘f `cms` "."’ In the expression: f `cms` "." `cms` s In the expression: let f = fmap head resBDwords s = fmap (head . tail) resBDwords mp = Just "." :: Maybe String .... in f `cms` "." `cms` s | 373 | in f `cms` "." `cms` s) :: Maybe String | ^^^^^^^^^^^ UpdateSidonie.hs:373:51: error: • Ambiguous type variable ‘a0’ arising from the literal ‘"."’ prevents the constraint ‘(Data.String.IsString a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance Data.String.IsString Query -- Defined in ‘Database.MySQL.Simple.Types’ instance Data.String.IsString Tx.Text -- Defined in ‘Data.Text’ instance (a ~ Char) => Data.String.IsString [a] -- Defined in ‘Data.String’ ...plus six instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the second argument of ‘cms’, namely ‘"."’ In the first argument of ‘cms’, namely ‘f `cms` "."’ In the expression: f `cms` "." `cms` s | 373 | in f `cms` "." `cms` s) :: Maybe String | ^^^ Failed, no modules loaded. Prelude> any idea? Damien

On Thu, 10 Jan 2019 at 19:34, Damien Mattei
Hi,
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))
when i use it on : f `cms` ("." ::String) `cms` s it works
but not on this: f `cms` "." `cms` s
"." is too ambigious to compile:
*Main> :load UpdateSidonie [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted )
UpdateSidonie.hs:373:43: error: • Ambiguous type variable ‘a0’ arising from a use of ‘cms’ prevents the constraint ‘(ConcatenateMaybeString a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance ConcatenateMaybeString (Maybe String) -- Defined at UpdateSidonie.hs:169:11 instance ConcatenateMaybeString String -- Defined at UpdateSidonie.hs:177:11 • In the first argument of ‘cms’, namely ‘f `cms` "."’ In the expression: f `cms` "." `cms` s In the expression: let f = fmap head resBDwords s = fmap (head . tail) resBDwords mp = Just "." :: Maybe String .... in f `cms` "." `cms` s | 373 | in f `cms` "." `cms` s) :: Maybe String | ^^^^^^^^^^^
UpdateSidonie.hs:373:51: error: • Ambiguous type variable ‘a0’ arising from the literal ‘"."’ prevents the constraint ‘(Data.String.IsString a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance Data.String.IsString Query -- Defined in ‘Database.MySQL.Simple.Types’ instance Data.String.IsString Tx.Text -- Defined in ‘Data.Text’ instance (a ~ Char) => Data.String.IsString [a] -- Defined in ‘Data.String’ ...plus six instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the second argument of ‘cms’, namely ‘"."’ In the first argument of ‘cms’, namely ‘f `cms` "."’ In the expression: f `cms` "." `cms` s | 373 | in f `cms` "." `cms` s) :: Maybe String | ^^^ Failed, no modules loaded. Prelude>
any idea?
Do you have the OverloadedStrings or OverloadedLists LANGUAGE pragmas enabled?
Damien
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

yes for use with the DB (Database.MySQL.Simple.QueryResults) it is necessary. It should be confusing about String for the compiler... Le 10/01/2019 13:00, Ivan Lazar Miljenovic a écrit :
On Thu, 10 Jan 2019 at 19:34, Damien Mattei
mailto:mattei@oca.eu> wrote: Hi,
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))
when i use it on : f `cms` ("." ::String) `cms` s it works
but not on this: f `cms` "." `cms` s
"." is too ambigious to compile:
*Main> :load UpdateSidonie [1 of 1] Compiling Main ( UpdateSidonie.hs, interpreted )
UpdateSidonie.hs:373:43: error: • Ambiguous type variable ‘a0’ arising from a use of ‘cms’ prevents the constraint ‘(ConcatenateMaybeString a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance ConcatenateMaybeString (Maybe String) -- Defined at UpdateSidonie.hs:169:11 instance ConcatenateMaybeString String -- Defined at UpdateSidonie.hs:177:11 • In the first argument of ‘cms’, namely ‘f `cms` "."’ In the expression: f `cms` "." `cms` s In the expression: let f = fmap head resBDwords s = fmap (head . tail) resBDwords mp = Just "." :: Maybe String .... in f `cms` "." `cms` s | 373 | in f `cms` "." `cms` s) :: Maybe String | ^^^^^^^^^^^
UpdateSidonie.hs:373:51: error: • Ambiguous type variable ‘a0’ arising from the literal ‘"."’ prevents the constraint ‘(Data.String.IsString a0)’ from being solved. Probable fix: use a type annotation to specify what ‘a0’ should be. These potential instances exist: instance Data.String.IsString Query -- Defined in ‘Database.MySQL.Simple.Types’ instance Data.String.IsString Tx.Text -- Defined in ‘Data.Text’ instance (a ~ Char) => Data.String.IsString [a] -- Defined in ‘Data.String’ ...plus six instances involving out-of-scope types (use -fprint-potential-instances to see them all) • In the second argument of ‘cms’, namely ‘"."’ In the first argument of ‘cms’, namely ‘f `cms` "."’ In the expression: f `cms` "." `cms` s | 373 | in f `cms` "." `cms` s) :: Maybe String | ^^^ Failed, no modules loaded. Prelude>
any idea?
Do you have the OverloadedStrings or OverloadedLists LANGUAGE pragmas enabled?
Damien
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- Ivan Lazar Miljenovic Ivan.Miljenovic@gmail.com mailto:Ivan.Miljenovic@gmail.com http://IvanMiljenovic.wordpress.com

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.

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

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!

i'm not so pessimist,i'm beginning to have fun with haskell...really! about teaching ressource i will be happy to know where i can find them... i only post in haskell cafe when i have not find the answer online (tutorials,stackoverflow,real haskell book http://book.realworldhaskell.org/etc,etc... in the hunded pages i search i even get a look at Categories for the working Mathematician https://books.google.fr/books?id=6KPSBwAAQBAJ&printsec=frontcover&source=gbs_ge_summary_r&cad=0#v=onepage&q&f=false) it is only when i have exhausted all the online ressource that i post to the cafe... On Thu, Jan 10, 2019 at 6:52 PM Tom Ellis < tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:
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! _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.

Category theory books are almost certainly not what you want to be looking
at. Yes, some things in Haskell are inspired by it; but they're entirely
usable wthout, and they're all rather simplified compared to the theory.
Typeclasses, you might want to start with the Typeclassopedia
https://wiki.haskell.org/Typeclassopedia. And understand that it is not
general function overloading, and you can get yourself into trouble by
trying to treat them as such: types flow "backwards" in Haskell, compared
to languages where overloading is common. If all you know about a type is
its name, you can't do anything with it. In most OO languages with
overloading, you can do anything you want with it and it'll throw an
exception if it doesn't support it; in Haskell, the compiler won't let you
get away with it at all, it never reaches the point of a runtime exception.
Similarly, if you know (Num a), this doesn't mean you can use division; you
need to also know (Integral a) to get div, or (Fractional a) to get (/).
One thing that follows from how this interacts with typeclasses is return
type polymorphism. Consider that maxBound takes no parameters, and decides
what to do based on the type it's used at.
On Thu, Jan 10, 2019 at 2:38 PM Damien Mattei
i'm not so pessimist,i'm beginning to have fun with haskell...really! about teaching ressource i will be happy to know where i can find them... i only post in haskell cafe when i have not find the answer online (tutorials,stackoverflow,real haskell book http://book.realworldhaskell.org/etc,etc... in the hunded pages i search i even get a look at Categories for the working Mathematician https://books.google.fr/books?id=6KPSBwAAQBAJ&printsec=frontcover&source=gbs_ge_summary_r&cad=0#v=onepage&q&f=false) it is only when i have exhausted all the online ressource that i post to the cafe...
On Thu, Jan 10, 2019 at 6:52 PM Tom Ellis < tom-lists-haskell-cafe-2017@jaguarpaw.co.uk> wrote:
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! _______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
_______________________________________________ Haskell-Cafe mailing list To (un)subscribe, modify options or view archives go to: http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe Only members subscribed via the mailman list are allowed to post.
-- brandon s allbery kf8nh allbery.b@gmail.com
participants (5)
-
Brandon Allbery
-
Damien Mattei
-
Damien Mattei
-
Ivan Lazar Miljenovic
-
Tom Ellis