Use cases for functor/applicative/monad instances for functions - haskell

Haskell has Functor, Applicative and Monad instances defined for functions (specifically the partially applied type (->) a) in the standard library, built around function composition.
Understanding these instances is a nice mind-bender exercise, but my question here is about the practical uses of these instances. I'd be happy to hear about realistic scenarios where folks used these for some practical code.

A common pattern that involves Functor and Applicative instances of functions is for example (+) <$> (*2) <*> (subtract 1). This is particularly useful when you have to feed a series of function with a single value. In this case the above is equivalent to \x -> (x * 2) + (x - 1). While this is very close to LiftA2 you may extend this pattern indefinitely. If you have an f function to take 5 parameters like a -> a -> a -> a -> a -> b you may do like f <$> (+2) <*> (*2) <*> (+1) <*> (subtract 3) <*> (/2) and feed it with a single value. Just like in below case ;
Prelude> (,,,,) <$> (+2) <*> (*2) <*> (+1) <*> (subtract 3) <*> (/2) $ 10
(12.0,20.0,11.0,7.0,5.0)
Edit: Credit for a re-comment of #Will Ness for a comment of mine under another topic, here comes a beautiful usage of applicative over functions;
Prelude> let isAscending = and . (zipWith (<=) <*> drop 1)
Prelude> isAscending [1,2,3,4]
True
Prelude> isAscending [1,2,5,4]
False

Sometimes you want to treat functions of the form a -> m b (where m is an Applicative) as Applicatives themselves. This often happens when writing validators, or parsers.
One way to do this is to use Data.Functor.Compose, which piggybacks on the Applicative instances of (->) a and m to give an Applicative instance for the composition:
import Control.Applicative
import Data.Functor.Compose
type Star m a b = Compose ((->) a) m b
readPrompt :: Star IO String Int
readPrompt = Compose $ \prompt -> do
putStrLn $ prompt ++ ":"
readLn
main :: IO ()
main = do
r <- getCompose (liftA2 (,) readPrompt readPrompt) "write number"
print r
There are other ways, like creating your own newtype, or using ready-made newtypes from base or other libraries.

here an application of the bind function that I used for solving the Diamond Kata. Take a simple function that mirrors its input discarding the last element
mirror :: [a] -> [a]
mirror xs = xs ++ (reverse . init) xs
let's rewrite it a bit
mirror xs = (++) xs ((reverse . init) xs)
mirror xs = flip (++) ((reverse . init) xs) xs
mirror xs = (reverse . init >>= flip (++)) xs
mirror = reverse . init >>= flip (++)
Here is my complete implementation of this Kata: https://github.com/enolive/exercism/blob/master/haskell/diamond/src/Diamond.hs

Related

Using a pure function in a Haskell monad / left-lifting?

Consider the following function:
foo =
[1,2,3] >>=
return . (*2) . (+1)
For better readability and logic, I would like to move my pure functions (*2) and (+1) to the left of the return. I could achieve this like this:
infixr 9 <.
(<.) :: (a -> b) -> (b -> c) -> (a -> c)
(<.) f g = g . f
bar =
[1,2,3] >>=
(+1) <.
(*2) <.
return
However, I don't like the right-associativity of (<.).
Let's introduce a function leftLift:
leftLift :: Monad m => (a -> b) -> a -> m b
leftLift f = return . f
baz =
[1,2,3] >>=
leftLift (+1) >>=
leftLift (*2) >>=
return
I quite like this. Another possibility would be to define a variant of bind:
infixl 1 >>$
(>>$) :: Monad m => m a -> (a -> b) -> m b
(>>$) m f = m >>= return . f
qux =
[1,2,3] >>$
(+1) >>$
(*2) >>=
return
I am not sure whether that is a good idea, since it would not allow me to use do notation should I want that. leftLift I can use with do:
bazDo = do
x <- [1,2,3]
y <- leftLift (+1) x
z <- leftLift (*2) y
return z
I didn't find a function on Hoogle with the signature of leftLift. Does such a function exist, and, if, what is it called? If not, what should I call it? And what would be the most idiomatic way of doing what I am trying to do?
Edit: Here's a version inspired by #dunlop's answer below:
infixl 4 <&>
(<&>) :: Functor f => f a -> (a -> b) -> f b
(<&>) = flip fmap
blah =
[1,2,3] <&>
(+1) <&>
(*2) >>=
return
I should also add that I was after a bind-variant, because I wanted to write my code in point-free style. For do-notation, I guess I don't need to "pretend" that I'm doing anything monadic, so I can use lets.
Every Monad is a Functor (and an Applicative too). Your (>>$) is (flipped) fmap.
GHCi> :t fmap
fmap :: Functor f => (a -> b) -> f a -> f b
GHCi> :t (<$>) -- Infix synonym for 'fmap'
(<$>) -- Infix synonym for 'fmap'
:: Functor f => (a -> b) -> f a -> f b
GHCi> fmap ((*2) . (+1)) [1,2,3]
[4,6,8]
GHCi> (*2) . (+1) <$> ([1,2,3] >>= \x -> [1..x])
[4,4,6,4,6,8]
(By the way, a common name for flipped fmap is (<&>). That is, for instance, what lens calls it.)
If you are using do-notation, there is little reason to use any variant of fmap explicitly for this kind of transformation. Just switch your <- monadic bindings for let-bindings:
bazDo = do
x <- [1,2,3]
let y = (+1) x
z = (*2) y
return z
bazDo = do
x <- [1,2,3]
let y = (+1) x
return ((*2) z)
For better readability...
That's going to be subjective as people disagree on what constitutes readable.
That being said, I agree that sometimes it's easier to understand data transformations when they are written left to right. I think your >>$ is overkill, though. The & operator in Data.Function does the job:
import Data.Function
foo = [1,2,3] & fmap (+1) & fmap (*2)
I like that this says exactly what to start with and exactly what to do at each step from left to right. And unlike >>$, you aren't forced to remain in the monad:
bar = [1,2,3] & fmap (+1) & fmap (*2) & sum & negate
Or you can just assemble your transformation beforehand and map it over your monad:
import Control.Category
f = (+1) >>> (*2)
quuz = fmap f [1,2,3]

