[Haskell-beginners] mempty and "No instance for (Monoid Int)"

David McBride toad3k at gmail.com
Wed Jun 7 19:00:55 UTC 2017


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 <aquagnu at 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 <aquagnu at 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 at haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>> _______________________________________________
>> Beginners mailing list
>> Beginners at haskell.org
>> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
>
>
>
> --
> Best regards,
>   Paul a.k.a. 6apcyk
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


More information about the Beginners mailing list