pointfree add to list in haskell - haskell

I'm trying to derive function of three args, using simple function chaining.
The function should be of type
addToList :: a -> a -> a -> [a]
and be pointfree analogue of
addToList :: a b c = (a : (b : (c : [])))
So far, I've figured out
addToList = ((.)((.) (flip (:)) . (flip (:))) . (flip (:))) []
But it works in reverse:
Prelude> addToList 4 5 6
[6,5,4]
and looks bulky.
How can one get something nice like
(.) (.) (.) (:) (:) (: [])
that works as follows:
Prelude> addToList 4 5 6
[4,5,6]
?

Let's have a look at a more general version, that uses three functions f, g and h:
func a b c = f a (g b (h c))
In our case, f = (:), g = (:) and h = return, but we can use this for any triple of functions that follow the same scheme:
func a b c = (f a . g b . h) c
For the next step, write the first application of (.) in prefix form, so that it's easier to combine (.) (f a) and the rest later:
func a b = (.) (f a) (g b . h)
= (.) (f a) (g b . h)
= (.) (f a) ((.) (g b) h)
= (.) (f a) (flip (.) h (g b))
= (.) (f a) ((flip (.) h . g) b)
= (.) (f a) . (flip (.) h . g) b
We can now do the same for a:
func a = (.) (f a) . (flip (.) h . g)
= (.) ((.) (f a)) (flip (.) h . g)
= flip (.) (flip (.) h . g) ((.) (f a))
= flip (.) (flip (.) h . g) . (.) (f a)
= flip (.) (flip (.) h . g) . (.) . f a
Since flip (.) x is (.x) we can get rid of flip:
func = flip (.) (flip (.) h . g) . (.) . f
= flip (.) ((.h) . g) . (.) . f
= (.((.h) . g)) . (.) . f
All we have to do now is to insert the definitions of f, g and h:
func = (.((.return) . (:))) . (.) . (:)
I didn't check whether there is a shorter version, but since this is the same result as pointfree.io yields, it should be more or less optimal.
That being said, if you compare
addToList = (.((.return) . (:))) . (.) . (:)
with
addToList a b c = [a, b, c]
which one would you like to read in three months?

Just playing with this a little, maybe it will give you some ideas...
-- | >>> append [4,5] 6
-- [4,5,6]
append :: [a] -> a -> [a]
append = flip (flip (++) . (: []))
-- | >>> f1 4
-- [4]
f1 :: a -> [a]
f1 = (:[])
-- | >>> f2 4 5
-- [4,5]
f2 :: a -> a -> [a]
f2 = append . f1
-- | >>> f3 4 5 6
-- [4,5,6]
f3 :: a -> a -> a -> [a]
f3 = (append .) . f2
-- | >>> f4 4 5 6 7
-- [4,5,6,7]
f4 :: a -> a -> a -> a -> [a]
f4 = ((append .) .) . f3

Related

How to implement uncurry point-free in Haskell without app?