Understanding Right Apply

For a List, why does right apply (*>) behave as repeating and appending the second argument n times, where n is the length of the first argument?
ghci> [1,2,3] *> [4,5]
[4,5,4,5,4,5]
The *> operator is defined, by default, as
xs *> ys = id <$ xs <*> ys
which in turn translates, by default, to
const id <$> xs <*> ys
That is, it replaces each element of xs with id to get xs' and then calculates xs' <*> ys. [] is a Monad instance, where (=<<) = concatMap. One of the laws of Applicative lays out the relationship between Applicative and Monad instances:
pure = return
fs <*> as = fs `ap` as = fs >>= \f -> as >>= \a -> f a
For lists, this is
fs <*> as = [f a | f <- fs, a <- as]
So *> for lists is ultimately determined by the Monad instance.
Note that there is another very sensible Applicative instance for lists, which is made available through a newtype in Control.Applicative:
newtype ZipList a = ZipList [a]
instance Applicative ZipList where
pure = repeat
(<*>) = zipWith ($)

Point-free equivalent

I have this function from another SO question,
f :: Ord a => [a] -> [(a, Int)]
f xs = zipWith (\x ys -> (x, length $ filter (< x) ys)) xs (inits xs)
I'm trying to write it in point-free style,
f = flip (zipWith (\x -> (,) x . length . filter (< x))) =<< inits
Is it possible to get rid of that x ?
It's possible, but absolutely not worth the pain. To directly answer your question, LambdaBot on FreeNode reports:
f = flip (zipWith (liftM2 (.) (,) ((length .) . filter . flip (<)))) =<< inits
At this point the function has lost whatever clarity it had, and has become unmaintainable. Here you'd do much better to introduce real names. Remember, just because we can make things point free does not mean we should.
As a general rule: if a variable turns up more than once in an expression, it's probably not a good idea to make it point-free. If you're determined however, the least unreadable way is with the Arrow combinators, because that makes it pretty clear where the data flow is "split". For the xs I'd write
uncurry (zipWith (...)) . (id &&& inits)
For x, the same method yields
zipWith ( curry $ uncurry(,) . (fst &&& length . uncurry filter . first(>)) )
This is even longer than the (->)-monad solution that you've used and lambdabot suggests, but it looks far more organised.
The point of pointfree style is not just omitting names for values, but preferring names for functions. This is significantly easier to do when you use very small definitions. Of course any code is going to become unreadable if you inline everything and don’t use good names.
So let’s start with your original function, and split it into a few smaller definitions.
f xs = zipWith combine xs (inits xs)
combine x xs = (x, countWhere (< x) xs)
countWhere f xs = length (filter f xs)
Now we can easily make these definitions pointfree in a readable way.
f = zipWith combine <*> inits
where combine = compose (,) countLessThan
compose = liftA2 (.)
countLessThan = countWhere . flip (<)
countWhere = length .: filter
(.:) = (.) . (.)
Using names judiciously and preferring composition over application allows us to factor code into small, easily understood definitions. Named parameters are the equivalent of goto for data—powerful, but best used to build reusable higher-level structures that are easier to understand and use correctly. These compositional combinators such as (.) and <*> are to data flow what map, filter, and fold are to control flow.
My stab at it:
f :: Ord a => [a] -> [(a, Int)]
f = zip <*> ((zipWith $ (length .) . filter . (>)) <*> inits)
Here I replaced (<) with (>) to have (length .) . filter . (>) as a function with arguments in the right order: a->[a]->Int. Passing it to zipWith, we get [a]->[[a]]->[Int].
Assuming we have [a] on input, we can see this as f ([[a]]->[Int]) for Applicative ((->) [a]), which can be combined with inits :: f [[a]] with <*> :: f ([[a]]->[Int])->f [[a]]->f [Int]. This gives us [a]->[Int], now need to consume both [a] and [Int] in parallel. zip is already of the right type: [a]->[Int]->[(a,Int)] to apply with <*>.
Not saying I recommend this, but the King of Pointfree is Control.Arrow
import Control.Arrow
-- A special version of zipWith' more amenable to pointfree style
zipWith' :: ((a, b) -> c) -> ([a], [b]) -> [c]
zipWith' = uncurry . zipWith . curry
f :: Ord a => [a] -> [(a, Int)]
f = zipWith' (fst &&& (length <<< uncurry filter <<< first (>))) <<< id &&& inits
Let me reclarify here—I really don't recommend this unless your intention is to somehow generalize the kind of arrow your program is operating in (e.g. into Arrowized FRP perhaps).
With the well-known
(f .: g) x y = f (g x y)
it is a semi-readable
zipWith (curry (fst &&& uncurry (length .: (filter . flip (<))) )) <*> inits
-- \(x,ys) -> (x , length ( (filter . flip (<)) x ys) )
Using Control.Applicative (f <*> g $ x = f x (g x), the S combinator), and Control.Arrow (as others, but a little bit differently).

