How would I write this function in point-free style? - haskell

I'm just looking to make general improvements to my Haskell code, and was wondering if the following function could be made point-free? Mostly for curiosity's sake.
Given two functions which we'd like to use in our filter:
isZero = (==0)
isOne = (==1)
How would we go about utilising those two functions in our contrived example, but making it point-free?
filter (\x -> isZero x || isOne x) [0..100]

There's a online-service for converting Haskell code to point-free.
It suggests: filter (liftM2 (||) isZero isOne) [0..100]
liftA2 (||) isZero isOne or (||) <$> isZero <*> isOne is also possible
(||) <$> isZero has type a0 -> Bool -> Bool and it's the composition of (||) and isZero. This composition takes a number (for isZero) and a boolean (as another argument for (||))
So, it's the same as \x y -> (||) (isZero x) y
The function type is an instance of Applicative Functor and we can look at its implementation:
instance Applicative ((->) r) where
pure x = (\_ -> x)
f <*> g = \x -> f x (g x)
So, (||) <$> isZero <*> isOne is the same as \x -> ((||) <$> isZero) x (isOne x) and the same as \x -> (||) (isZero x) (isOne x)
Thus, if there's z x = y (f x) (g x), it can be transformed into point free: z = y <$> f <*> g

An alternate point-free form would be to use the a -> Any monoid:
λ import Data.Monoid (Any(..))
λ :t getAny . (Any . isZero <> Any . isOne)
getAny . (Any . isZero <> Any . isOne)
:: (Num a, Eq a) => a -> Bool
λ filter (getAny . (Any . isZero <> Any . isOne)) [0..100]
[0,1]
It's a bit longer than the Applicative solution, but I think it's a little easier to follow when you have more conditions to combine. Compare
getAny . (Any . isZero <> Any . isOne <> Any . isSquare <> Any . isPrime)
or
getAny . foldMap (Any .) [isZero, isOne, isSquare, isPrime]
and
liftA2 (||) (liftA2 (||) (liftA2 (||) isZero isOne) isSquare) isPrime
or
liftA2 (||) isZero $ liftA2 (||) isOne $ liftA2 (||) isSquare isPrime
Though to be honest, if I had lots of these to do, I'd be tempted to define <||> = liftA2 (||) and do
isZero <||> isOne <||> isSquare <||> isPrime

Related

How to combine two composed applicative functors?

I have two composed applicative functors Maybe [Integer] and want to combine them with <$>/<*> but I am stuck with applying the applicative operation. The following does not typecheck:
(<*>) (<*>) ((<$>) ((+) <$>) $ Just [1,2,3]) $ Just [4,5,6]
Expected result:
Just [5,6,7,6,7,8,7,8,9]
The functor part works, i.e. the intermediate value passed to <*> as the first argument is Just [Integer -> Integer]. I am used to S-expressions so I have a hard time with the Haskell syntax. I know of Compose but I am interested in the mere composition wihtout abstraction.
As Li-yao Xia said, using liftA2 makes it a lot less confusing.
But if you still what to see what it becomes in terms of the underlaying operations, we can expand the definition of liftA2:
liftA2 :: (a -> b -> c) -> f a -> f b -> f c
liftA2 f x y = f <$> x <*> y
so the solution becomes
(liftA2 . liftA2) (+) (Just [1,2,3]) (Just [4,5,6])
= liftA2 (liftA2 (+)) (Just [1,2,3]) (Just [4,5,6])
= (\f x y -> f <$> x <*> y) ((\f x y -> f <$> x <*> y) (+)) (Just [1,2,3]) (Just [4,5,6])
= ((\f x y -> f <$> x <*> y) (+)) <$> Just [1,2,3] <*> Just [4,5,6]
= (\x y -> (+) <$> x <*> y) <$> Just [1,2,3] <*> Just [4,5,6]
Now, this is not in point free style like your example above, and I really don't think it's helpful to convert it into point free, but here's the output from http://pointfree.io:
((<*>) . ((+) <$>)) <$> Just [1, 2, 3] <*> Just [4, 5, 6]
we can see that this is the same by eta-expanding:
(<*>) . ((+) <$>)
= \x y -> ((<*>) . ((+) <$>)) x y
= \x y -> ((<*>) $ ((+) <$>) x) y
= \x y -> ((<*>) ((+) <$> x)) y
= \x y -> (<*>) ((+) <$> x) y
= \x y -> ((+) <$> x) <*> y
= \x y -> (+) <$> x <*> y
liftA2 might be less confusing for this than (<*>).
(+) :: Int -> Int -> Int
liftA2 (+) :: [Int] -> [Int] -> [Int]
liftA2 (liftA2 (+)) :: Maybe [Int] -> Maybe [Int] -> Maybe [Int]
liftA2 (liftA2 (+)) (Just [1,2,3]) (Just [4,5,6])
The composition of two Applicatives is always an Applicative (unlike the case for Monad).
We can use this to our advantage here with the Compose newtype from Data.Functor.Compose:
newtype Compose f g a = Compose { getCompose :: f (g a) }
It requires a bit of wrapping, but this kind of solution could be useful under the right circumstances:
example :: Maybe [Int]
example =
getCompose ((+) <$> Compose (Just [1,2,3]) <*> Compose (Just [4,5,6]))
One other way could be to use the ListT transformer. While it works just fine in this case, for some reason it's a depreciated transformer, marked in red with "Deprecated: This transformer is invalid on most monads".
import Control.Monad.Trans.List
doit :: (Int-> Int -> Int) -> Maybe [Int] -> Maybe [Int] -> Maybe [Int]
doit f mt1 mt2 = runListT $ f <$> (ListT mt1) <*> (ListT mt2)
λ> doit (+) (Just [1,2,3]) (Just [4,5,6])
Just [5,6,7,6,7,8,7,8,9]

