Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  mempty and "No instance for (Monoid Int)" (David McBride)
   2. Re:  mempty and "No instance for (Monoid Int)" (aquagnu)
   3. Re:  mempty and "No instance for (Monoid Int)" (David McBride)
   4. Re:  Alternative instance w/ additional restriction (aquagnu)


----------------------------------------------------------------------

Message: 1
Date: Wed, 7 Jun 2017 12:53:19 -0400
From: David McBride <toa...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] mempty and "No instance for (Monoid
        Int)"
Message-ID:
        <can+tr41qluzu3hjx-os1ybth-6uhpf2datn0idr_gxkjpsa...@mail.gmail.com>
Content-Type: text/plain; charset="UTF-8"

In ghci there are type defaulting rules.  When you go mempty ==
Nothing, it type defaults it to "Maybe ()".  But when you type Just 4,
4 is definitely not (), and so it looks at the Monoid instance for the
a default type to use in cases of numeric literals, the first of which
is Int.

Which brings you to the next problem.  Maybe Int is only a Monoid if
Int is an instance of Monoid, and Int is definitely not.

That's because is 3 `mappend` 3 == 6 via addition?  Or should it be 9
via multiplication?  Or something else?  What should mempty be, 0?  Or
maybe 1?  Who is to decide what the only way of combining Ints
together is.

It turns out there are instances for both of those cases, but you have
to wrap the int into a type so that it knows which way you want it to
be interpreted.

import Data.Monoid
mempty == Just (Product 1)
> false
mempty == Just (Sum 1)
> false

There are similar monoidal instances for Bool, such as Any and All.

On Wed, Jun 7, 2017 at 12:33 PM, Baa <aqua...@gmail.com> wrote:
> Maybe a is the Monoid:
>
>   instance Monoid a => Monoid (Maybe a) -- Defined in ‘GHC.Base’
>
> so I can compare its values with empty value:
>
>   mempty == Nothing
>   => True
>
> But if I try:
>
>   mempty == Just 4
>
> I get:
>
>   <interactive>:1:1: error:
>       • Ambiguous type variable ‘a0’ arising from a use of ‘mempty’
>         prevents the constraint ‘(Monoid a0)’ from being solved.
>         Probable fix: use a type annotation to specify what ‘a0’ should
>          be. These potential instances exist:
>           instance Monoid a => Monoid (IO a) -- Defined in ‘GHC.Base’
>           instance Monoid Ordering -- Defined in ‘GHC.Base’
>           instance Monoid a => Monoid (Maybe a) -- Defined in ‘GHC.Base’
>           ...plus 7 others
>           (use -fprint-potential-instances to see them all)
>       • In the first argument of ‘(==)’, namely ‘mempty’
>         In the expression: mempty == Just 4
>         In an equation for ‘it’: it = mempty == Just 4
>
> OK, I try:
>
>   mempty::Maybe Int
>
> and get:
>
>   <interactive>:1:1: error:
>       • No instance for (Monoid Int) arising from a use of ‘mempty’
>       • In the expression: mempty :: Maybe Int
>         In an equation for ‘it’: it = mempty :: Maybe Int
>
> so, how is related Int to Monoid, why does ghc expect from mempty::Maybe
> Int, Int to be Monoid?! As I understand, this means only that I
> mean "mempty" from (Maybe Int) type, which is Monoid and exists sure.
>
> Interesting is, that:
>
>   mempty::Maybe [Int]
>   => Nothing
>
> but how is related "monoidality" of "Maybe a" with "monoidality of
> "a" ???
>
> Initial idea was to make comparison:
>
>   mempty :: Maybe Int == Just 4
>   => False
>
>
> /Best regards,
>   Paul
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

Message: 2
Date: Wed, 7 Jun 2017 21:53:36 +0300
From: aquagnu <aqua...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] mempty and "No instance for (Monoid
        Int)"
Message-ID: <20170607215336.28871...@gmail.com>
Content-Type: text/plain; charset=UTF-8