I have been wondering how different standard Haskell functions could be implemented point-free. Currently, I am interested in uncurry and I feel this one is quite non-trivial.
The main problem is that we are unable (or as it seems to me) to group the arguments. If we had uncurry (in fact, uncurry ($) would suffice) in use, the solution would have been quite simple:
Make a tuple (f, (x, y)).
Apply assoc1 :: (a, (b, c)) -> ((a, b), c) to the tuple and get ((f, x), y).
Apply the uncurried ($) to the first element of the pair and get (f x, y).
Apply the uncurried ($) to the pair itself and get f x y.
Without the uncurried ($) we would have to extract both elements of the pair separately. E.g.:
uncurry f pair = f (fst pair) (snd pair)
I do not reckon this to be a smooth way to implement something point-free.
In fact, we have got this uncurried ($) at our behest: Control.Arrow.apply (other useful for the solution combinators could also be imported from Control.Arrow). Therefore:
import Control.Arrow ((>>>), (&&&), first, app)
myUncurry = let myAssoc1 = (fst &&& (fst . snd)) &&& (snd . snd)
in (,) >>> (>>> myAssoc1 >>> first app >>> app)
Yet, this feels a small bit like cheating.
Are there any other approaches towards this problem which do not require anything like app?
join on functions gives you (a -> a -> b) -> a -> b, so:
myUncurry f = join (\x y -> f (fst x) (snd y))
myUncurry f = join (\x -> f (fst x) . snd)
myUncurry f = join ((.snd) . f . fst)
myUncurry f = join ((.fst) ((.snd) . f))
myUncurry f = join ((.fst) ((.) (.snd) f))
myUncurry = join . (.fst) . \f -> (.) (.snd) f
myUncurry = join . (.fst) . ((.snd).)
join . (.fst) . ((.snd).) is very readable indeed
The artless, mechanical solution, by "pushing lambdas inward".
uncurry f (x,y) = f x y
uncurry f p = f (fst p) (snd p)
uncurry f = \p -> f (fst p) (snd p)
uncurry f = (<*>) (\p -> f (fst p)) (\p -> snd p)
uncurry f = (<*>) (f . fst) snd
uncurry = \f -> (<*>) (f . fst) snd
uncurry = flip (\f -> (<*>) (f . fst)) snd
uncurry = flip ((<*>) . (\f -> f . fst)) snd
uncurry = flip ((<*>) . (. fst)) snd
With Lambda Calculus' S combinator, Sabc = (a <*> b) c = a c $ b c,
uncurry f (x,y) = f (fst (x,y)) (snd (x,y))
= (f . fst <*> snd) (x,y)
uncurry f = (<*> snd) (f . fst)
= (<*> snd) . (. fst) $ f
hence,
uncurry :: (a -> b -> c) -> (a, b) -> c
uncurry = (<*> snd) . (. fst)
(edit:)
Still it's much more readable (and somewhat elucidating) with one explicit argument left there, as seen above:
uncurry f = f . fst <*> snd
But then this variant, shown by Jon Purdy in the comments,
uncurry f = liftA2 f fst snd
just might be the clearest.
This is because for functions, the monad and the applicative are equivalent in power,
(k =<< f) x = k (f x) x = flip k x (f x) = (flip k <*> f) x
-- i.e., uncurry f = flip (f . fst) =<< snd
and liftA2 f fst snd means, by definition,
= [ f a b | a <- fst ; b <- snd ]
=
do { a <- fst ;
b <- snd ;
return (f a b)
}
= \x -> let
{ a = fst x ;
b = snd x ;
}
in const (f a b) x
(the first one written with Monad Comprehensions). Thus,
uncurry f x = liftA2 f fst snd x
= let
{ a = fst x ;
b = snd x ;
}
in f a b
=
f (fst x) (snd x)
=
(f . fst <*> snd) x
=
(flip (f . fst) =<< snd) x
=
flip (f . fst) (snd x) x
=
(flip (f . fst) . snd) x x
=
join (flip (f . fst) . snd) x
=
join (flip (f . fst) <$> snd) x
following the well known equivalence, k =<< m = join (fmap k m) (and for functions, (<$>) = fmap = (.)).
So we've found yet another expression here,
uncurry f x = join (flip (f . fst) . snd)
= liftA2 f fst snd
= f . fst <*> snd
= flip (f . fst) =<< snd
The liftA2 one just might be the clearest and the least noisy.

Eta reduction in haskell

