[Haskell] Re: Monad transformer question

apfelmus at quantentunnel.de apfelmus at quantentunnel.de
Thu Oct 26 08:12:04 EDT 2006


Cyril Schmidt wrote:
> Working on a Monte-Carlo simulation where I have to
> calculate the values of a certain function on the given set of inputs,
> I noticed that some of the input variables change for every iteration,
> while others do not.
> 
> To give a simple example, let's suppose I have a function
> 
> f a1 a2 p = a1*a2 + p
> 
> and I have to get its values for
> [ (a1,a2,p) | a1 <- [0.1,0.2], a2 <- [0.1,0.2], p <- [0..9] ]
> 
> For efficiency, I want to pre-calculate (a1*a2) for each pair of a1 and a2,
> and then calculate f for each p.

This pre-calculation can be put into the function definition:

    f a1 a2 = \p -> a + p
        where a = a1*a2

The expression

    map (f 0.1 0.1) [0..9]

will only involve one multiplication whereas

    map (g 0.1 0.1) [0..9]
    g a1 a2 p = a1*a2 + p

will involve ten multiplications. The reason is that f shares a = a1*a2
across different p.


Of course, the problem now is to make this sharing happen for a list
comprehension of the form

    [f a1 a2 p | a1 <- [0.1,0.2], a2 <- [0.1,0.2], p <- [0..9] ]

The translation into monadic do notation reads

    do
        a1 <- [0.1,0.2]
        a2 <- [0.1,0.2]
        p  <- [0..9]
        return (f a1 a2 p)

which is not what we want as it amounts to generating all parameters and
mapping f over them. Similarly, one loses sharing by pre-generating all
parameters:

    map (\(a1,a2,r) -> f a1 a2 r)
        [(a1,a2,p) | a1 <- [0.1,0.2], a2 <- [0.1,0.2], p <- [0..9] ]

We want to partially apply the function f to the parameters:

    do
        a1 <- [0.1,0.2]
        a2 <- [0.1,0.2]
        let f' = f a1 a2
        p  <- [0..9]
        return (f' p)

or equivalently

    [f' p | a1 <- [0.1,0.2], a2 <- [0.1,0.2],
            let f'=f a1 a2, p <- [0..9] ]


Of course, it would be preferable to separate the process of generating
all parameter triples from applying them. By separating this completely,
we lose sharing. So the generation of parameters should incorporate
information about "pre-applying" parameters. One solution is to appeal
to `ap`:

    ap :: [a -> b] -> [a] -> [b]
    ap fs xs = concatMap (\f -> map f xs) fs

The equivalent definition from Control.Monad is

    ap fs xs = fs >>= \f -> xs >>= \x -> f x

With this, our list comprehension can be rewritten as

    return f `ap` [0.1,0.2] `ap` [0.1,0.2] `ap` [0..9]
==
    ((map f [0.1,0.2]) `ap` [0.1,0.2]) `ap` [0..9]

This way, the parameters are pre-applied and we gain some
compositionality by separating the parameter part:

    (`ap` [0.1,0.2] `ap` [0.1,0.2] `ap` [0..9]) :: [a->a->b->c] -> [c]

In short, information about partial application can be incorporated by
switching from [(a,a,b)] as parameter list to its dual (continuation
passing) form ([(a,a,b) -> c] -> c) and making use of currying ([a->a->b
-> c] -> c).



Concerning list comprehension syntax, I wonder whether there is a
different translation to a Haskell core which already pre-applies
parameters, so that
    [f a1 a2 p | a1 <- [0.1,0.2], a2 <- [0.1,0.2], p <- [0..9] ]
respects sharing and thus involves only 4 multiplications.

For the translation, this would mean that the expression e in [e | Q]
will be lambda-abstracted in its free variables and `ap`-ed to the list
l when something like [e | p<-l, Q] occurs. Of course, one still has to
track the elements of l to allow boolean conditions b to filter things out.


Regards,
apfelmus



More information about the Haskell mailing list