Map list of functions over a single argument

I'm after a function, sort of equivalent to map, but rather than mapping a function over a list of arguments, I want to map a list of functions over the same argument. The signature would be [a -> b] -> a -> [b], but hoogle didn't come up with anything. It seems like an obvious analogue of map, so I'm pretty sure I'm missing something (otherwise, I'd just write it myself, and not bother :-)) Can anyone point me in the right direction? Thanks, Paul.

p.f.moore:
I'm after a function, sort of equivalent to map, but rather than mapping a function over a list of arguments, I want to map a list of functions over the same argument. The signature would be [a -> b] -> a -> [b], but hoogle didn't come up with anything.
Prelude> map ($ 3) [(*2),(+1),div 1] [6,4,0]

On 20/02/07, Donald Bruce Stewart
p.f.moore:
I'm after a function, sort of equivalent to map, but rather than mapping a function over a list of arguments, I want to map a list of functions over the same argument. The signature would be [a -> b] -> a -> [b], but hoogle didn't come up with anything.
Prelude> map ($ 3) [(*2),(+1),div 1] [6,4,0]
Cool. I told you I was missing something! :-) The more I learn about using higher order functions, the more impressed I get. Thanks, Paul

Quoth Paul Moore, nevermore,
Prelude> map ($ 3) [(*2),(+1),div 1] [6,4,0]
Cool. I told you I was missing something! :-)
I suppose this would fit your original idea if you wanted that particular type signature. (Warning: not tested.)
f :: a -> [a -> b] -> [b] f c fs = map ($ c) fs
mapF :: [a -> b] -> a -> [b] mapF = flip f
Aren't higher order functions just dreamy... ? ;-) -- Dougal Stanton