I tried for a long time to reduct this function in haskell, I want to express for example:
mySum x y = x + y
mySum x y = (+) x y
mySum x = (+) x
mySum = (+) -- it's Messi's goal!
My function it a little more complex, but I really can't do it, I was looking out here and there, and I know there are some techniques, like modify the right side, and use flip. I tried and I got stuck here:
zipWith' :: (a -> b -> c) -> [a] -> [b] -> [c]
zipWith' f x y = map (uncurry f) (zip x y)
Steps:
zipWith' f x y = map (uncurry f) (zip x y)
zipWith' f x y = flip map (zip x y) (uncurry f)
zipWith' f x y = flip map (zip x y) $ uncurry f
and then I don't know how to continue...
I'm looking for an answer that could explain step by step how to achieve the "Messi's goal", I know is a lot to ask, so I will add as soon as I can a bounty to thank the effort
zipWith' f x y = map (uncurry f) (zip x y)
Rewrite application to composition and eta-reduce:
-- \y -> let g = map (uncurry f); h = zip x in (g . h) y
-- let g = map (uncurry f); h = zip x in g . h
zipWith' f x = map (uncurry f) . zip x
Rewrite infix to prefix:
-- g . h = (.) g h
zipWith' f x = (.) (map (uncurry f)) (zip x)
Rewrite application to composition and eta-reduce:
-- \x -> let g = (.) (map (uncurry f)); h = zip in (g . h) x
-- let g = (.) (map (uncurry f)); h = zip in g . h
zipWith' f = (.) (map (uncurry f)) . zip
Rewrite infix to prefix:
-- g . h = (.) g h
zipWith' f = (.) ((.) (map (uncurry f))) zip
Use flip to move f to the right-hand side:
-- flip f x y = f y x
zipWith' f = flip (.) zip ((.) (map (uncurry f)))
Rewrite application to composition:
-- g (h (i x)) = (g . h . i) x
zipWith' f = flip (.) zip (((.) . map . uncurry) f)
Rewrite application to composition and eta-reduce:
-- \f -> let g = flip (.) zip; h = (.) . map . uncurry in (g . h) f
-- let g = flip (.) zip; h = (.) . map . uncurry in g . h
zipWith' = (flip (.) zip) . ((.) . map . uncurry)
Remove redundant parentheses:
zipWith' = flip (.) zip . (.) . map . uncurry
And simplify to infix if you like:
zipWith' = (. zip) . (.) . map . uncurry
This result isn’t very readable, though.
Often when writing fully point-free code, you want to take advantage of the -> applicative and arrow combinators from Control.Arrow. Rather than trying to write a function like \ f x y -> ..., you can start by grouping the arguments into tuples to make them easier to rearrange and pipe around. In this case I’ll use \ (f, (x, y)) -> ...
\ (f, (x, y)) -> map (uncurry f) (zip x y)
We can eliminate the unpacking of (x, y) by applying uncurry to zip:
\ (f, (x, y)) -> map (uncurry f) (uncurry zip (x, y))
\ (f, xy) -> map (uncurry f) (uncurry zip xy)
Now we have a simple case: applying two functions (uncurry and uncurry zip) to two arguments (f and xy), then combining the results (with map). For this we can use the *** combinator from Control.Arrow, of type:
(***) :: Arrow a => a b c -> a b' c' -> a (b, b') (c, c')
Specialised to functions, that’s:
(***) #(->) :: (b -> c) -> (b' -> c') -> (b, b') -> (c, c')
This just lets us apply a function to each element of a pair. Perfect!
uncurry *** uncurry zip
:: (a -> b -> c, ([x], [y])) -> ((a, b) -> c, [(x, y)])
You can think of uncurry f as combining the elements of a pair using the function f. So here we can combine the results using uncurry map:
uncurry map . (uncurry *** uncurry zip)
:: (a -> b -> c, ([a], [b])) -> [c]
And you can think of curry as turning a function on tuples into a multi-argument function. Here we have two levels of tuples, the outer (f, xy) and the inner (x, y). We can unpack the outer one with curry:
curry $ uncurry map . (uncurry *** uncurry zip)
:: (a -> b -> c) -> ([a], [b]) -> [c]
Now, you can think of fmap f in the -> applicative as “skipping over” the first argument:
fmap #((->) _) :: (a -> b) -> (t -> a) -> t -> b
So we can unpack the second tuple using fmap curry:
fmap curry $ curry $ uncurry map . (uncurry *** uncurry zip)
:: (a -> b -> c) -> [a] -> [b] -> [c]
And we’re done! Or not quite. When writing point-free code, it pays to break things out into many small reusable functions with clearer names, for example:
zipWith' = untuple2 $ combineWith map apply zipped
where
untuple2 = fmap curry . curry
combineWith f g h = uncurry f . (g *** h)
apply = uncurry
zipped = uncurry zip
However, while knowing these techniques is useful, all this is just unproductive trickery that’s easy to get lost in. Most of the time, you should only use point-free style in Haskell when it’s a clear win for readability, and neither of these results is clearer than the simple original version:
zipWith' f x y = map (uncurry f) (zip x y)
Or a partially point-free version:
zipWith' f = map (uncurry f) .: zip
where (.:) = (.) . (.)

($) is to (.) as `fmap` is to?

