 
            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
 
            Hi Debasish, You can also write (f1 >=> f2 >=> f3) acc or f1 acc >>= f2 >>= f3 or foldr (>=>) [f1, f2, f3] pure acc Regards, Li-yao On 2/1/20 1:54 PM, Debasish Ghosh 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.
 
            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 
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.
 
            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 
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
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.
 
            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
Not undervaluing this post, but to be clear to the OP, all of that really isn't adding any capabilities, just reifying the ones that others exposed. (You can use foldMap instead of foldr). This could be useful if you want to do higher-level stuff with it later on, but for the purposes of the original post I think it really is overkill, isn't it? -- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.
 
            Thanks for all the suggestions ..
On Sun, Feb 2, 2020 at 4:20 AM Juan Casanova 
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
Not undervaluing this post, but to be clear to the OP, all of that really isn't adding any capabilities, just reifying the ones that others exposed. (You can use foldMap instead of foldr). This could be useful if you want to do higher-level stuff with it later on, but for the purposes of the original post I think it really is overkill, isn't it?
-- The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336.
_______________________________________________ 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.
-- Debasish Ghosh http://manning.com/ghosh2 http://manning.com/ghosh Twttr: @debasishg Blog: http://debasishg.blogspot.com Code: http://github.com/debasishg
 
            On 2/1/20, Jack Kelly 
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 }
I define a general `Endo` type in the category package, here: http://hackage.haskell.org/package/category-0.2.5.0/docs/Data-Morphism-Endo.... Thus one can use `Endo (Kleisli m)`.
 
            I finally ended up defining a combinator
flattenAndCompose :: (Category cat) => [cat a a] -> cat a a
flattenAndCompose = foldr (>>>) id
that can be used both for function composition and Kleislis since both (->)
and Kleisli are instances of Category. I will take a look at Endo - thanks
for the pointer ..
regards.
On Fri, Feb 7, 2020 at 11:26 PM Matthew Farkas-Dyck 
On 2/1/20, Jack Kelly
wrote: 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 }
I define a general `Endo` type in the category package, here:
http://hackage.haskell.org/package/category-0.2.5.0/docs/Data-Morphism-Endo....
Thus one can use `Endo (Kleisli m)`. _______________________________________________ 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.
-- Debasish Ghosh http://manning.com/ghosh2 http://manning.com/ghosh Twttr: @debasishg Blog: http://debasishg.blogspot.com Code: http://github.com/debasishg
participants (6)
- 
                 Debasish Ghosh Debasish Ghosh
- 
                 Jack Kelly Jack Kelly
- 
                 Juan Casanova Juan Casanova
- 
                 Justin Paston-Cooper Justin Paston-Cooper
- 
                 Li-yao Xia Li-yao Xia
- 
                 Matthew Farkas-Dyck Matthew Farkas-Dyck