5

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
masayuki takagi
  • 442
  • 3
  • 12
  • Shouldn't you have `f :: f a -> f b` (not `f :: (f a -> f b) -> f [a] -> f [b]`) in your first block of code? Or am I misunderstanding something? – Antal Spector-Zabusky May 17 '11 at 14:02
  • thanks! I was wrong with the type of f. – masayuki takagi May 17 '11 at 14:04
  • Could you sketch out what you would imagine `a` would look like by the way? I'd think you could do it in a way that didn't require `mapX`. – sclv May 17 '11 at 14:27
  • the a is sketched out as below (not accurate): a = liftA sum $ mapX aux $ liftA2 neighbors (x!i) nbr where aux :: f Int -> f Vector3 aux i = ... the type of "liftA2 neighbors (x!i) nbr" is "f [Int]" – masayuki takagi May 17 '11 at 14:46
  • Could you add the code to your post by editing then? And fill in the aux function while you're at it? Thanks. – sclv May 17 '11 at 15:47

3 Answers3

7

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.

sclv
  • 38,665
  • 7
  • 99
  • 204
  • Thanks! But, as comment to Antal S-Z, I once tried to make "newtype Sim a = Sim [a]" type the instance of Monad, however, I could't make it satisfy the Monad laws. Any idea? – masayuki takagi May 17 '11 at 15:06
  • Your sketch is very right in the viewpoint of the result of computation, while what I challenge in this problem is to build a DSL that describes physical simulation on the top of Haskell. I think the "Sim a" type is an abstraction of time evolution of some physical amounts, and I want to write all the code of simulation in fully Applicative, or Monadic, world. So, each time points should be hidden from "Sim a" type users. Ideally, It would be good that lambda calculous could be built in the "Sim a" world. – masayuki takagi May 18 '11 at 03:28
6

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.

Community
  • 1
  • 1
Antal Spector-Zabusky
  • 36,191
  • 7
  • 77
  • 140
  • It sounds great that if I use monad instead of Applicative, i can get what i want! But, I define the Sim type as "newtype Sim a = Sim [a]" and once tried to make it the instance of Monad, however, I could't make it satisfy the Monad laws. Can the Sim type satisfy Monad laws? Or are there any other data structure that satisfy Monad laws for my purpose? – masayuki takagi May 17 '11 at 15:00
  • Additionaly, i've found this post (http://patternsinfp.wordpress.com/2010/12/31/stream-monad/) that shows "The stream monad", but the implementation is very inefficient on computatinal time... – masayuki takagi May 17 '11 at 15:03
  • @masayuki: Sure: lists are monads in ordinary Haskell. If you have normal lists, then `return x = [x]` and `(=<<) = flip concatMap`. If you have infinite lists, then that post is what you want. I also have to agree with sclv's comment—this seems like a strange type signature to want. – Antal Spector-Zabusky May 17 '11 at 15:06
  • Sim is a infinite list, defined "return x = Sim $ repeat x" – masayuki takagi May 17 '11 at 15:11
  • 1
    @Antal S-Z: it is possible to define `Applicative f => [f b] -> f [b]`. It's `Data.Traversible.sequenceA`. Even with `sequenceA` I don't see any way around needing `join` for this problem unfortunately. – John L May 17 '11 at 16:37
  • @John: Thanks! I added that to my answer. – Antal Spector-Zabusky May 17 '11 at 18:13
-1

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)?

Tarrasch
  • 10,199
  • 6
  • 41
  • 57