I have a function funcM :: a -> b -> c -> IO (x, y)
I want to write a function funcM_ :: a-> b-> c-> IO x so:
funcM_ = fst `fmap` funcM -- error
I could add back all the points, but it seems like there should be something I could replace fmap with so that the above will work. Kind of like replacing ($) with (.) would make this work in a pure context.
What is the function I am looking for?
Since you’re composing a one-argument function (fmap) with a three-argument function (funcM), you need three levels of composition:
funcM_ = ((fmap fst .) .) . funcM
This is equivalent to the pointed version by a simple expansion:
funcM_ x = (fmap fst .) . funcM x
funcM_ x y = fmap fst . funcM x y
funcM_ x y z = fmap fst (funcM x y z)
This follows from the type of fmap, really:
fmap :: (Functor f) => (a -> b) -> f a -> f b
You’re just partially applying the arguments to funcM so that you have an f a (here IO (x, y)) which you give to fmap fst to get back an f b (IO x).
As an aside, M_ usually implies returning m ().
Take a look at the following answer: https://stackoverflow.com/a/20279307/783743 It explains how to convert your code into pointfree style. Let's start with a non-pointfree definition of funcM_:
funcM_ a b c = fmap fst (funcM a b c)
-- But `\x -> f (g x)` is `f . g`. Hence:
funcM_ a b = fmap fst . (funcM a b)
-- But `\x -> f (g x)` is `f . g`. Hence:
funcM_ a = (fmap fst .) . (funcM a)
-- But `\x -> f (g x)` is `f . g`. Hence:
funcM_ = ((fmap fst .) .) . funcM
Another way to do this would be to use uncurry and curry as follows:
uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
uncurry3 f (a, b, c) = f a b c
curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
curry3 f a b c = f (a, b, c)
(.::) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e
f .:: g = curry3 (f . (uncurry3 g))
Now you can write funcM_ as follows:
funcM_ = fmap fst .:: funcM
You could also write .:: in pointfree style as follows:
(.::) :: (d -> e) -> (a -> b -> c -> d) -> a -> b -> c -> e
(.::) = (.) . (.) . (.)
Hope that helped.
Add a dot for each argument to funcM
These are all equivalent:
((fmap fst . ) .) . funcM
((.) . (.) . (.)) (fmap fst) funcM
(fmap . fmap . fmap) (fmap fst) funcM
import Data.Functor.Syntax -- from 'functors' package
(.::) (fmap fst) funcM
Note that all I did was change the implicit ($) to (.).
:-)
(.) is the implementation of fmap for the function instance of Functor :
instance Functor ((->) a) b where
fmap f g = f . g
GHCi :t is your friend.

What does (f .) . g mean in Haskell?