> In ghci there are type defaulting rules.  When you go mempty ==
> Nothing, it type defaults it to "Maybe ()". 

Aha, OK. These defaults are preset also in non-interactive: I tried the
same and get the same result.

> But when you type Just 4,
> 4 is definitely not (), and so it looks at the Monoid instance for the
> a default type to use in cases of numeric literals, the first of which
> is Int.

This I can not understand. Literal "4" is under "Just", so why are we
talking about "Int" as Monoid but not about "Maybe Int" as Monoid? And
"Maybe Int" as Monoid does not depend on Int and is the same for "Maybe
Int", "Maybe Bool", "Maybe String"... When I added type annotation, like
"::Maybe Int", I suppose, usual "Maybe a"'s implementations of
"mempty", "mappend" will be used, - no more defaults. Seems it is not
true, but why?


> 
> Which brings you to the next problem.  Maybe Int is only a Monoid if
> Int is an instance of Monoid, and Int is definitely not.
> 

I don't understand it. Monoid is "Maybe a" for any "a". And I can
understand your point if we are talking only for interactive GHCI and
its defaults, but when I tried in source code to write:

  m :: Maybe Int
  m = mempty
  ...
  ... print $ Nothing == m

i get the same, about no instance for (Monoid Int). But Maybe's "mempty"
is "Nothing", nothing else. And its "mappend" processes any (Just _) and
Nothing's, right? May be all magic is from defaults?


> That's because is 3 `mappend` 3 == 6 via addition?  Or should it be 9
> via multiplication?  Or something else?  What should mempty be, 0?  Or
> maybe 1?  Who is to decide what the only way of combining Ints
> together is.
> 
> It turns out there are instances for both of those cases, but you have
> to wrap the int into a type so that it knows which way you want it to
> be interpreted.
> 
> import Data.Monoid
> mempty == Just (Product 1)
> > false  
> mempty == Just (Sum 1)
> > false  

Yes, this is absolutely understandable. Except one detail:

  Prelude Data.Monoid Data.Maybe> mempty == Product 1
  True
  Prelude Data.Monoid Data.Maybe> mempty == Just (Product 1)
  False

so, "Product Int" as Monoid and "Maybe (Product Int)" as Monoid are totally
different, - I understand what is Abel's groups on + and *, but I don't
understand why GHC looks for Monoid instance for Int while Int is under
Maybe... It will be right if:

  instance (Monoid a) => Monoid (Maybe a) where
    ...

but is it true?! I suppose no such constraint on "a". Is it all due to
defaults? Or I lost my brain at this night :)


/Best regards, Paul


> 
> There are similar monoidal instances for Bool, such as Any and All.
> 
> On Wed, Jun 7, 2017 at 12:33 PM, Baa <aqua...@gmail.com> wrote:
> > Maybe a is the Monoid:
> >
> >   instance Monoid a => Monoid (Maybe a) -- Defined in ‘GHC.Base’
> >
> > so I can compare its values with empty value:
> >
> >   mempty == Nothing  
> >   => True  
> >
> > But if I try:
> >
> >   mempty == Just 4
> >
> > I get:
> >
> >   <interactive>:1:1: error:
> >       • Ambiguous type variable ‘a0’ arising from a use of ‘mempty’
> >         prevents the constraint ‘(Monoid a0)’ from being solved.
> >         Probable fix: use a type annotation to specify what ‘a0’
> > should be. These potential instances exist:
> >           instance Monoid a => Monoid (IO a) -- Defined in
> > ‘GHC.Base’ instance Monoid Ordering -- Defined in ‘GHC.Base’
> >           instance Monoid a => Monoid (Maybe a) -- Defined in
> > ‘GHC.Base’ ...plus 7 others
> >           (use -fprint-potential-instances to see them all)
> >       • In the first argument of ‘(==)’, namely ‘mempty’
> >         In the expression: mempty == Just 4
> >         In an equation for ‘it’: it = mempty == Just 4
> >
> > OK, I try:
> >
> >   mempty::Maybe Int
> >
> > and get:
> >
> >   <interactive>:1:1: error:
> >       • No instance for (Monoid Int) arising from a use of ‘mempty’
> >       • In the expression: mempty :: Maybe Int
> >         In an equation for ‘it’: it = mempty :: Maybe Int
> >
> > so, how is related Int to Monoid, why does ghc expect from
> > mempty::Maybe Int, Int to be Monoid?! As I understand, this means
> > only that I mean "mempty" from (Maybe Int) type, which is Monoid
> > and exists sure.
> >
> > Interesting is, that:
> >
> >   mempty::Maybe [Int]  
> >   => Nothing  
> >
> > but how is related "monoidality" of "Maybe a" with "monoidality of
> > "a" ???
> >
> > Initial idea was to make comparison:
> >
> >   mempty :: Maybe Int == Just 4  
> >   => False  
> >
> >
> > /Best regards,
> >   Paul
> > _______________________________________________
> > Beginners mailing list
> > Beginners@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners  
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners



