[Haskell-beginners] Capture the notion of invertible

Javran Cheng javran.c at gmail.com
Thu Mar 20 20:25:07 UTC 2014


I thought every Monad is a Category because I see
"instance Monad m => Category (Kleisli m)" in Control.Category,
So what are the other ways?

I tried to do the exercise:

import Prelude hiding ((.), id)
import Control.Category
import Control.Arrow
import Data.Monoid

newtype Endomorphism cat a = E { runE :: cat a a }

instance Category cat => Monoid (Endomorphism cat a) where
    mempty = E id
    (E g) `mappend` (E f) = E (g . f)

testMonoid :: [Endomorphism (Kleisli []) Int]
testMonoid = map (E . Kleisli)
    [ \x -> [x, x+1]
    , \x -> [x-1, x]
    , \x -> [x+10]
    ]

main :: IO ()
main =
    print $ runKleisli (runE (mconcat testMonoid)) 10
    --   [10]
    -- > [10,11]
    -- > [9,10, 10,11]
    -- > [19,20,20,21]

Is this what you meant?

Javran


> Date: Thu, 20 Mar 2014 09:47:30 -0400
> From: Brent Yorgey <byorgey at seas.upenn.edu>
> To: beginners at haskell.org
> Subject: Re: [Haskell-beginners] Capture the notion of invertible
> Message-ID: <20140320134730.GA4285 at seas.upenn.edu>
> Content-Type: text/plain; charset=us-ascii
>
> On Thu, Mar 20, 2014 at 02:18:12AM -0400, Javran Cheng wrote:
>> Off topic:
>
> This is not off topic for the beginners list at all. =)
>
>> This comment makes perfect sense to me, because "monoid-like" reminds
>> me of Data.Monoid,
>> which does not totally capture what I know about monoid: monad is
>> "just a monoid in the category of endofunctors"
>
> The "monoid" being referred to here is a very generalized sense of the
> word, and is quite different from (though distantly related to)
> Haskell's Monoid type class.
>
>> but Monad is not in any sense fit into a Monoid.
>> Here I find that when I talk about "monoid-like", I actually refer to Category,
>> and Monad is an instance of Category, which backs up my guess.
>
> "Monad is an instance of Category" --- this doesn't really make
> sense as stated.  It's certainly not true that every instance of Monad
> is also an instance of Category; the kinds don't even match.  It is
> true that you can build a Category out of a Monad, though there are
> actually several ways to do so.  The most well-known in the Haskell
> world is Kleisli, but there are other ways.
>
>> In a word, can I say that when talking about reducing data (Sum,
>> Product, etc.), I'm referring to Monoid,
>> and when I talking about monoid-like composition, I'm referring to
>> Category?
>
> "monoid-like composition" can refer to Monoid too.  The essential
> difference is *types*: in particular you can think of a Category as a
> "typed Monoid": with a Monoid, *any* two things can be composed.  With
> a Category, you can only compose things whose types match.  So
> conversely you can also think of a Monoid as a "Category with only one
> type".  As an (easy) exercise:
>
>   newtype Endomorphism cat a = E (cat a a)
>
>   instance Category cat => Monoid (Endomorphism cat a) where
>     ...
>
> -Brent
>
>>
>> Javran
>>
>> > Date: Tue, 18 Mar 2014 02:48:21 +0700
>> > From: Kim-Ee Yeoh <ky3 at atamo.com>
>> > To: The Haskell-Beginners Mailing List - Discussion of primarily
>> >         beginner-level topics related to Haskell <beginners at haskell.org>
>> > Subject: Re: [Haskell-beginners] Capture the notion of invertible
>> >         functions
>> > Message-ID:
>> >         <CAPY+ZdTyj81gcUaZJfHGeta8rbjxup8ReKHJ=iy7ePzKkQPomQ at mail.gmail.com>
>> > Content-Type: text/plain; charset="iso-8859-1"
>> >
>> > > When you're talking about invertible functions, the idea you're probably
>> > reaching for is an isomorphism -- that is, we want the function to have
>> > certain nice properties on top of just being a map from a -> b with an
>> > inverse map from b -> a.
>> >
>> > The usual meaning of 'f is invertible' is that it is both left- and
>> > right-invertible, thus making it bijective: see first bullet in [1].
>> >
>> > Here you're alluding to f being merely left-invertible, something I don't
>> > see mentioned in OP.
>> >
>> > > You also want the function to be a bijection, which is captured in the
>> > notion of an isomorphism.
>> >
>> > I'm reminded of a reddit convo where the idea was tossed out that
>> > semigroups should always be promoted to monoids [2].
>> >
>> > I argued no. I also cited a case where a supposedly nicer monoid causes
>> > more problems for a ghc hacker than the true semigroup [3].
>> >
>> > Having structure is nice. And sometimes we just have to work with what's
>> > given to us.
>> >
>> > Category theory calls a /monomorphism/ something that's strictly weaker
>> > than left-invertible. An arrow that's (additionally) left-invertible
>> > corresponds to a /split mono/.
>> >
>> > Hence in order of _decreasing_ niceness: Iso, Split mono, Mono. As research
>> > uncovers more interesting phenomena, this sequence will continuing growing
>> > to the right.
>> >
>> > We can't always impose that niceness because that nukes whatever we're
>> > studying. So we gotta respect the situation. And given lemons, make
>> > lemonade.
>> >
>> >
>> > [1]
>> > http://en.wikipedia.org/wiki/Bijection,_injection_and_surjection#Bijection
>> >
>> > [2]
>> > http://www.reddit.com/r/haskell/comments/1ou06l/improving_applicative_donotation/ccvtqot?context=1
>> >
>> > [3]
>> > http://www.reddit.com/r/haskell/comments/1ou06l/improving_applicative_donotation/ccy4n2d
>>
>>
>>
>>
>>
>> --
>> Javran (Fang) Cheng
>> _______________________________________________
>> Beginners mailing list
>> Beginners at haskell.org
>> http://www.haskell.org/mailman/listinfo/beginners
>>


More information about the Beginners mailing list