Is there a point-free way to convert a conditional check into a Maybe type of the input?

I am just working through some simple exercises in haskell and was wondering if there was a point-free way of converting an if-then-else statement into a Maybe type: Nothing being returned if the condition is false, and Just the input if the condition is true.
In short, given some:
maybeIf :: (a -> Bool) -> a -> Maybe a
maybeIf cond a = if cond a then Just a else Nothing
Is there an implementation that is point-free with respect to a? I've also been looking at a more concrete version, a -> Maybe a, and feel like there may be an answer somewhere in Control.Arrow. However, since Maybe is a data type and if-else statements control data flow, I'm unsure if there is a clean way of doing it.
The main thing getting in the way of making that pointfree is the if/then/else. You can define an if' combinator, or you can use this generalized version that I define and use often:
ensure p x = x <$ guard (p x)
Standard tools give successive point-free versions as
ensure p = ap (<$) (guard . p)
ensure = ap (<$) . (guard .)
though I really don't think either are better than the pointful version.
You can import find from Data.Foldable and then it's quite simply:
import Data.Foldable(find)
maybeIf cond = find cond . Just
The function find is not complicated so you could quite easily define it yourself less generically, in terms of Maybe, but it isn't actually so different from your own implementation of maybeIf so you might not gain much, depending on why you wanted to do it.
If we choose a Church-encoding for Booleans…
truth :: Bool -> a -> a -> a
truth True t f = t
truth False t f = f
Then we can write a point-free maybeIf in Applicative-style.
maybeIf :: (a -> Bool) -> a -> Maybe a
maybeIf = liftA3 truth <*> pure Just <*> pure (pure Nothing)
Some intuitions…
f <$> m₁ <*> … <*> mₙ = \x -> f (m₁ x) … (mₙ x)
liftAₙ f <$> m₁ <*> … <*> mₙ = \x -> f <$> m₁ x <*> … <*> mₙ x
Here is a rendering in PNG format of the above "intuitions", in case your installed fonts do not support the needed unicode characters.
So therefore:
liftA3 truth <*> pure Just <*> pure (pure Nothing)
= liftA3 truth <$> id <*> pure Just <*> pure (pure Nothing)
= \p -> truth <$> id p <*> (pure Just) p <*> (pure (pure Nothing)) p
= \p -> truth <$> p <*> Just <*> pure Nothing
= \p -> \a -> truth (p a) (Just a) ((pure Nothing) a)
= \p -> \a -> truth (p a) (Just a) Nothing
Following dfeuer's lead (and using Daniel Wagner's new name for this function),
import Data.Bool (bool)
-- F T
-- bool :: a -> a -> Bool -> a
ensure :: (a -> Bool) -> a -> Maybe a
ensure p x = bool (const Nothing) Just (p x) x
ensure p = join (bool (const Nothing) Just . p)
= bool (const Nothing) Just =<< p
ensure = (bool (const Nothing) Just =<<)
join is a monadic function, join :: Monad m => m (m a) -> m a, but for functions it is simply
join k x = k x x
(k =<< f) x = k (f x) x
join is accepted as a replacement for W combinator in point-free code.
You only wanted it point-free with respect to the value argument, but it's easy to transform the equation with join further (readability of the result is another issue altogether), as
= join ((bool (const Nothing) Just .) p)
= (join . (bool (const Nothing) Just .)) p
Indeed,
#> (join . (bool (const Nothing) Just .)) even 3
Nothing
#> (bool (const Nothing) Just =<<) even 4
Just 4
But I'd much rather see \p x -> listToMaybe [x | p x] in an actual code.
Or just \p x -> [x | p x], with Monad Comprehensions. Which is the same as Daniel Wagner's x <$ guard (p x), only with different syntax.
This function is defined in Control.Monad.Plus and is called partial

Is it possible to implement foldl/foldr using unsided fold?

