[Haskell-cafe] Seeking help to generalize this ..

Jack Kelly jack at jackkelly.name
Sat Feb 1 22:05:49 UTC 2020


Related:

In Data.Monoid there is the 'Endo' newtype, which wraps functions of
type 'a -> a'. Is there an 'EndoM' variant, or is that something that's
usually created by putting other pieces together? Below is a sketch of
what I mean:

-- Maybe this is known by another name?
newtype EndoM f a = EndoM { appEndoM :: a -> f a }

-- Bind typeclass is from package semigroupoids.
-- It means "Monad sans 'return'".
-- Maybe use Monad f => here instead if getting the Bind instances is
-- too annoying? (e.g., Writing orphan instances).
instance Bind f => Semigroup (EndoM f a) where
  EndoM f <> EndoM g = EndoM $ f ->- g

-- Bind is not a superclass of Monad, so we get this awkward set of
-- required constraints here.
instance (Bind f, Monad f) => Monoid (EndoM f a) where
  mempty = EndoM pure

-- Jack

Justin Paston-Cooper <paston.cooper at gmail.com> writes:

> Hello,
>
> I suggest taking a quick look at the function ‘fold’ in Data.Foldable, and
> also Data.Functor.Compose. That should be good start for composing any list
> of such functions.
>
> Cheers,
>
> J.
>
> On Sat, 1 Feb 2020 at 19:55, Debasish Ghosh <ghosh.debasish at gmail.com>
> wrote:
>
>> Hi -
>>
>> How can I generalize the following pattern to an arbitrary list of
>> functions ?
>>
>> compose :: (Monad m) => (Foo -> m Foo) -> (Foo -> m Foo) -> (Foo -> m Foo)
>> -> Foo -> m Foo
>> compose f1 f2 f3 acc = do
>>   a <- f1 acc
>>   b <- f2 a
>>   f3 b
>>
>> Any help please ..
>> regards.
>>
>> --
>> Debasish Ghosh
>> http://manning.com/ghosh2
>> http://manning.com/ghosh
>>
>> Twttr: @debasishg
>> Blog: http://debasishg.blogspot.com
>> Code: http://github.com/debasishg
>> _______________________________________________
>> 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.


More information about the Haskell-Cafe mailing list