Partially applying <*> with zip - haskell

I started to look at some Haskell code and found:
foo :: ([a] -> [b]) -> [a] -> [(a, b)]
let foo = (<*>) zip
I don't understand how this works, ap expects a f (a -> b) -> f a but zip is of type [a] -> [b] -> ([a, b]). I understand that f a -> f b would match [a] -> [b], but not f (a -> b).

Let's work out the types by hand. First, what are the types of the relevant expressions?
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
zip :: [a] -> [b] -> [(a, b)]
Now, we need to unify the type of zip with the type of the first argument to (<*>). Let's rename the unrelated as and bs:
Applicative f => f (a -> b)
[c] -> [d] -> [(c, d)]
First, what is f? What Applicative are we working in? The type of the bottom half is a function, so f must be ((->) [c]), or "functions taking a list of c as input". And once we've done that, we can see that:
f ~ ((->) [c])
a ~ [d]
b ~ [(c, d)]
Now that we've got the types to match up, we can look up the definition of (<*>) for functions:
instance Applicative ((->) a) where
pure = const
(<*>) f g x = f x (g x)
Substituting zip for f here, and rewriting as a lambda, yields:
(<*>) zip = \g x -> zip x (g x)
So, this needs a function from [a] -> [b] and an [a], and zips the input list with the result of calling the function on it.
That makes sense mechanically, but why? What more general understanding can lead us to this conclusion without having to work everything out by hand? I'm not sure my own explanation of this will be useful, so you may want to study the instances for ((->) t) yourself if you don't understand what's going on. But in case it is useful, here is a handwavy expanation.
The Functor, Applicative, and Monad instances for ((->) t) are the same as Reader t: "functions which have implicit access to a value of type t". (<*>) is about calling a function inside of an Applicative wrapper, which for functions is a two-argument function. It arranges that the "implicit" argument be passed to f, yielding another function, and calls that function with the value obtained by passing the implicit argument to g as well. So, (<*>) f, for some f, is "Give me another function, and a value x, and I'll pass x to both f and the other function".

Related

`(a -> b) -> (c -> d)` in Haskell?

