(liftM join .) . mapM

Can (liftM join .) . mapM be improved? (Monad m) => (a -> m [b]) -> [a] -> m [b] -- Tony Morris http://tmorris.net/

I'd write it as foo f = join .<$> sequence . (f <$>) where (.<$>) :: (.<$>) :: Functor f => (a -> b) -> ((x -> f a) -> (x -> f b)) x .<$> y = (x <$>) . y is part of my line-noise toolbox. This join .* sequence family of functions is quite common. Should really have a name for them. Tony Morris-4 wrote:
Can (liftM join .) . mapM be improved? (Monad m) => (a -> m [b]) -> [a] -> m [b]
-- View this message in context: http://old.nabble.com/%28liftM-join-.%29-.-mapM-tp26953786p26954040.html Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

2009/12/29 Tony Morris
Can (liftM join .) . mapM be improved? (Monad m) => (a -> m [b]) -> [a] -> m [b]
Hi Tony I count this as a personal preference rather than an improvement: joinything2 :: (Monad m) => (a -> m [b]) -> [a] -> m [b] joinything2 = liftM join `oo` mapM oo is one of of a family of functions I use often to avoid sectioning/composing mania. It's known to Raymond Smullyan fans as 'blackbird', though I call it oo as a pun on Standard MLs o (which is Haskells (.) of course). -- | Compose an arity 1 function with an arity 2 function. -- B1 - blackbird oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d oo f g = (f .) . g Extending the arity works quite nicely too: -- | Compose an arity 1 function with an arity 3 function. -- B2 - bunting ooo :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e ooo f g = ((f .) .) . g ... and so on. I've used `oooo` but some how never needed `ooooo`. Due to their typographical appearance in infix form, the family name I have for them is specs (i.e. glasses, googles...) - `oo` Best wishes Stephen

On Tue, Dec 29, 2009 at 12:24 PM, Stephen Tetley
oo is one of of a family of functions I use often to avoid sectioning/composing mania. It's known to Raymond Smullyan fans as 'blackbird', though I call it oo as a pun on Standard MLs o (which is Haskells (.) of course).
-- | Compose an arity 1 function with an arity 2 function. -- B1 - blackbird oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d oo f g = (f .) . g
Extending the arity works quite nicely too:
-- | Compose an arity 1 function with an arity 3 function. -- B2 - bunting ooo :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e ooo f g = ((f .) .) . g
... and so on. I've used `oooo` but some how never needed `ooooo`. Due to their typographical appearance in infix form, the family name I have for them is specs (i.e. glasses, googles...) - `oo`
Why restrict yourself to functions? You can generalize this to
arbitrary stacks of functors.
oo :: (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b)
oo = fmap . fmap
ooo :: (Functor f, Functor g, Functor h) => (a -> b) -> f (g (h a))
-> f (g (h b))
ooo = oo . fmap
etc.
(Unfortunately, the Functor ((->) a) instance is orphaned in
Control.Monad.Instances, at least until some future Haskell revision
finally adds it to the Prelude.)
--
Dave Menendez

2009/12/29 David Menendez
Why restrict yourself to functions? You can generalize this to arbitrary stacks of functors.
oo :: (Functor f, Functor g) => (a -> b) -> f (g a) -> f (g b) oo = fmap . fmap
Hi David Nice! this seems to be taking things into TypeCompose territory, cf. fmapFF. http://hackage.haskell.org/package/TypeCompose For my purposes, I do like the simple (functional) type signatures of the original specs combinators, but maybe they are under-utilizing good names on something that merits being more general... Best wishes Stephen

Hi Stefan
The bird names for combinators stem from Raymond Smullyan's book - To
Mock a Mockingbird (this is second-hand knowledge as I don't have my
own copy - though I think I've just obliged to get myself one as a
post-Christmas treat).
The other names B1 B2 and the more common S K I C W etc - many of
these surely date back to Schonfinkel, but maybe some of the exotic
ones are due to David Turner as he used a particular set to implement
the pioneering functional language SASL (again this is all second hand
knowledge via Antoni Diller's excellent, but out of print book
'Compiling Functional Languages').
Best wishes
Stephen
2009/12/29 Stefan Holdermans
Stephen,
oo f g = (f .) . g
ooo f g = ((f .) .) . g
Why are these also called blackbird and bunting?
Thanks,
Stefan