On Tue, Feb 20, 2007 at 02:07:08PM +0000, Paul Moore wrote:
I'm after a function, sort of equivalent to map, but rather than mapping a function over a list of arguments, I want to map a list of functions over the same argument. The signature would be [a -> b] -> a -> [b], but hoogle didn't come up with anything.
It seems like an obvious analogue of map, so I'm pretty sure I'm missing something (otherwise, I'd just write it myself, and not bother :-))
Can anyone point me in the right direction?
It's rather a small function to bother putting in the libraries, and I think better expressed using map directly: rmap fs x = map ($ x) fs -- David Roundy http://www.darcs.net

On 20/02/07, David Roundy
It's rather a small function to bother putting in the libraries, and I think better expressed using map directly:
rmap fs x = map ($ x) fs
Yes. Now that I know the idiom, there's clearly little point in having a named function for it. Thanks, Paul.

Paul Moore wrote:
I'm after a function, sort of equivalent to map, but rather than mapping a function over a list of arguments, I want to map a list of functions over the same argument. The signature would be [a -> b] -> a -> [b], but hoogle didn't come up with anything.
It seems like an obvious analogue of map, so I'm pretty sure I'm missing something (otherwise, I'd just write it myself, and not bother :-))
Can anyone point me in the right direction?
It's also known as sequence :: Monad m => [m b] -> m [b] with m = (->) a sequence :: [a -> b] -> (a -> [b]) This is the fabulous MonadReader. Regards, apfelmus

Here comes an overwhelming post (so stop here if you're not interested
in applicative functors), but apfelmus stepped in this direction. The
funny part is that, modulo dictionary passing (which might be compiled
away), all 6 functions below do the Exact Same Thing because of
newtype erasure (Calling all experts: am I right about that?).
All of the themes below are explained in the Applicative Functors
pearl, which is an excellent read. See:
http://lambda-the-ultimate.org/node/1137
The "aha!" this code attempts to illuminate is that the point that
'maps' can be written as the sequencing of the environment monad is
akin to saying that "all regular polygons have a perimeter" as opposed
to "all 2-dimensional shapes have a perimeter." Both are obviously
legitimate claims, but we might be able to squeeze a little more
understanding out of the second version. A more germaine formulation:
it's not the monadic properties of the environment reader that we need
in order to solve this problem so much as it is the applicative
functor properties of the environment reader (which also happens to be
a monad).
Moreover, it doesn't just work for lists of functions--e.g. it could
work for trees too. The required property here is captured by
Data.Traversable, which the list type constructor satisfies. Use of
traversable often comes hand-in-hand with applicative functors.
\begin{code}
import qualified Control.Monad as M
import Control.Monad.Reader
import qualified Control.Applicative as AF
import qualified Data.Traversable as T
-- Nothing Fancy Here:
-- to avoid confusion with monad during this presentation,
-- we create a newtype for environment as an applicative functor
newtype ReaderAF r a = ReaderAF { runReaderAF :: r -> a }
instance Functor (ReaderAF r) where
fmap fn (ReaderAF f) = ReaderAF (fn . f)
instance AF.Applicative (ReaderAF r) where
pure a = ReaderAF (const a)
(ReaderAF f) <*> (ReaderAF g) = ReaderAF (\r -> (f r) (g r))
-- our target functions
maps, mi_maps, me_maps, afe_maps, afi_maps, maf_maps :: [a -> b] -> a -> [b]
-- conventional
maps fs a = map ($ a) fs
-- monadic (implicit reader)
mi_maps fs a = (M.sequence fs) a
-- monadic (explicit reader)
me_maps fs a = runReader (M.sequence fs') a
where fs' = map Reader fs
-- applicative functor (explicit reader)
afe_maps fs a = runReaderAF (T.sequenceA fs') a
where fs' = map ReaderAF fs
-- applicative functor (implicit reader)
afi_maps fs a = (T.sequenceA fs) a
-- combination (a monad as an applicative functor)
maf_maps fs a = runReader (AF.unwrapMonad (T.sequenceA fs')) a
where fs' = map (AF.WrapMonad . Reader) fs
\end{code}
Also, Data.Traversable exports a function 'sequence' that generalizes
the one from Control.Monad/Prelude to work on more than just lists:
Prelude> :m + Data.Traversable
Prelude Data.Traversable> :t Data.Traversable.sequence
Data.Traversable.sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
So we could have even written 4 more versions of the function that
again all reduce to the same thing (modulo dictionary passing)!
It isn't really highlighted above, but one high-level difference
between monads and applicative functors is a question of how paramount
is the notion of sequencing (the >>= kind of sequencing more so than
the 'sequence' kind of sequencing).
Sorry for the dropping the concept bomb on a simple question, but
hopefully someone enjoyed the adventure.
Nick
On 2/20/07, David House
On 20/02/07, apfelmus@quantentunnel.de
wrote: It's also known as
sequence :: Monad m => [m b] -> m [b]
with m = (->) a
Don't forget to import Control.Monad.Instances for this to work.

On Tue, 20 Feb 2007 apfelmus@quantentunnel.de wrote:
Paul Moore wrote:
I'm after a function, sort of equivalent to map, but rather than mapping a function over a list of arguments, I want to map a list of functions over the same argument. The signature would be [a -> b] -> a -> [b], but hoogle didn't come up with anything.
It seems like an obvious analogue of map, so I'm pretty sure I'm missing something (otherwise, I'd just write it myself, and not bother :-))
Can anyone point me in the right direction?
It's also known as
sequence :: Monad m => [m b] -> m [b]
with m = (->) a
sequence :: [a -> b] -> (a -> [b])
This is the fabulous MonadReader.
Since there are a few questions, where 'sequence' is the answer - what about a 'sequence' honour Wiki page? I remember the combinatoric problem: http://www.haskell.org/pipermail/haskell-cafe/2006-June/015976.html

On 2/21/07, Henning Thielemann
On Tue, 20 Feb 2007 apfelmus@quantentunnel.de wrote:
Paul Moore wrote:
I'm after a function, sort of equivalent to map, but rather than mapping a function over a list of arguments, I want to map a list of functions over the same argument.
Well this is not very sexy, no monads or anything, but I kinda believe in Keep It Simple: Prelude> let revApply a f = f a Prelude> let rMap a fs = map (revApply a) fs Prelude> rMap 2 [(*4),(^2),(+12),(**0.5)] [8.0,4.0,14.0,1.4142135623730951] oh and I REALLY enjoyed the discussions that this spawned about things monadic, as there was some really slick stuff in there... The little thing about 'join' and etcetera... really good stuff. cheers... gene

Gene A wrote:
Well this is not very sexy, no monads or anything, but I kinda believe in Keep It Simple:
Prelude> let revApply a f = f a Prelude> let rMap a fs = map (revApply a) fs Prelude> rMap 2 [(*4),(^2),(+12),(**0.5)] [8.0,4.0,14.0,1.4142135623730951]
Note that revApply here is precisely flip ($). And ($a) is the same as flip ($) a. So this reduces to one of the earlier examples rather quickly. It is possible to argue 'it's nice to give revApply a name'. It's also possible to argue 'taking a section of $ is even better than naming revApply'. Beauty in the eye of the beholder... Jules

On 2/21/07, Jules Bean
Gene A wrote:
Prelude> let revApply a f = f a Prelude> let rMap a fs = map (revApply a) fs Prelude> rMap 2 [(*4),(^2),(+12),(**0.5)] [8.0,4.0,14.0,1.4142135623730951]
Note that revApply here is precisely flip ($).
And ($a) is the same as flip ($) a.
So this reduces to one of the earlier examples rather quickly.
It is possible to argue 'it's nice to give revApply a name'. It's also possible to argue 'taking a section of $ is even better than naming revApply'.
----------------- jules, .. right on... ran this through ghci... let rMap a fs = map ($ a) fs { that is clean ... gotta admit.. } Prelude> rMap 2 [(*4),(^2),(+12),(**0.5)] [8.0,4.0,14.0,1.4142135623730951] Prelude> :t rMap rMap :: forall a b. a -> [a -> b] -> [b] ==== About naming the secondary revApply function would agree and that would have been in a "where" clause inside the definition of rMap had that been saved to a file, but ghci doesn't really lend itself to multiline definitions so that is why that was there, and it was also named in this case to show what was going on... The functions as I originally defined them are probably easier for someone new to Haskell to understand what was going on than the rather stark ($ a) in the final factoring of the function... Though the final resulting function is far the cleaner for that notation! gene

On 2/22/07, Gene A
The functions as I originally defined them are probably easier for someone new to Haskell to understand what was going on than the rather stark ($ a) in the final factoring of the function... Though the final resulting function is far the cleaner for that notation!
This is what I came up with when I was experimenting: map (\f -> f $ a) fs which then helped me to see it could be rewritten as just map ($ a) fs martin
participants (11)
-
apfelmus@quantentunnel.de
-
David House
-
David Roundy
-
dons@cse.unsw.edu.au
-
Dougal Stanton
-
Gene A
-
Henning Thielemann
-
Jules Bean
-
Martin DeMello
-
Nicolas Frisby
-
Paul Moore