This is yet another Haskell-through-category-theory question.
Let's take something simple and well-known as an example. fmap?
So fmap :: (a -> b) -> f a -> f b, omitting the fact that f is actually a Functor. As far as I understand, (a -> b) -> f a -> f b is nothing but a syntax sugar for the (a -> b) -> (f a -> f b); hence conclusion:
(1) fmap is a function producing a function.
Now, Hask contains functions as well, so (a -> b) and, in particular, (f a -> f b) is an object of the Hask (because objects of the Hask are well-defined Haskell types - a-ka mathematical sets - and there indeed exists set of type (a -> b) for each possible a, right?). So, once again:
(2) (a -> b) is an object of the Hask.
Now weird thing happens: fmap, obviously, is a morphism of the Hask, so it is a function, that takes another function and transform it to a yet another function; final function hasn't been applied yet.
Hence, one needs one more Hask's morphism to get from the (f a -> f b) to the f b. For each item i of type a there exists a morphism apply_i :: (f a -> f b) -> f b defined as \f -> f (lift i), where lift i is a way to build an f a with particular i inside.
The other way to see it is GHC-style: (a -> b) -> f a -> f b. On the contrast with what I've written above, (a -> b) -> f a is mapping to the regular object of the Hask. But such a view contradicts fundamental Haskell's axiom - no multivariate functions, but applied (curried) alternatives.
I'd like to ask at this point: is (a -> b) -> f a -> f b suppose to be an (a -> b) -> (f a -> f b) -> f b, sugared for simplicity, or am I missing something really, really important there?
is (a -> b) -> f a -> f b suppose to be an (a -> b) -> (f a -> f b) -> f b, sugared for simplicity
No. I think what you're missing, and it's not really your fault, is that it's only a very special case that the middle arrow in (a -> b) -> (f a -> f b) can be called morphism in the same way as the outer (a -> b) -> (f a -> f b) can. The general case of a Functor class would be (in pseudo-syntax)
class (Category (──>), Category (~>)) => Functor f (──>) (~>) where
fmap :: (a ──> b) -> f a ~> f b
So, it maps morphisms in the category whose arrows are denoted ──> to morphisms in the category ~>, but this morphism-mapping itself is just plainly a function. Your right, in Hask specifically function-arrows are the same sort of arrows as the morphism arrows, but this is mathematically speaking a rather degenerate scenario.
fmap is actually an entire family of morphisms. A morphism in Hask is always from a concrete type to another concrete type. You can think of a function as a morphism if the function has a concrete argument type and a concrete return type. A function of type Int -> Int represents a morphism (an endomorphism, really) from Int to Int in Hask. fmap, however has type Functor f => (a -> b) -> f a -> f b. Not a concrete type in sight! We just have type variables and a quasi-operator => to deal with.
Consider the following set of concrete function types.
Int -> Int
Char -> Int
Int -> Char
Char -> Char
Further, consider the following type constructors
[]
Maybe
[] applied to Int returns a type we could call List-of-Ints, but we usually just call [Int]. (One of the most confusing things about functors when I started out was that we just don't have separate names to refer to the types that various type constructors produce; the output is just named by the expression that evaluates to it.) Maybe Int returns the type we just call, well, Maybe Int.
Now, we can define a bunch of functions like the following
fmap_int_int_list :: (Int -> Int) -> [Int] -> [Int]
fmap_int_char_list :: (Int -> Char) -> [Int] -> [Char]
fmap_char_int_list :: (Char -> Int) -> [Char] -> [Int]
fmap_char_char_list :: (Char -> Char) -> [Char] -> [Char]
fmap_int_int_maybe :: (Int -> Int) -> Maybe Int -> Maybe Int
fmap_int_char_maybe :: (Int -> Char) -> Maybe Int -> Maybe Char
fmap_char_int_maybe:: (Char -> Int) -> Maybe Char -> Maybe Int
fmap_char_char_maybe :: (Char -> Char) -> Maybe Char -> Maybe Char
Each of these is a distinct morphism in Hask, but when we define them in Haskell, there's a lot of repetition.
fmap_int_int_list f xs = map f xs
fmap_int_char_list f xs = map f xs
fmap_char_int_list f xs = map f xs
fmap_char_char_list f xs = map f xs
fmap_int_int_maybe f x = case x of Nothing -> Nothing; Just y -> Just (f y)
fmap_int_char_maybe f x = case x of Nothing -> Nothing; Just y -> Just (f y)
fmap_char_int_maybe f x = case x of Nothing -> Nothing; Just y -> Just (f y)
fmap_char_char_maybe f x = case x of Nothing -> Nothing; Just y -> Just (f y)
The definitions don't differ when the type of f differs, only when the type of x/xs differs. That means we can define the following polymorphic functions
fmap_a_b_list f xs = map f xs
fmap_a_b_maybe f x = case x of Nothing -> Nothing; Just y -> Just (f y)
each of which represents a set of morphisms in Hask.
fmap itself is an umbrella term we use to refer to constructor-specific morphisms referred to by all the polymorphic functions.
With that out of the way, we can better understand fmap :: Functor f => (a -> b) -> f a -> f b.
Given fmap f, we first look at the type of f. We might find out, for example, that f :: Int -> Int, which means fmap f has to return one of fmap_int_int_list or fmap_int_int_maybe, but we're not sure which yet. So instead, it returns a constrained function of type Functor f => (Int -> Int) -> f Int -> f Int. Once that function is applied to a value of type [Int] or Maybe Int, we'll finally have enough information to know which morphism is actually meant.
Now weird thing happens: fmap, obviously, is a morphism of the Hask, so it is a function, that takes another function and transform it to a yet another function; final function hasn't been applied yet.
Hence, one needs one more Hask's morphism to get from the (f a -> f b) to the f b. For each item i of type a there exists a morphism apply_i :: (f a -> f b) -> f b defined as \f -> f (lift i), where lift i is a way to build an f a with particular i inside.
The notion of application in category theory is modelled in the form of CCC's - Cartesian Closed Categories. A category 𝓒 is a CCC if you have a natural bijection 𝓒(X×Y,Z) ≅ 𝓒(X,Y⇒Z).
In particular this implies that there exists a natural transformation 𝜺 (the evaluation), where 𝜺[Y,Z]:(Y⇒Z)×Y→Z, such that for every g:X×Y→Z there exists a 𝝀g:X→(Y⇒Z) such that, g = 𝝀g×id;𝜺[Y,Z]. So when you say,
Hence, one needs one more Hask's morphism to get from the (f a -> f b) to the f b.
The way you go from (f a -> f b) to the f b, or using the notation above, from (f a ⇒ f b) is via 𝜺[f a,f b]:(f a ⇒ f b) × f a → f b.
The other important point to keep in mind is that in Category Theory "elements" are not primitive concepts. Rather an element is an arrow of the form 𝟏→X,where 𝟏 is the terminal object. If you take X=𝟏 you have that 𝓒(Y,Z) ≅ 𝓒(𝟏×Y,Z) ≅ 𝓒(𝟏,Y⇒Z). That is, the morphisms g:Y→Z are in bijection to elements 𝝀g:𝟏→(Y⇒Z).
In Haskell this means functions are precisely the "elements" of arrow types. So in Haskell an application h y would be modelled via the evaluation of 𝝀h:𝟏→(Y⇒Z) on y:𝟏→Y. That is, the evaluation of (𝝀h)×y:𝟏→(Y⇒Z)×Y, which is given by the composition (𝝀h)×y;𝜺[Y,Z]:𝟏→Z.
For the sake of completeness, this answer focuses on a point that was addressed in various comments, but not by the the other answers.
The other way to see it is GHC-style: (a -> b) -> f a -> f b. On the contrast with what I've written above, (a -> b) -> f a is mapping to the regular object of the Hask.
-> in type signatures is right-associative. That being so, (a -> b) -> f a -> f b is really the same as (a -> b) -> (f a -> f b), and seeing (a -> b) -> f a in it would be a syntactic mix-up. It is no different from how...
(++) :: [a] -> [a] -> [a]
... doesn't mean that partially applying (++) will give us an [a] list (rather, it gives us a function that prepends some list).
From this point of view, the category theory questions you raise (for instance, on "need[ing] one more Hask's morphism to get from the (f a -> f b) to the f b") are a separate matter, addressed well by Jorge Adriano's answer.

Pushing a Functor into a tuple

I've simplified the type signature of some code I need, and it looks roughly like this:
Functor f => f (Maybe a, b) -> (Maybe (f a), f b)
Can I, how do I implement such a function? And if so, how? I'm half guessing I need to push the functor down using Traversable, but I'm having trouble putting this all together in my head.
Pushing f one level down can be done by:
fn :: Functor f => f (a, b) -> (f a, f b)
fn v = (fmap fst v, fmap snd v)
(Note that tuples are not traversable if you want both sides.)
The second part is
Functor f => f (Maybe a) -> Maybe (f a)
This type is only inhabited by const Nothing, because the only function you can apply to this value is fmap, getting a value of type f b for some b.
To illustrate why this second part is not possible, consider the fact that IO is an instance of Functor. If you could get a Maybe (IO a) from your value, applying isJust to it would leak one bit of information about the original IO (Maybe a) value without executing it.
We can do, if it is Traversable and not Functor.
fn :: Traversable t => t (Maybe a, b) -> (Maybe (t a), t b)
fn v = (sequenceA $ fmap fst v, fmap snd v)
Is it okay?

Inverse lifting on applicative functors

I'm pretty sure this has a simple solution but it eludes me and I cannot seem to find a straight answer.
Normally, when applying liftA2 assuming the binary function has already been lifted once, the signature looks like this:
liftA2' :: (Applicative f1, Applicative f)
=> (f a -> f b -> f c) -> f1 (f a) -> f1 (f b) -> f1 (f c)
Is it possible to apply the "inverse" of, for example liftA2 such as:
inverseA2 :: (Applicative f, Applicative f1)
=> (f a -> f b -> f c) -> f (f1 a) -> f (f1 b) -> f (f1 c)
As a concrete example, I would like to obtain the function:
f :: ([a] -> [b] -> [c]) -> [Maybe a] -> [Maybe b] -> [Maybe c]
One way would be to resort to "pack" each argument [Maybe a] -> Maybe [a] and "unpack" Maybe [a] -> [Maybe a] the result of applying a normal liftA2. I would like to avoid that since, as you can imagine, packing is destructive (e.g. pack [Just 1, Nothing, Just 2] == Nothing ).
Update: as #user2407038 pointed out, in order for f to apply the given function you necessarily need a function along the lines of [Maybe a] -> [a] which does lose information. So for these two particular functors there is no apparent way to satisfy the additional requirement posed. But for any other two functors f, f1 which have an invertible function forall a . f a -> f1 a the answer accepted fits perfectly as a solution to this question.
I'm sure you've probably figured this out, but I don't think you can do this with the constraints you have. If you are a bit more liberal with your constraints, you'll get something though....
inverseA2 :: (Applicative f, Traversable f, Applicative f1, Traversable f1)
=> (f a -> f b -> f c) -> f (f1 a) -> f (f1 b) -> f (f1 c)
inverseA2 f x y = sequenceA (liftA2 f (sequenceA x) (sequenceA y))
The only reason I'm putting this up is that for your particular example with Maybe and [], these constraints are all satisfied, so doing this is possible for that case. Still not settling at all though.
You could also try experimenting with writing your own instances for Data.Distributive giving you distribute, which is similar to sequenceA...
Edited to include #dfeuer's suggestions.

Why use such a peculiar function type in monads?

New to Haskell, and am trying to figure out this Monad thing. The monadic bind operator -- >>= -- has a very peculiar type signature:
(>>=) :: Monad m => m a -> (a -> m b) -> m b
To simplify, let's substitute Maybe for m:
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b
However, note that the definition could have been written in three different ways:
(>>=) :: Maybe a -> (Maybe a -> Maybe b) -> Maybe b
(>>=) :: Maybe a -> ( a -> Maybe b) -> Maybe b
(>>=) :: Maybe a -> ( a -> b) -> Maybe b
Of the three the one in the centre is the most asymmetric. However, I understand that the first one is kinda meaningless if we want to avoid (what LYAH calls boilerplate code). However, of the next two, I would prefer the last one. For Maybe, this would look like:
When this is defined as:
(>>=) :: Maybe a -> (a -> b) -> Maybe b
instance Monad Maybe where
Nothing >>= f = Nothing
(Just x) >>= f = return $ f x
Here, a -> b is an ordinary function. Also, I don't immediately see anything unsafe, because Nothing catches the exception before the function application, so the a -> b function will not be called unless a Just a is obtained.
So maybe there is something that isn't apparent to me which has caused the (>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b definition to be preferred over the much simpler (>>=) :: Maybe a -> (a -> b) -> Maybe b definition? Is there some inherent problem associated with the (what I think is a) simpler definition?
It's much more symmetric if you think in terms the following derived function (from Control.Monad):
(>=>) :: Monad m => (a -> m b) -> (b -> m c) -> (a -> m c)
(f >=> g) x = f x >>= g
The reason this function is significant is that it obeys three useful equations:
-- Associativity
(f >=> g) >=> h = f >=> (g >=> h)
-- Left identity
return >=> f = f
-- Right identity
f >=> return = f
These are category laws and if you translate them to use (>>=) instead of (>=>), you get the three monad laws:
(m >>= g) >>= h = m >>= \x -> (g x >>= h)
return x >>= f = f x
m >>= return = m
So it's really not (>>=) that is the elegant operator but rather (>=>) is the symmetric operator you are looking for. However, the reason we usually think in terms of (>>=) is because that is what do notation desugars to.
Let us consider one of the common uses of the Maybe monad: handling errors. Say I wanted to divide two numbers safely. I could write this function:
safeDiv :: Int -> Int -> Maybe Int
safeDiv _ 0 = Nothing
safeDiv n d = n `div` d
Then with the standard Maybe monad, I could do something like this:
foo :: Int -> Int -> Maybe Int
foo a b = do
c <- safeDiv 1000 b
d <- safeDiv a c -- These last two lines could be combined.
return d -- I am not doing so for clarity.
Note that at each step, safeDiv can fail, but at both steps, safeDiv takes Ints, not Maybe Ints. If >>= had this signature:
(>>=) :: Maybe a -> (a -> b) -> Maybe b
You could compose functions together, then give it either a Nothing or a Just, and either it would unwrap the Just, go through the whole pipeline, and re-wrap it in Just, or it would just pass the Nothing through essentially untouched. That might be useful, but it's not a monad. For it to be of any use, we have to be able to fail in the middle, and that's what this signature gives us:
(>>=) :: Maybe a -> (a -> Maybe b) -> Maybe b
By the way, something with the signature you devised does exist:
flip fmap :: Maybe a -> (a -> b) -> Maybe b
The more complicated function with a -> Maybe b is the more generic and more useful one and can be used to implement the simple one. That doesn't work the other way around.
You can build a a -> Maybe b function from a function f :: a -> b:
f' :: a -> Maybe b
f' x = Just (f x)
Or, in terms of return (which is Just for Maybe):
f' = return . f
The other way around is not necessarily possible. If you have a function g :: a -> Maybe b and want to use it with the "simple" bind, you would have to convert it into a function a -> b first. But this doesn't usually work, because g might return Nothing where the a -> b function needs to return a b value.
So generally the "simple" bind can be implemented in terms of the "complicated" one, but not the other way around. Additionally, the complicated bind is often useful and not having it would make many things impossible. So by using the more generic bind monads are applicable to more situations.
The problem with the alternative type signature for (>>=) is that it only accidently works for the Maybe monad, if you try it out with another monad (i.e. List monad) you'll see it breaks down at the type of b for the general case. The signature you provided doesn't describe a monadic bind and the monad laws can't don't hold with that definition.
import Prelude hiding (Monad, return)
-- assume monad was defined like this
class Monad m where
(>>=) :: m a -> (a -> b) -> m b
return :: a -> m a
instance Monad Maybe where
Nothing >>= f = Nothing
(Just x) >>= f = return $ f x
instance Monad [] where
m >>= f = concat (map f m)
return x = [x]
Fails with the type error:
Couldn't match type `b' with `[b]'
`b' is a rigid type variable bound by
the type signature for >>= :: [a] -> (a -> b) -> [b]
at monadfail.hs:12:3
Expected type: a -> [b]
Actual type: a -> b
In the first argument of `map', namely `f'
In the first argument of `concat', namely `(map f m)'
In the expression: concat (map f m)
The thing that makes a monad a monad is how 'join' works. Recall that join has the type:
join :: m (m a) -> m a
What 'join' does is "interpret" a monad action that returns a monad action in terms of a monad action. So, you can think of it peeling away a layer of the monad (or better yet, pulling the stuff in the inner layer out into the outer layer). This means that the 'm''s form a "stack", in the sense of a "call stack". Each 'm' represents a context, and 'join' lets us join contexts together, in order.
So, what does this have to do with bind? Recall:
(>>=) :: m a -> (a -> m b) -> m b
And now consider that for f :: a -> m b, and ma :: m a:
fmap f ma :: m (m b)
That is, the result of applying f directly to the a in ma is an (m (m b)). We can apply join to this, to get an m b. In short,
ma >>= f = join (fmap f ma)

How to map over Applicative form?

I want to map over Applicative form.
The type of map-like function would be like below:
mapX :: (Applicative f) => (f a -> f b) -> f [a] -> f [b]
used as:
result :: (Applicative f) => f [b]
result = mapX f xs
where f :: f a -> f b
f = ...
xs :: f[a]
xs = ...
As the background of this post, I try to write fluid simulation program using Applicative style referring to Paul Haduk's "The Haskell School of Expression", and I want to express the simulation with Applicative style as below:
x, v, a :: Sim VArray
x = x0 +: integral (v * dt)
v = v0 +: integral (a * dt)
a = (...calculate acceleration with x v...)
instance Applicative Sim where
...
where Sim type means the process of simulation computation and VArray means Array of Vector (x,y,z). X, v a are the arrays of position, velocity and acceleration, respectively.
Mapping over Applicative form comes when definining a.
I've found one answer to my question.
After all, my question is "How to lift high-order functions (like map
:: (a -> b) -> [a] -> [b]) to the Applicative world?" and the answer
I've found is "To build them using lifted first-order functions."
For example, the "mapX" is defined with lifted first-order functions
(headA, tailA, consA, nullA, condA) as below:
mapX :: (f a -> f b) -> f [a] -> f [b]
mapX f xs0 = condA (nullA xs0) (pure []) (consA (f x) (mapA f xs))
where
x = headA xs0
xs = tailA xs0
headA = liftA head
tailA = liftA tail
consA = liftA2 (:)
nullA = liftA null
condA b t e = liftA3 aux b t e
where aux b t e = if b then t else e
First, I don't think your proposed type signature makes much sense. Given an applicative list f [a] there's no general way to turn that into [f a] -- so there's no need for a function of type f a -> f b. For the sake of sanity, we'll reduce that function to a -> f b (to transform that into the other is trivial, but only if f is a monad).
So now we want:
mapX :: (Applicative f) => (a -> f b) -> f [a] -> f [b]
What immediately comes to mind now is traverse which is a generalization of mapM. Traverse, specialized to lists:
traverse :: (Applicative f) => (a -> f b) -> [a] -> f [b]
Close, but no cigar. Again, we can lift traverse to the required type signature, but this requires a monad constraint: mapX f xs = xs >>= traverse f.
If you don't mind the monad constraint, this is fine (and in fact you can do it more straightforwardly just with mapM). If you need to restrict yourself to applicative, then this should be enough to illustrate why you proposed signature isn't really possible.
Edit: based on further information, here's how I'd start to tackle the underlying problem.
-- your sketch
a = liftA sum $ mapX aux $ liftA2 neighbors (x!i) nbr
where aux :: f Int -> f Vector3
-- the type of "liftA2 neighbors (x!i) nbr" is "f [Int]
-- my interpretation
a = liftA2 aux x v
where
aux :: VArray -> VArray -> VArray
aux xi vi = ...
If you can't write aux like that -- as a pure function from the positions and velocities at one point in time to the accelerations, then you have bigger problems...
Here's an intuitive sketch as to why. The stream applicative functor takes a value and lifts it into a value over time -- a sequence or stream of values. If you have access to a value over time, you can derive properties of it. So velocity can be defined in terms of acceleration, position can be defined in terms of velocity, and soforth. Great! But now you want to define acceleration in terms of position and velocity. Also great! But you should not need, in this instance, to define acceleration in terms of velocity over time. Why, you may ask? Because velocity over time is all acceleration is to begin with. So if you define a in terms of dv, and v in terms of integral(a) then you've got a closed loop, and your equations are not propertly determined -- either there are, even given initial conditions, infinitely many solutions, or there are no solutions at all.
If I'm thinking about this right, you can't do this just with an applicative functor; you'll need a monad. If you have an Applicative—call it f—you have the following three functions available to you:
fmap :: (a -> b) -> f a -> f b
pure :: a -> f a
(<*>) :: f (a -> b) -> f a -> f b
So, given some f :: f a -> f b, what can you do with it? Well, if you have some xs :: [a], then you can map it across: map (f . pure) xs :: [f b]. And if you instead have fxs :: f [a], then you could instead do fmap (map (f . pure)) fxs :: f [f b].1 However, you're stuck at this point. You want some function of type [f b] -> f [b], and possibly a function of type f (f b) -> f b; however, you can't define these on applicative functors (edit: actually, you can define the former; see the edit). Why? Well, if you look at fmap, pure, and <*>, you'll see that you have no way to get rid of (or rearrange) the f type constructor, so once you have [f a], you're stuck in that form.
Luckily, this is what monads are for: computations which can "change shape", so to speak. If you have a monad m, then in addition to the above, you get two extra methods (and return as a synonym for pure):
(>>=) :: m a -> (a -> m b) -> m b
join :: m (m a) -> m a
While join is only defined in Control.Monad, it's just as fundamental as >>=, and can sometimes be clearer to think about. Now we have the ability to define your [m b] -> m [b] function, or your m (m b) -> m b. The latter one is just join; and the former is sequence, from the Prelude. So, with monad m, you can define your mapX as
mapX :: Monad m => (m a -> m b) -> m [a] -> m [b]
mapX f mxs = mxs >>= sequence . map (f . return)
However, this would be an odd way to define it. There are a couple of other useful functions on monads in the prelude: mapM :: Monad m => (a -> m b) -> [a] -> m [b], which is equivalent to mapM f = sequence . map f; and (=<<) :: (a -> m b) -> m a -> m b, which is equivalent to flip (>>=). Using those, I'd probably define mapX as
mapX :: Monad m => (m a -> m b) -> m [a] -> m [b]
mapX f mxs = mapM (f . return) =<< mxs
Edit: Actually, my mistake: as John L kindly pointed out in a comment, Data.Traversable (which is a base package) supplies the function sequenceA :: (Applicative f, Traversable t) => t (f a) => f (t a); and since [] is an instance of Traversable, you can sequence an applicative functor. Nevertheless, your type signature still requires join or =<<, so you're still stuck. I would probably suggest rethinking your design; I think sclv probably has the right idea.
1: Or map (f . pure) <$> fxs, using the <$> synonym for fmap from Control.Applicative.
Here is a session in ghci where I define mapX the way you wanted it.
Prelude>
Prelude> import Control.Applicative
Prelude Control.Applicative> :t pure
pure :: Applicative f => a -> f a
Prelude Control.Applicative> :t (<*>)
(<*>) :: Applicative f => f (a -> b) -> f a -> f b
Prelude Control.Applicative> let mapX fun ma = pure fun <*> ma
Prelude Control.Applicative> :t mapX
mapX :: Applicative f => (a -> b) -> f a -> f b
I must however add that fmap is better to use, since Functor is less expressive than Applicative (that means that using fmap will work more often).
Prelude> :t fmap
fmap :: Functor f => (a -> b) -> f a -> f b
edit:
Oh, you have some other signature for mapX, anyway, you maybe meant the one I suggested (fmap)?

Resources