I have seen a lot of functions being defined according to the pattern (f .) . g. For example:
countWhere = (length .) . filter
duplicate = (concat .) . replicate
concatMap = (concat .) . map
What does this mean?
The dot operator (i.e. (.)) is the function composition operator. It is defined as follows:
infixr 9 .
(.) :: (b -> c) -> (a -> b) -> a -> c
f . g = \x -> f (g x)
As you can see it takes a function of type b -> c and another function of type a -> b and returns a function of type a -> c (i.e. which applies the first function to the result of the second function).
The function composition operator is very useful. It allows you to pipe the output of one function into the input of another function. For example you could write a tac program in Haskell as follows:
main = interact (\x -> unlines (reverse (lines x)))
Not very readable. Using function composition however you could write it as follows:
main = interact (unlines . reverse . lines)
As you can see function composition is very useful but you can't use it everywhere. For example you can't pipe the output of filter into length using function composition:
countWhere = length . filter -- this is not allowed
The reason this is not allowed is because filter is of type (a -> Bool) -> [a] -> [a]. Comparing it with a -> b we find that a is of type (a -> Bool) and b is of type [a] -> [a]. This results in a type mismatch because Haskell expects length to be of type b -> c (i.e. ([a] -> [a]) -> c). However it's actually of type [a] -> Int.
The solution is pretty simple:
countWhere f = length . filter f
However some people don't like that extra dangling f. They prefer to write countWhere in pointfree style as follows:
countWhere = (length .) . filter
How do they get this? Consider:
countWhere f xs = length (filter f xs)
-- But `f x y` is `(f x) y`. Hence:
countWhere f xs = length ((filter f) xs)
-- But `\x -> f (g x)` is `f . g`. Hence:
countWhere f = length . (filter f)
-- But `f . g` is `(f .) g`. Hence:
countWhere f = (length .) (filter f)
-- But `\x -> f (g x)` is `f . g`. Hence:
countWhere = (length .) . filter
As you can see (f .) . g is simply \x y -> f (g x y). This concept can actually be iterated:
f . g --> \x -> f (g x)
(f .) . g --> \x y -> f (g x y)
((f .) .) . g --> \x y z -> f (g x y z)
(((f .) .) .) . g --> \w x y z -> f (g w x y z)
It's not pretty but it gets the job done. Given two functions you can also write your own function composition operators:
f .: g = (f .) . g
f .:: g = ((f .) .) . g
f .::: g = (((f .) .) .) . g
Using the (.:) operator you could write countWhere as follows instead:
countWhere = length .: filter
Interestingly though you could write (.:) in point free style as well:
f .: g = (f .) . g
-- But `f . g` is `(.) f g`. Hence:
f .: g = (.) (f .) g
-- But `\x -> f x` is `f`. Hence:
(f .:) = (.) (f .)
-- But `(f .)` is `((.) f)`. Hence:
(f .:) = (.) ((.) f)
-- But `\x -> f (g x)` is `f . g`. Hence:
(.:) = (.) . (.)
Similarly we get:
(.::) = (.) . (.) . (.)
(.:::) = (.) . (.) . (.) . (.)
As you can see (.:), (.::) and (.:::) are just powers of (.) (i.e. they are iterated functions of (.)). For numbers in Mathematics:
x ^ 0 = 1
x ^ n = x * x ^ (n - 1)
Similarly for functions in Mathematics:
f .^ 0 = id
f .^ n = f . (f .^ (n - 1))
If f is (.) then:
(.) .^ 1 = (.)
(.) .^ 2 = (.:)
(.) .^ 3 = (.::)
(.) .^ 4 = (.:::)
That brings us close to the end of this article. For a final challenge let's write the following function in pointfree style:
mf a b c = filter a (map b c)
mf a b c = filter a ((map b) c)
mf a b = filter a . (map b)
mf a b = (filter a .) (map b)
mf a = (filter a .) . map
mf a = (. map) (filter a .)
mf a = (. map) ((filter a) .)
mf a = (. map) ((.) (filter a))
mf a = ((. map) . (.)) (filter a)
mf = ((. map) . (.)) . filter
mf = (. map) . (.) . filter
We can further simplify this as follows:
compose f g = (. f) . (.) . g
compose f g = ((. f) . (.)) . g
compose f g = (.) ((. f) . (.)) g
compose f = (.) ((. f) . (.))
compose f = (.) ((. (.)) (. f))
compose f = ((.) . (. (.))) (. f)
compose f = ((.) . (. (.))) (flip (.) f)
compose f = ((.) . (. (.))) ((flip (.)) f)
compose = ((.) . (. (.))) . (flip (.))
Using compose you can now write mf as:
mf = compose map filter
Yes it is a bit ugly but it's also a really awesome mind-boggling concept. You can now write any function of the form \x y z -> f x (g y z) as compose f g and that is very neat.
This is a matter of taste, but I find such style to be unpleasant. First I'll describe what it means, and then I suggest an alternative that I prefer.
You need to know that (f . g) x = f (g x) and (f ?) x = f ? x for any operator ?. From this we can deduce that
countWhere p = ((length .) . filter) p
= (length .) (filter p)
= length . filter p
so
countWhere p xs = length (filter p xs)
I prefer to use a function called .:
(.:) :: (r -> z) -> (a -> b -> r) -> a -> b -> z
(f .: g) x y = f (g x y)
Then countWhere = length .: filter. Personally I find this a lot clearer.
(.: is defined in Data.Composition and probably other places too.)

applicative rewrite (Haskell)

