Wrap a partial pattern matching into a Maybe - haskell

Is there any way to wrap a partial pattern-match into a Maybe?
I wish to write some code kind of like this:
fromMaybe defaultValue $ do
[a, b] <- mkList :: [Int]
[x] <- mkList' a b :: [Int]
return $ x
where this expression's value would be defaultValue if mkList evaluates to a list with length /= 2, or if mkList' a b evaluates to a list of length /= 1. Otherwise the expression evaluates to the only element returned by mkList' a b.
I figured the Maybe monad would be great to achieve this. But how can I turn a failed pattern-matching into a Nothing, and a successful match into a Just?
Is it possible to achieve this in Haskell?

Your code almost works as is. You only need to add some pure and change the type:
import Data.Maybe
f defaultValue mkList mkList' = fromMaybe defaultValue $ do
[a, b] <- pure mkList :: Maybe [Int]
[x] <- pure (mkList' a b) :: Maybe [Int]
return x
You don't even need those :: Maybe [Int] annotations.
In GHCi you can see it has the expected behavior:
ghci> f 0 [1,2,3] (\x y -> [x,y])
0
ghci> f 0 [1,2] (\x y -> [x])
1
ghci> f 0 [1,2] (\x y -> [y])
2
ghci> f 0 [1,2] (\x y -> [x,y])
0
The mechanism behind it is explained by Daniel Wagner in the comments:
do
[a, b] <- <X>
<Y>
is syntax sugar for
let ok [a, b] = do <Y>
ok _ = fail "..."
in <X> >>= ok
(And for Maybe, the definition of fail is fail _ = Nothing.)
See the Report.
Note that this only works inside do blocks where the monad is an instance of MonadFail.

Related

How to check that all list items are odd and bigger than 10?

I need to check if a list only contains odd numbers, bigger than 10.
This is what I did.
f :: [Int] -> Bool
f xs= [x |x<-xs, x >10, odd x]
Why does this not work?
When you write [x |x<-xs, x >10, odd x] you're making up a list of Ints, a [Int], not a Boolean. For instance you can verify that
[x | x <- [1..20], x > 10, odd x] is the list [11,13,15,17,19]. So it does contain the numbers that you want, but how do you tell that those are all of the numebrers in xs?
You could certainly equate that list to xs itself, and that would work:
f xs = xs == [x |x<-xs, x >10, odd x]
This way the == ensures that when you only take odd numbers greater than 10 from xs you get back exactly xs, meaning that all numbers satisfy the predicate.
Maybe this is the mistake you were looking for.
I'm not sure whether this solution traverses xs twice (once to extract the entries satisfying the predicate, and once to check for equality) or not. It looks very simple, so I can't help but think that the list is traversed only once.
Anyway, another strategy is to stick to your request: you want all numbers x from the list xs for which odd x and x > 10 are both True:
f :: [Int] -> Bool
f xs = all (\x -> odd x && x > 10) xs
By noticing that both sides have a trailing xs, you can reduce the definition:
f :: [Int] -> Bool
f = all (\x -> odd x && x > 10)
And that lambda, if you want, could be define more succintly as (odd & (> 10)), thus getting
f :: [Int] -> Bool
f = all (odd & (> 10))
provided you import Control.Monad (liftM2) and define
(&) :: (a -> Bool) -> (a -> Bool) -> (a -> Bool)
(&) = liftM2 (&&)
Your type signature mentions that the function returns a boolean value, but your proposed body returns a list of numbers. Haskell has no automatic conversions such as Lisp.
Should you wish to stick to pedestrian code, you could get the sublist of offending numbers, and just check that the sublist is empty.
f :: [Int] -> Bool
f xs = let offenders = [x | x <- xs, x <= 10 || even x]
in (null offenders)
Note that due to the laziness of the language runtime, evaluation of offenders stops as soon as we find a first element.
Should you want something a bit more haskell-ish, you can use the sequence :: (Traversable t, Monad m) => t (m a) -> m (t a) polymorphic library function to turn a list of predicates into a single function returning a list of boolean values, then pass that list to and. That checks one number.
Then use all to apply these checks to all numbers in the input list. Like this:
f2 :: [Int] -> Bool
f2 = all (and . sequence [(>10), odd])
Explanation:
To understand how exactly the sequence function gets specialized by the compiler, one can use the TypeApplications language extension.
With the extension enabled, given 3 type arguments, expression sequence #tt #tm #ta maps tt to the Traversable instance, tm to the Monad instance and ta to argument type a.
$ ghci
GHCi, version 8.8.4: https://www.haskell.org/ghc/ :? for help
λ>
λ> :type sequence
sequence :: (Traversable t, Monad m) => t (m a) -> m (t a)
λ>
λ> :set -XTypeApplications
λ>
We start with the easiest part, mapping tt to lists and ta to Bool, leaving tm undefined as an underscore _:
λ>
λ> :type sequence #[] #_ #Bool
sequence #[] #_ #Bool :: Monad _ => [_ Bool] -> _ [Bool]
λ>
Now, if we assign tm to “function of an Int variable”, we have the whole picture:
λ>
λ> :type sequence #[] #((->)Int) #Bool
sequence #[] #((->)Int) #Bool :: [Int -> Bool] -> Int -> [Bool]
λ>
The last type can be interpreted as [Int -> Bool] -> (Int -> [Bool]), that is, function sequence transforming a list of predicates into a single function returning a list of boolean values.

What does "<-" mean? [duplicate]

This question already has answers here:
Replace a 3 parameter list-comprehension by using map, concat
(3 answers)
Closed 3 years ago.
In this tutorial http://learnyouahaskell.com/starting-out the author writes this piece of code.
boomBangs xs = [ if x < 10 then "BOOM!" else "BANG!" | x <- xs, odd x]
And then later executes it like this
boomBangs[7..13]
And my question is, what does the "<-" operator do? To me this seems like it would cause recursive behavior, since I am referencing what looks to me like a function inside a function, or perhaps defining how to create a list comprehension.
Searching around I found this explanation by chi on a different question:
"x <- action runs the IO action, gets its result, and binds it to x"
Is the "<-" in the question linked above different to the "<-" used in the code I copied above? Does xs run inside xs? I'd be grateful if someone could explain to me what's going on here.
Your list comprehension is in essence just syntactical sugar for:
import Control.Monad(guard)
boomBangs :: Integral i => [i] -> [String]
boomBangs xs = do
x <- xs
guard (odd x)
return (if x < 10 then "BOOM!" else "BANG!")
This is thus a do expression [Haskell report], and as the report says, it is syntactical sugar. It is syntactical sugar for:
boomBangs xs = xs >>= \x -> (guard (odd x) >> return (if x < 10 then "BOOM!" else "BANG!"))
For a list the Monad instance is defined as:
instance Monad [] where
(>>=) = flip concatMap
return x = [x]
Furthermore the guard is defined as:
guard :: Monad m => Bool -> m ()
guard True = pure ()
guard False = empty
and the default implementation of (>>) is:
(>>) :: Monad m => m a -> m b -> m b
(>>) u v = u >>= \_ -> v
So the boomBangs is basically implemented as:
boomBangs xs = concatMap (\x -> (guard (odd x) >>= \_ -> [if x < 10 then "BOOM!" else "BANG!"])) xs
= concatMap (\x -> concatMap (\_ -> [if x < 10 then "BOOM!" else "BANG!"]) guard (odd x)) xs
Since for a list, the guard can be specialized to:
-- guard for the Monad []
guard :: Bool -> [()]
guard True = [()]
guard False = []
It thus means that if the guard gets a True, it returns a singleton list, and for False an empty list. This thus means that given the guard holds, the concatMap (\_ -> [if x < 10 then "BOOM!" else "BANG!"]) will return the content in the [if x < 10 then "BOOM!" else "BANG!"], if the guard fails, it will return an empty list. The guard acts thus as some sort of filter.
So now what is the x <-. If we look at how the do-expressions are desugared, an x <- foo, corresponds to the foo >>= \x -> ....
For list comprehensions, x <- ... acts as some sort of "enumerator": it will enumerate over all elements in the list, and x will each time obtain one of the elements in the list to do further processing.

How to filter a list by another list in Haskell?

Suppose I have two lists A and B of the same length. I want to keep elements in A which are greater than corresponding elements in B. Let A=[1,5,8], B=[2,4,9], the result should be [5] because 1<2, 5>4, 8<9.
I come up with a solution. Let C=zip A B, then filter C, finally get result by taking fst of each element in C. It's not so elegant. Is there a simpler way?
Code:
map fst (filter (\ x-> (fst x) > (snd x)) (zip a b))
Your described solution looks fine to me.
An alternative which is not necessarily better:
import Data.Maybe
import Control.Monad
catMaybes $ zipWith (\a b -> guard (a>b) >> return a) list1 list2
According to the desugaring of monad comprehensions this should also work
{-# LANGUAGE MonadComprehensions #-}
[ a | ( a <- list1 | b <- list2 ), a > b ]
... but in practice it does not. It is a pity because I find it quite elegant.
I wonder whether I got it wrong or it is a GHC bug.
I was working on something similar and as a newbie this is the best I came up with:
filterGreaterThan xs ys = do (x,y) <- zip xs ys
guard (x > y)
return x
This solution is easier to reason about than the others. The do notation really shines here.
I'm not sure how your code looks but the following function look quite elegant to me:
greater :: Ord a => [a] -> [a] -> [a]
greater xs = map fst . filter ((>) <$> fst <*> snd) . zip xs
example :: [Int]
example = greater [1,5,8] [2,4,9] -- result is [5]
This pattern is well known in the Lisp community as the decorate-process-undecorate pattern.
A recursive approach, not so elegant as (any) of the other approaches, this relies on no explicit zipping and we get the result in one pass,
greater :: Ord a => [a] -> [a] -> [a]
greater [] [] = []
greater (x:xs) (y:ys)
| x > y = x : greater xs ys
| otherwise = greater xs ys
If you want to generalize this idea nicely, I would recommend looking to mapMaybe:
mapMaybe
:: (a -> Maybe b)
-> [a] -> [b]
Applying that idea to zipWith yields
zipWithMaybe
:: (a -> b -> Maybe c)
-> [a] -> [b] -> [c]
zipWithMaybe f xs ys =
[c | Just c <- zipWith f xs ys]
Now you can write your function
keepGreater :: Ord a => [a] -> [a] -> [a]
keepGreater = zipWithMaybe $
\x y -> x <$ guard (x > y)
Is it really worth the trouble? For lists, probably not. But something like this turns out to be useful in the context of merges for Data.Map.
Pretty similar to #chi's solution with Lists concant:
concat $ zipWith (\a b -> last $ []:[[a] | a > b]) as bs

What does $ mean/do in Haskell?

When you are writing slightly more complex functions I notice that $ is used a lot but I don't have a clue what it does?
$ is infix "application". It's defined as
($) :: (a -> b) -> (a -> b)
f $ x = f x
-- or
($) f x = f x
-- or
($) = id
It's useful for avoiding extra parentheses: f (g x) == f $ g x.
A particularly useful location for it is for a "trailing lambda body" like
forM_ [1..10] $ \i -> do
l <- readLine
replicateM_ i $ print l
compared to
forM_ [1..10] (\i -> do
l <- readLine
replicateM_ i (print l)
)
Or, trickily, it shows up sectioned sometimes when expressing "apply this argument to whatever function"
applyArg :: a -> (a -> b) -> b
applyArg x = ($ x)
>>> map ($ 10) [(+1), (+2), (+3)]
[11, 12, 13]
I like to think of the $ sign as a replacement for parenthesis.
For example, the following expression:
take 1 $ filter even [1..10]
-- = [2]
What happens if we don't put the $? Then we would get
take 1 filter even [1..10]
and the compiler would now complain, because it would think we're trying to apply 4 arguments to the take function, with the arguments being 1 :: Int, filter :: (a -> Bool) -> [a] -> [a], even :: Integral a => a -> Bool, [1..10] :: [Int].
This is obviously incorrect. So what can we do instead? Well, we could put parenthesis around our expression:
(take 1) (filter even [1..10])
This would now reduce to:
(take 1) ([2,4,6,8,10])
which then becomes:
take 1 [2,4,6,8,10]
But we don't always want to be writing parenthesis, especially when functions start getting nested in each other. An alternative is to place the $ sign between where the pair of parenthesis would go, which in this case would be:
take 1 $ filter even [1..10]

Best practice how to evaluate a list of Maybes

i am looking for a function which takes a function (a -> a -> a) and a list of [Maybe a] and returns Maybe a. Hoogle gave me nothing useful. This looks like a pretty common pattern, so i am asking if there is a best practice for this case?
>>> f (+) [Just 3, Just 3]
Just 6
>>> f (+) [Just 3, Just 3, Nothing]
Nothing
Thanks in advance, Chris
You should first turn the [Maybe a] into a Maybe [a] with all the Just elements (yielding Nothing if any of them are Nothing).
This can be done using sequence, using Maybe's Monad instance:
GHCi> sequence [Just 1, Just 2]
Just [1,2]
GHCi> sequence [Just 1, Just 2, Nothing]
Nothing
The definition of sequence is equivalent to the following:
sequence [] = return []
sequence (m:ms) = do
x <- m
xs <- sequence ms
return (x:xs)
So we can expand the latter example as:
do x <- Just 1
xs <- do
y <- Just 2
ys <- do
z <- Nothing
zs <- return []
return (z:zs)
return (y:ys)
return (x:xs)
Using the do-notation expression of the monad laws, we can rewrite this as follows:
do x <- Just 1
y <- Just 2
z <- Nothing
return [x, y, z]
If you know how the Maybe monad works, you should now understand how sequence works to achieve the desired behaviour. :)
You can then compose this with foldr using (<$>) (from Control.Applicative; equivalently, fmap or liftM) to fold your binary function over the list:
GHCi> foldl' (+) 0 <$> sequence [Just 1, Just 2]
Just 3
Of course, you can use any fold you want, such as foldr, foldl1 etc.
As an extra, if you want the result to be Nothing when the list is empty, and thus be able to omit the zero value of the fold without worrying about errors on empty lists, then you can use this fold function:
mfoldl1' :: (MonadPlus m) => (a -> a -> a) -> [a] -> m a
mfoldl1' _ [] = mzero
mfoldl1' f (x:xs) = return $ foldl' f x xs
and similarly for foldr, foldl, etc. You'll need to import Control.Monad for this.
However, this has to be used slightly differently:
GHCi> mfoldl1' (+) =<< sequence [Just 1, Just 2]
Just 3
or
GHCi> sequence [Just 1, Just 2] >>= mfoldl1' (+)
Just 3
This is because, unlike the other folds, the result type looks like m a instead of a; it's a bind rather than a map.
As I understand it, you want to get the sum of a bunch of maybes or Nothing if any of them are Nothing. This is actually pretty simple:
maybeSum = foldl1 (liftM2 (+))
You can generalize this to something like:
f :: Monad m => (a -> a -> a) -> [m a] -> m a
f = foldl1 . liftM2
When used with the Maybe monad, f works exactly the way you want.
If you care about empty lists, you can use this version:
f :: MonadPlus m => (a -> a -> a) -> [m a] -> m a
f _ [] = mzero
f fn (x:xs) = foldl (liftM2 fn) x xs
What about something as simple as:
λ Prelude > fmap sum . sequence $ [Just 1, Just 2]
Just 3
λ Prelude > fmap sum . sequence $ [Just 1, Just 2, Nothing]
Nothing
Or, by using (+):
λ Prelude > fmap (foldr (+) 0) . sequence $ [Just 1, Just 2]
Just 3
λ Prelude > fmap (foldr (+) 0) . sequence $ [Just 1, Just 2, Nothing]
Nothing
So, maybeSum = fmap sum . sequence.

Resources