[Haskell-cafe] Endo a, endomorphisms

Olaf Klinke olf at aatal-apotheke.de
Mon Dec 6 22:45:26 UTC 2021


> it might be possible that the intention was
> to state that function composition is an endomorphism of the set of endofunctions (Endo a).

> So again, given that the context is the Data.Monoid library, it seems much more appropriate to
> say that Endo a forms a monoid of endofunctions under composition. As the examples I presented
> above show, even stating that function composition is an endomorphism of Endo a (endofunctions)
> seems incorrect.
> 

What you write does not even type-check: Composition is an operation
(b -> c) -> (a -> b) -> (a -> c)
so it is a binary operation. Hence it cannot form an endomorphism,
because you can't unify the above type with (x -> x). No ambiguity
here. 

> opening :: String -> String
> opening = ("Hello, " ++)
> 
> closing :: String -> String
> 
> closing = (++ "!")
> 
> eo = Endo opening
> 
> ec = Endo closing

This is a manifestation of the fact that every monoid has a function 
	a -> Endo a
given by 
	\a -> Endo (mappend a)
This is indeed a monoid homomorphism (by virtue of associativity). Your
'eo' is of this kind. But then you mixed in another monoid
homomorphism, namely 
	\a -> Endo (flip mappend a)
where your 'ec' is of this kind. It is not true in general that you can
mix these two monoid homomorphisms. Only for commutative monoids the
above two homomorphisms are identical. And (String,++) is not
commutative. 

Indeed we could not give a Monoid instance to naked (a -> a) because it
overlaps with the Semigroup instance you mention. But historically this
is not the reason why the Endo newtype was introduced. One could argue
that the Semigroup instance should also be on a newtype. I'd be in
favour of such a proposal. 

Olaf

P.S.: Let S be a functor (a signature) and a be an S-algebra, that is,
there is a structure map
	alpha :: S a -> a.
Then for any r, the type (r -> a) is an S-algebra, too. Indeed, 
    alpha' :: Functor s => (s       a  ->      a) -> 
                            s (r -> a) -> r -> a
    alpha' alpha sf = \r -> alpha (fmap ($x) sf)
This is what makes the ReaderT transformer work. 
For Semigroup, the signature is S a = (a,a) and alpha = uncurry (<>).



More information about the Haskell-Cafe mailing list