-- 
Best regards,
  Paul a.k.a. 6apcyk


------------------------------

Message: 3
Date: Wed, 7 Jun 2017 15:00:55 -0400
From: David McBride <toa...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] mempty and "No instance for (Monoid
        Int)"
Message-ID:
        <can+tr41qc2nxfthputxces3tkxkv69tsgyxejs2j2buujo0...@mail.gmail.com>
Content-Type: text/plain; charset="UTF-8"

I glossed over the key fact

> Maybe Int is only a Monoid if Int is an instance of Monoid

This is derived from the Monoid instance of Maybe.

instance Monoid a => Monoid (Maybe a) -- Defined in ‘GHC.Base’

Maybe is only an instance if a is an instance.  If a isn't then Maybe
isn't either, and it will be rejected.  That is why Maybe Int is not a
Monoid, but Maybe (Product Int) and Maybe () are.


On Wed, Jun 7, 2017 at 2:53 PM, aquagnu <aqua...@gmail.com> wrote:
>> In ghci there are type defaulting rules.  When you go mempty ==
>> Nothing, it type defaults it to "Maybe ()".
>
> Aha, OK. These defaults are preset also in non-interactive: I tried the
> same and get the same result.
>
>> But when you type Just 4,
>> 4 is definitely not (), and so it looks at the Monoid instance for the
>> a default type to use in cases of numeric literals, the first of which
>> is Int.
>
> This I can not understand. Literal "4" is under "Just", so why are we
> talking about "Int" as Monoid but not about "Maybe Int" as Monoid? And
> "Maybe Int" as Monoid does not depend on Int and is the same for "Maybe
> Int", "Maybe Bool", "Maybe String"... When I added type annotation, like
> "::Maybe Int", I suppose, usual "Maybe a"'s implementations of
> "mempty", "mappend" will be used, - no more defaults. Seems it is not
> true, but why?
>
>
>>
>> Which brings you to the next problem.  Maybe Int is only a Monoid if
>> Int is an instance of Monoid, and Int is definitely not.
>>
>
> I don't understand it. Monoid is "Maybe a" for any "a". And I can
> understand your point if we are talking only for interactive GHCI and
> its defaults, but when I tried in source code to write:
>
>   m :: Maybe Int
>   m = mempty
>   ...
>   ... print $ Nothing == m
>
> i get the same, about no instance for (Monoid Int). But Maybe's "mempty"
> is "Nothing", nothing else. And its "mappend" processes any (Just _) and
> Nothing's, right? May be all magic is from defaults?
>
>
>> That's because is 3 `mappend` 3 == 6 via addition?  Or should it be 9
>> via multiplication?  Or something else?  What should mempty be, 0?  Or
>> maybe 1?  Who is to decide what the only way of combining Ints
>> together is.
>>
>> It turns out there are instances for both of those cases, but you have
>> to wrap the int into a type so that it knows which way you want it to
>> be interpreted.
>>
>> import Data.Monoid
>> mempty == Just (Product 1)
>> > false
>> mempty == Just (Sum 1)
>> > false
>
> Yes, this is absolutely understandable. Except one detail:
>
>   Prelude Data.Monoid Data.Maybe> mempty == Product 1
>   True
>   Prelude Data.Monoid Data.Maybe> mempty == Just (Product 1)
>   False
>
> so, "Product Int" as Monoid and "Maybe (Product Int)" as Monoid are totally
> different, - I understand what is Abel's groups on + and *, but I don't
> understand why GHC looks for Monoid instance for Int while Int is under
> Maybe... It will be right if:
>
>   instance (Monoid a) => Monoid (Maybe a) where
>     ...
>
> but is it true?! I suppose no such constraint on "a". Is it all due to
> defaults? Or I lost my brain at this night :)
>
>
> /Best regards, Paul
>
>
>>
>> There are similar monoidal instances for Bool, such as Any and All.
>>
>> On Wed, Jun 7, 2017 at 12:33 PM, Baa <aqua...@gmail.com> wrote:
>> > Maybe a is the Monoid:
>> >
>> >   instance Monoid a => Monoid (Maybe a) -- Defined in ‘GHC.Base’
>> >
>> > so I can compare its values with empty value:
>> >
>> >   mempty == Nothing
>> >   => True
>> >
>> > But if I try:
>> >
>> >   mempty == Just 4
>> >
>> > I get:
>> >
>> >   <interactive>:1:1: error:
>> >       • Ambiguous type variable ‘a0’ arising from a use of ‘mempty’
>> >         prevents the constraint ‘(Monoid a0)’ from being solved.
>> >         Probable fix: use a type annotation to specify what ‘a0’
>> > should be. These potential instances exist:
>> >           instance Monoid a => Monoid (IO a) -- Defined in
>> > ‘GHC.Base’ instance Monoid Ordering -- Defined in ‘GHC.Base’
>> >           instance Monoid a => Monoid (Maybe a) -- Defined in
>> > ‘GHC.Base’ ...plus 7 others
>> >           (use -fprint-potential-instances to see them all)
>> >       • In the first argument of ‘(==)’, namely ‘mempty’
>> >         In the expression: mempty == Just 4
>> >         In an equation for ‘it’: it = mempty == Just 4
>> >
>> > OK, I try:
>> >
>> >   mempty::Maybe Int
>> >
>> > and get:
>> >
>> >   <interactive>:1:1: error:
>> >       • No instance for (Monoid Int) arising from a use of ‘mempty’
>> >       • In the expression: mempty :: Maybe Int
>> >         In an equation for ‘it’: it = mempty :: Maybe Int
>> >
>> > so, how is related Int to Monoid, why does ghc expect from
>> > mempty::Maybe Int, Int to be Monoid?! As I understand, this means
>> > only that I mean "mempty" from (Maybe Int) type, which is Monoid
>> > and exists sure.
>> >
>> > Interesting is, that:
>> >
>> >   mempty::Maybe [Int]
>> >   => Nothing
>> >
>> > but how is related "monoidality" of "Maybe a" with "monoidality of
>> > "a" ???
>> >
>> > Initial idea was to make comparison:
>> >
>> >   mempty :: Maybe Int == Just 4
>> >   => False
>> >
>> >
>> > /Best regards,
>> >   Paul
>> > _______________________________________________
>> > Beginners mailing list
>> > Beginners@haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>> _______________________________________________
>> Beginners mailing list
>> Beginners@haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
>
> --
> Best regards,
>   Paul a.k.a. 6apcyk
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