When I don't grasp how an expression in Haskell works I often find it helps to decompose it into a more basic form.
Using the following definitions
sequenceA :: (Applicative f) => [f a] -> f [a]
sequenceA [] = pure []
sequenceA (x:xs) = (:) <$> x <*> sequenceA xs
instance Applicative ((->) r) where
pure x = (\_ -> x)
f <*> g = \x -> f x (g x)
I rewrote sequenceA [(+3),(+2)] 3 as
(\_ -> (:)) <*> (+3) <*> ((\_ -> (:)) <*> (+2) <*> (\_-> [])) $ 3
And then turned it into (please excuse the format; I'm not sure what the convention is for splitting lines)
(\d ->(\c->(\b -> (\a -> (\_ -> (:)) a (+3) a) b (\_ -> (:)) b) c (+2) c) d (\_ -> []) d) 3
This seems right when I work through it by hand, but I can't get GHCi to accept it. What have I done wrong here? My second question is how to convert from this form into functional composition. I've tried substituing dots in various combinations, but GHCi rejects all of them....
Being an idle goodfornothing, I thought I would make a computer do the expansion for me. So into GHCi, I typed
let pu x = "(\\_ -> " ++ x ++ ")"
let f >*< a = "(\\g -> " ++ f ++ " g (" ++ a ++ " g))"
So now I have funny versions of pure and <*> which map strings which look like expressions to string which look like more complicated expressions. I then defined, similarly, the analogue of sequenceA, replacing functions by strings.
let sqa [] = pu "[]" ; sqa (f : fs) = (pu "(:)" >*< f) >*< sqa fs
I was then able to generate the expanded form of the example as follows
putStrLn $ sqa ["(+3)","(+2)"] ++ " 3"
which duly printed
(\g -> (\g -> (\_ -> (:)) g ((+3) g)) g ((\g -> (\g -> (\_ -> (:)) g ((+2) g)) g ((\_ -> []) g)) g)) 3
This last, copied to the prompt, yielded
[6,5]
Comparing the output from my "metaprogram" with the attempt in the question shows a shorter initial prefix of lambdas, arising from a shallower nesting of <*> operations. Remember, it's
(pure (:) <*> (+3)) <*> ((pure (:) <*> (+2)) <*> pure [])
so the outer (:) should be only three lambdas deep. I suspect the proposed expansion may correspond to a differently bracketed version of the above, perhaps
pure (:) <*> (+3) <*> pure (:) <*> (+2) <*> pure []
Indeed, when I evaluate
putStrLn $ pu "(:)" >*< "(+3)" >*< pu "(:)" >*< "(+2)" >*< pu "[]" ++ " 3 "
I get
(\g -> (\g -> (\g -> (\g -> (\_ -> (:)) g ((+3) g)) g ((\_ -> (:)) g)) g ((+2) g)) g ((\_ -> []) g)) 3
which looks like it matches the (updated)
(\d -> (\c -> (\b -> (\a -> (\_ -> (:)) a ((+3) a)) b ((\_ -> (:)) b)) c ((+2) c)) d ((\_ -> []) d)) 3
I hope this machine-assisted investigation helps to clarify what's going on.
You rewrote (\_ -> (:)) <*> (+3) as \a -> (\_ -> (:)) a (+3) a, which is rewriting f <*> g as f x g x instead of f x (g x). I think you made that mistake for every <*>.
It might be easier to use combinators, e.g. _S and _K, symbolically, and not their definitions as lambda-expressions,
_S f g x = f x (g x)
_K x y = x
With functions, fmap is (.) and <*> is _S, as others already mentioned. So,
sequenceA [(+3),(+2)] 3 ==
( ((:) <$> (+3)) <*> sequenceA [(+2)] ) 3 ==
_S ((:).(+3)) ( ((:) <$> (+2)) <*> pure [] ) 3 ==
_S ((:).(+3)) ( _S ((:).(+2)) (_K []) ) 3 ==
((:).(+3)) 3 ( _S ((:).(+2)) (_K []) 3 ) ==
((:).(+3)) 3 ( ((:).(+2)) 3 (_K [] 3) ) ==
(6:) ( (5:) [] ) ==
[6,5]
So it might be easier to decompose expressions down to basic functions and combinators and stop there (i.e. not decomposing them to their lambda expressions), using their "re-write rules" in manipulating the expression to find its more comprehensible form.
If you wanted to, you could now write down for yourself a more abstract, informal re-write rule for sequenceA as
sequenceA [f,g,..., z] ==
_S ((:).f) . _S ((:).g) . _S ..... . _S ((:).z) . _K []
and so
sequenceA [f,g,..., z] a ==
((:).f) a $ ((:).g) a $ ..... $ ((:).z) a $ _K [] a ==
(f a:) $ (g a:) $ ..... $ (z a:) $ [] ==
[f a, g a, ..., z a]
and hence
sequenceA fs a == map ($ a) fs == flip (map . flip ($)) fs a
to wit,
Prelude Control.Applicative> flip (map . flip ($)) [(+3),(+2)] 3
[6,5]

Resources