Stephen Tetley
-- | Compose an arity 1 function with an arity 2 function. -- B1 - blackbird oo :: (c -> d) -> (a -> b -> c) -> a -> b -> d oo f g = (f .) . g
Extending the arity works quite nicely too:
-- | Compose an arity 1 function with an arity 3 function. -- B2 - bunting ooo :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e ooo f g = ((f .) .) . g
And oo = (.).(.) and ooo = (.).(.).(.) There was a suggestion a few years back to standardise these as I recall something like: $0 = $ $1 = . $2 = (.).(.) and so on but nothing came of it. Dominic.

2009/12/29 Dominic Steinitz
And oo = (.).(.) and ooo = (.).(.).(.)
There was a suggestion a few years back to standardise these as I recall something like:
$0 = $ $1 = . $2 = (.).(.)
and so on but nothing came of it.
Hi Dominic Hmm, name-wise I would have to be dishonourable and vote for myself on this particular one. But, I rather suspect that Haskell-prime-prime (or whatever it gets called in a few years time) will bite the bullet and go for Unicode symbols, otherwise we'll be doomed to programs that look somewhat 'expletive-deleted'. Best wishes Stephen

Hi Tony On 29 Dec 2009, at 12:10, Tony Morris wrote:
Can (liftM join .) . mapM be improved? (Monad m) => (a -> m [b]) -> [a] -> m [b]
You can (a) generalize m from Monad to Applicative (b) generalize [b] to any Monoid (c) generalize [a] to f a for any Foldable f and write ala AppLift foldMap if you happen to have some of my usual kit. See below. Cheers Conor Here's the machinery.
class Newtype n where type Unwrap n wrap :: Unwrap n -> n unwrap :: n -> Unwrap n
ala :: Newtype v' => (t -> t') -> ((s -> t') -> u -> v') -> (s -> t) -> u -> Unwrap v' ala p h f u = unwrap (h (p . f) u)
Here's a rather useful newtype, capturing applicative lifting of monoids.
newtype AppLift a x = AppLift (a x)
instance (Applicative a, Monoid x) => Monoid (AppLift a x) where mempty = AppLift (pure mempty) mappend (AppLift ax) (AppLift ay) = AppLift (mappend <$> ax <*> ay)
instance Newtype (AppLift a x) where type Unwrap (AppLift a x) = a x wrap = AppLift unwrap (AppLift ax) = ax

On Tue, 2009-12-29 at 18:20 +0000, Conor McBride wrote:
Hi Tony
On 29 Dec 2009, at 12:10, Tony Morris wrote:
Can (liftM join .) . mapM be improved? (Monad m) => (a -> m [b]) -> [a] -> m [b]
You can
(a) generalize m from Monad to Applicative (b) generalize [b] to any Monoid (c) generalize [a] to f a for any Foldable f
and write
ala AppLift foldMap
if you happen to have some of my usual kit. See below.
Cheers
Conor
What is benefit of it over: concatMapA f = foldr (liftA2 mappend . f) (pure mempty) Regards

Hi Maciej On 29 Dec 2009, at 20:52, Maciej Piechotka wrote:
On Tue, 2009-12-29 at 18:20 +0000, Conor McBride wrote:
ala AppLift foldMap
What is benefit of it over: concatMapA f = foldr (liftA2 mappend . f) (pure mempty)
Given that applicative functors take monoids to monoids, it's nice to exploit that property by name, rather than reconstructing it by engineered coincidence. I reuse the "library" pattern once (AppLift) that you reinvent in two places (liftA2 mappend) (pure mempty). (Ironically, foldr is defined in terms of foldMap by code that amounts to, modulo a flip, ala Endo foldMap appealing to the monoid of endomorphisms.) The result is an operation which (a) points out the essential mechanism, foldMap; (b) points out the structures on which it works, lifted monoids; (c) is short enough not to bother naming. More structure, less code, Conor

On Tue, 2009-12-29 at 23:00 +0000, Conor McBride wrote:
Hi Maciej
On 29 Dec 2009, at 20:52, Maciej Piechotka wrote:
On Tue, 2009-12-29 at 18:20 +0000, Conor McBride wrote:
ala AppLift foldMap
What is benefit of it over: concatMapA f = foldr (liftA2 mappend . f) (pure mempty)
Given that applicative functors take monoids to monoids, it's nice to exploit that property by name, rather than reconstructing it by engineered coincidence.
I wouldn't state it as 'coincidence'. I don't need to create explicit map where implicit (liftA2 mappend and pure mempty) is sufficient. In this case I have one line when you have many (however it might be other case with more complicated examples - but I don't quite see how)[1]. Also I'm not quite sure if ala is something general and therefore should be exposed instead of just putting it. But I may be wrong Regards [1] http://www.willamette.edu/~fruehr/haskell/evolution.html ;)

Hi Maciej On 30 Dec 2009, at 00:07, Maciej Piechotka wrote:
On Tue, 2009-12-29 at 23:00 +0000, Conor McBride wrote:
Hi Maciej
On 29 Dec 2009, at 20:52, Maciej Piechotka wrote:
On Tue, 2009-12-29 at 18:20 +0000, Conor McBride wrote:
ala AppLift foldMap
What is benefit of it over: concatMapA f = foldr (liftA2 mappend . f) (pure mempty)
Given that applicative functors take monoids to monoids, it's nice to exploit that property by name, rather than reconstructing it by engineered coincidence.
I wouldn't state it as 'coincidence'. I don't need to create explicit map where implicit (liftA2 mappend and pure mempty) is sufficient.
The coincidence I mean is *between* liftA2 mappend and pure mempty: those are the pieces of a lifted monoid, without the observation that that's what's going on.
In this case I have one line when you have many (however it might be other case with more complicated examples - but I don't quite see how)[1].
It depends how you count. I have three symbols. The rest may not be in the standard library, but it's in my library. I certainlt wouldn't propose setting up that machinery just for that one problem. But if you google, you'll find I've suggested it several times, for a number of different problems.
Also I'm not quite sure if ala is something general and therefore should be exposed instead of just putting it. But I may be wrong
I've been programming with ala for some years now. I find it really useful. Zooming out a bit, I think there's a very healthy trend to introduce type distinctions at a finer level than is necessary for purposes of data representation, just to put a particular structural spin on things. The payback from that is writing less code, provided your library is set up to exploit richer type information.
[1] http://www.willamette.edu/~fruehr/haskell/evolution.html ;)
Quite so. I like evolving. All the best Conor

On Wed, 2009-12-30 at 00:45 +0000, Conor McBride wrote:
Hi Maciej
On 30 Dec 2009, at 00:07, Maciej Piechotka wrote:
On Tue, 2009-12-29 at 23:00 +0000, Conor McBride wrote:
Hi Maciej
On 29 Dec 2009, at 20:52, Maciej Piechotka wrote:
On Tue, 2009-12-29 at 18:20 +0000, Conor McBride wrote:
ala AppLift foldMap
What is benefit of it over: concatMapA f = foldr (liftA2 mappend . f) (pure mempty)
Given that applicative functors take monoids to monoids, it's nice to exploit that property by name, rather than reconstructing it by engineered coincidence.
I wouldn't state it as 'coincidence'. I don't need to create explicit map where implicit (liftA2 mappend and pure mempty) is sufficient.
The coincidence I mean is *between* liftA2 mappend and pure mempty: those are the pieces of a lifted monoid, without the observation that that's what's going on.
Hmm. Without explicit *writing* that it is what is going on. They are as coincidental as using return and >>= together - they are mappings betwean functions operating in specific domains (pure is liftA0, liftA is liftA1).
In this case I have one line when you have many (however it might be other case with more complicated examples - but I don't quite see how)[1].
It depends how you count. I have three symbols. The rest may not be in the standard library, but it's in my library. I certainlt wouldn't propose setting up that machinery just for that one problem. But if you google, you'll find I've suggested it several times, for a number of different problems.
Hmm. I would rather count per program. And, at least now, in increase length of program. However if [a) 'program' is a library and we get increased generalisation then increased length migh be justified b) we get more type safty c) we reuse it so many times in program the increase of code is not significant] it is a bit different matter.
Also I'm not quite sure if ala is something general and therefore should be exposed instead of just putting it. But I may be wrong
I've been programming with ala for some years now. I find it really useful. Zooming out a bit, I think there's a very healthy trend to introduce type distinctions at a finer level than is necessary for purposes of data representation, just to put a particular structural spin on things. The payback from that is writing less code, provided your library is set up to exploit richer type information.
While I agree in general I would rather limit it to between-function methods and when it suits in function. For example I had pice of code which was basicly state transformation composed by state transformations. Something similar to: myFunc :: Int -> State MyState Result However I found it clearer to have explicit let as transformations: let (v, s') = something s (v', s'') = somethingElse s' in somethingCompletlyDifferent v v' s'' And have signatures of ... -> MyState -> MyState. Well OK. It was state transformation. It is sometimes useful to have a finer level. But sometimes it's easier not to have it (sorry for gramar structure).
All the best
The same to you
participants (9)
-
Conor McBride
-
David Menendez
-
Dominic Steinitz
-
Kim-Ee Yeoh
-
Lutz Donnerhacke
-
Maciej Piechotka
-
Stefan Holdermans
-
Stephen Tetley
-
Tony Morris