Message: 4
Date: Wed, 7 Jun 2017 22:03:34 +0300
From: aquagnu <aqua...@gmail.com>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Alternative instance w/ additional
        restriction
Message-ID: <20170607220334.20747...@gmail.com>
Content-Type: text/plain; charset=UTF-8

Thank you, David!

> I honestly don't think so.  But you can ask on haskell-cafe or on
> stackoverflow if you like.  There is a reasonable chance that a class
> or library exists that already will do what you are looking for, just
> that I haven't heard of it.
> 
> On Wed, Jun 7, 2017 at 12:06 PM, Baa <aqua...@gmail.com> wrote:
> > So, if I understood right, I'm trying to restrict instance more than
> > class allows. And only way to accomplish it - is to create own class
> > instead of Alternative which will not be based on
> > Functor :: (* -> *) -> *, like Alternative. No other workarounds?
> >
> >
> >
> > В Wed, 7 Jun 2017 11:25:26 -0400
> > David McBride <toa...@gmail.com> пишет:
> >  
> >> The Alternative class says nothing about the a in MyData a.  It
> >> only represents code relevant to MyData.
> >>
> >> When you see class Applicative f => Alternative (f :: * -> *), that
> >> means all of its functions had to work on any f, where f takes any
> >> type and becomes some other type which could be anything.
> >>
> >> The reason it works for Monoid is that class Monoid a where implies
> >> that a is completely known by the time the instance is fulfilled,
> >> therefore the instance can look at what a ended up being and ensure
> >> whatever a is, it must have this constraint on it.
> >>
> >> You can tell the difference because mempty returns a type that
> >> mentions the a mentioned in the class, whereas empty returns an a
> >> that is not mentioned in the class, therefore it has to work for
> >> any a.
> >>
> >> On Wed, Jun 7, 2017 at 8:26 AM, Baa <aqua...@gmail.com> wrote:  
> >> > Hello all!
> >> >
> >> > If I try to write, for example:
> >> >
> >> >   instance Alternative MyData where
> >> >     empty = NoMyData
> >> >     a <|> b = if a == b then ...
> >> >
> >> > I get error (see on bottom of the mail) sure, bcz I suppose
> >> > something like:
> >> >
> >> >    Eq a => (MyData a)
> >> >
> >> > All my attempts to add something to instance's `pure` signature
> >> > have failed. How can I instantiate something with additional
> >> > restrictions, like in this case? Or are there another solutions
> >> > for such problem?
> >> >
> >> > Interesting is that MyData derives Eq itself! Which, I suppose,
> >> > must means that "Eq (MyData a)", and if it's true than "Eq a" is
> >> > true, because how "MyData a" can be Eq without to be "Eq a" (with
> >> > *automatically deriving* of Eq instance) ?!
> >> >
> >> > By the way, for Monoid (which is "* -> Constraint") I can add
> >> > "Eq a" constraint without problems:
> >> >
> >> >   instance Eq a => Monoid (Origin a) where
> >> >     mempty = NoMyData
> >> >     mappend NoMyData a = a
> >> >     mappend a NoMyData = a
> >> >     mappend (MyData a) (MyData b)|a == b = MyData a
> >> >                                  |otherwise = NoMyData
> >> >
> >> > but not for Alternative, which is "(* -> *) -> Constraint".
> >> >
> >> > *ORIGINAL ERROR DUMP*:
> >> > ======================
> >> >     42  16 error           error:
> >> >                                • No instance for (Eq a) arising
> >> > from a use of ‘==’ Possible fix:
> >> >                                    add (Eq a) to the context of
> >> >                                      the type signature for:
> >> >                                        (<|>) :: Origin a ->
> >> > Origin a -> Origin a • In the expression: a == b
> >> >                                  In the expression: if a == b
> >> > then NoOrigin else NoOrigin In an equation for ‘<|>’:
> >> >                                      a <|> b = if a == b then
> >> > NoOrigin else NoOrigin (intero)
> >> >
> >> >
> >> > /Best regards
> >> >   Paul
> >> > _______________________________________________
> >> > Beginners mailing list
> >> > Beginners@haskell.org
> >> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners  
> >> _______________________________________________
> >> Beginners mailing list
> >> Beginners@haskell.org
> >> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners  
> >
> > _______________________________________________
> > Beginners mailing list
> > Beginners@haskell.org
> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners  
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners



-- 
Best regards,
  Paul a.k.a. 6apcyk


------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 108, Issue 4
*****************************************

Reply via email to