By unsided fold, I mean a hypothetic primitive fold operation for associative operators that, does not guarantee any ordering. That is, (fold + 0 [a b c d]) could be (+ (+ a b) (+ c d)) or (+ (+ (+ a b) c) d).
Given that this operation is fusionable, highly paralelizable and universal, I've thought in including it together with map and concat as the only list primitives for my non-recursive minimalist language. I've managed to implement most list functions with it, but not the sided folds foldl/foldrthemselves. Is it possible?
If you have fold and map that is universal. The slogan here is foldr is made of monoids In fact, the standard haskell typeclass Foldable implements foldr and foldl in just this way
The trick is that the set of endomorphisms over a set forms a monoid under function composition with the identity function as the identity.
Note though that foldr and foldl are inherently sequential. So, this trick has to give up any parallelism you have in your implementation of fold and map. Essentially, the encoding of foldr into foldMap is the encoding of a delayed sequential computation into a potentially unordered one. That is why I encourage the use of foldMap over foldr when possible--it supports implicit parallism when that is possible, but is equivalent in expressive power.
EDIT: Putting everything in one place
We define the set of endo morphisms over a
newtype Endo a = Endo { appEndo :: a -> a }
instance Monoid (Endo a) where
mempty = Endo id
Endo f `mappend` Endo g = Endo (f . g)
then in foldable, we see the definition for foldr
foldr f z t = appEndo (foldMap (Endo . f) t) z
this uses foldMap which has type Monoid m => (a -> m) -> t a -> m (where t is the collection we are folding over, we can pretend it is a list from now on giving Monoid m => (a -> m) -> [a] -> m and is equivalent to
foldMap f ls = fold (map f ls)
where fold is the monoid fold. If you have a unordered fold called fold' :: (a -> a -> a) -> a -> [a] -> a then that is just
fold = fold' mappend mempty
so
foldr f z t = appEndo (foldMap (Endo . f) t) z
= appEndo (fold (map (Endo . f) t)) z
= appEndo (fold' mappend mempty (map (Endo . f) t)) z
= appEndo (fold' (\(Endo f) (Endo g) -> Endo (f . g) (Endo id) (map (Endo . f) t)) z
which can be further simplified to
foldr f z t = (fold' (.) id (map f t)) z
and dropping the unecessary parens
foldr f z t = fold' (.) id (map f t) z
which is what Daniel Wagner gave as his answer. You can implement foldl in a similar way, or via foldr.
foldr f z xs = fold (.) id (map f xs) z
For example, in ghci:
*Dmwit Debug.SimpleReflect> let foldr' f z xs = foldb (.) id (map f xs) z
*Dmwit Debug.SimpleReflect> foldr' f z [w,x,y]
f w (f x (f y z))
*Dmwit Debug.SimpleReflect> foldr f z [w,x,y]
f w (f x (f y z))

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]

Why does the pointfree version of this function look like this?

I've been playing around with Haskell a fair bit, including practising writing functions in point-free form. Here is an example function:
dotProduct :: (Num a) => [a] -> [a] -> a
dotProduct xs ys = sum (zipWith (*) xs ys)
I would like to write this function in point-free form. Here is an example I found elsewhere:
dotProduct = (sum .) . zipWith (*)
However, I don't understand why the point-free form looks like (sum .) . zipWith (*) instead of sum . zipWith (*). Why is sum in brackets and have 2 composition operators?
dotProduct xs ys = sum (zipWith (*) xs ys) -- # definition
dotProduct xs = \ys -> sum (zipWith (*) xs ys) -- # f x = g <=> f = \x -> g
= \ys -> (sum . (zipWith (*) xs)) ys -- # f (g x) == (f . g) x
= sum . (zipWith (*) xs) -- # \x -> f x == f
= sum . zipWith (*) xs -- # Precedence rule
dotProduct = \xs -> sum . zipWith (*) xs -- # f x = g <=> f = \x -> g
= \xs -> (sum .) (zipWith (*) xs) -- # f * g == (f *) g
= \xs -> ((sum .) . zipWith (*)) xs -- # f (g x) == (f . g) x
= (sum .) . zipWith (*) -- # \x -> f x == f
The (sum .) is a section. It is defined as
(sum .) f = sum . f
Any binary operators can be written like this, e.g. map (7 -) [1,2,3] == [7-1, 7-2, 7-3].
KennyTM's answer is excellent, but still I'd like to offer another perspective:
dotProduct = (.) (.) (.) sum (zipWith (*))
(.) f g applies f on the result of g given one argument
(.) (.) (.) f g applies f on the result of g given two arguments
(.) (.) ((.) (.) (.)) f g applies f on the result of g given three arguments
...
Can do (.~) = (.) (.) (.), (.~~) = (.) (.) (.~), (.~~~) = (.) (.) (.~~) and now let foo a b c d = [1..5]; (.~~~) sum foo 0 0 0 0 results in 15.
But I wouldn't do it. It will probably make code unreadable. Just be point-full.
Conal's TypeCompose provides a synonym for (.) called result. Perhaps this name is more helpful for understanding what's going on.
fmap also works instead of (.), if importing the relevant instances (import Control.Applicative would do it) but its type is more general and thus perhaps more confusing.
Conal's concept of "fusion" (not to be confused with other usages of "fusion") is kind of related and imho offers a nice way to compose functions. More details in this long Google Tech Talk that Conal gave

Resources