Clarify role of list monad operator

I came across a Haskell function that tells whether a list is sorted, and I'm having trouble understanding how it works.
The code in question is
f = zipWith (<=) <*> tail
which I understand to be equivalent (in point-ful style) to
f' xs = zipWith (<=) xs (tail xs)
and as an example returns
f [4, 5, 1] == [True,False]
I take it that it has something to do with the list monad and sequential application, but would appreciate if someone could make the meaning more clear to me. What exactly is <*> doing here?
The <*> here isn't acting on the [a] applicative, it's acting in the (->) a applicative instance.
Essentially
instance Applicative ((->) a) where
pure = const -- same as monadic return
f <*> a = \x -> f x (a x)
So it acts like function application, but also wraps the application in a function and gives the argument to both sides.
So expanding your function
zipWith (<=) <*> tail
\x -> zipWith (<=) x (tail x)
\(x:xs) -> zipWith (<=) (x:xs) xs
In general it's correct to view <*> as just function application + some extra goodies. You can almost read it as whitespace!
<*> is actually from (->) a as Applicative Functor. It is a S-combinator which distributes the argument (list xs in your expansion) to two functions (zipWith (<=) and tail) in the manner that you specified in the expansion: (f <*> g) x = f x (g x).
To understand this, you need to check the type (<*>) is applied to. Since both of its arguments are a->b, we are talking about a->b as Applicative Functor - not List.

Trick for "reusing" arguments in Haskell?

From time to time I stumble over the problem that I want to express "please use the last argument twice", e.g. in order to write pointfree style or to avoid a lambda. E.g.
sqr x = x * x
could be written as
sqr = doubleArgs (*) where
doubleArgs f x = f x x
Or consider this slightly more complicated function (taken from this question):
ins x xs = zipWith (\ a b -> a ++ (x:b)) (inits xs) (tails xs)
I could write this code pointfree if there were a function like this:
ins x = dup (zipWith (\ a b -> a ++ (x:b))) inits tails where
dup f f1 f2 x = f (f1 x) (f2 x)
But as I can't find something like doubleArgs or dup in Hoogle, so I guess that I might miss a trick or idiom here.
From Control.Monad:
join :: (Monad m) -> m (m a) -> m a
join m = m >>= id
instance Monad ((->) r) where
return = const
m >>= f = \x -> f (m x) x
Expanding:
join :: (a -> a -> b) -> (a -> b)
join f = f >>= id
= \x -> id (f x) x
= \x -> f x x
So, yeah, Control.Monad.join.
Oh, and for your pointfree example, have you tried using applicative notation (from Control.Applicative):
ins x = zipWith (\a b -> a ++ (x:b)) <$> inits <*> tails
(I also don't know why people are so fond of a ++ (x:b) instead of a ++ [x] ++ b... it's not faster -- the inliner will take care of it -- and the latter is so much more symmetrical! Oh well)
What you call 'doubleArgs' is more often called dup - it is the W combinator (called warbler in To Mock a Mockingbird) - "the elementary duplicator".
What you call 'dup' is actually the 'starling-prime' combinator.
Haskell has a fairly small "combinator basis" see Data.Function, plus some Applicative and Monadic operations add more "standard" combinators by virtue of the function instances for Applicative and Monad (<*> from Applicative is the S - starling combinator for the functional instance, liftA2 & liftM2 are starling-prime). There doesn't seem to be much enthusiasm in the community for expanding Data.Function, so whilst combinators are good fun, pragmatically I've come to prefer long-hand in situations where a combinator is not directly available.
Here is another solution for the second part of my question: Arrows!
import Control.Arrow
ins x = inits &&& tails >>> second (map (x:)) >>> uncurry (zipWith (++))
The &&& ("fanout") distributes an argument to two functions and returns the pair of the results. >>> ("and then") reverses the function application order, which allows to have a chain of operations from left to right. second works only on the second part of a pair. Of course you need an uncurry at the end to feed the pair in a function expecting two arguments.

Resources