Simplifying nested Maybe pattern matching - haskell

I have the following construct in my code:
f :: Maybe A -> X
f a = case a of
Nothing -> x
(Just b) -> case b of
Nothing -> y
(Just c) -> case c of
Nothing -> z
(Just d) -> d
I'm not seeing an obvious way to simplify this instead of using nested maybe functions, which wouldn't make the whole thing look much better. Are there any clever - but still understandable - tricks that would help make this construct more "elegant"?

Why did the code construct a Maybe (Maybe (Maybe X)) value in the first place? Unpacking such a value isn't nice, but the real question is, why there even is such a value. Maybe the code would better avoid all those nested Maybes.
If you really need to have such a value and need to do different things in all the Just/Nothing cases you'll have to write them all down. But instead of several nested case statements you could combine them into one big pattern match:
f Nothing = x
f (Just Nothing)) = y
f (Just (Just Nothing)) = z
f (Just (Just (Just d))) = d

Despite your constraint about not using maybe, I think this looks quite nice:
f = maybe x (maybe y (maybe z id))
or even better, as #pat suggests in his comment:
f = maybe x . maybe y . maybe z $ id

UPDATED 2
Monad Either is for you
import Data.Maybe (maybe)
maybeE :: e -> Maybe a -> Either e a
maybeE e = maybe (Left e) Right
f :: Maybe (Maybe (Maybe d)) -> Either e d
f a = maybeE x a
>>= maybeE y
>>= maybeE z
UPDATED 3
If we want to have not Either type, we could rewrite function:
import Data.Either(either)
either' = either id id
f :: Maybe (Maybe (Maybe d)) -> d
f a = either' $ maybeE x a
>>= maybeE y
>>= maybeE z

Related

How to implement Factorial via Control.Arrow.loop?

I wonder whether it is possible to implement factorial using Control.Arrow.loop.
loop :: ArrowLoop a => a (b, d) (c, d) -> a b c
One of the evident ideas is to implement a somehow terminating branch (a branch where the first element of the pair (type c) wouldn't depend on the second element of the pair (type d)).
It seems to me that it can't be done since we can't apply any boolean function to the second element of the pair (type d) during the first iteration because it would cause infinite recursion, so it only leaves us with the argument (type b), but the result of any boolean function wouldn't differ depending on the iteration (the argument doesn't change), thus, it would either terminate instantly or never terminate at all.
The other idea I had is to create an endless stream of factorials, but this doesn't seem real either, since, once again, the argument can't be changed.
So, I have 3 questions:
Am I right about the points above?
Am I missing any other concept which would help to implement factorial via Control.Arrow.loop?
What is the correct idea behind this implementation?
I've never actually used ArrowLoop before, loop is pretty cool.
Here is a factorial implemented using loop:
fact :: Integer -> Integer
fact =
loop $ \(n, f) ->
( f n 1
, \i acc ->
if i > 0
then f (i - 1) (i * acc)
else acc)
Let's give it a try:
λ> fact <$> [1..11]
[1,2,6,24,120,720,5040,40320,362880,3628800,39916800]
I don't know if I can answer the first question you have, but for the 3rd one it's obviously possible. For the concepts that could help you, I think the fix point is the one you are looking for. For example you can start by trying this ;)
λ> import Data.Function
λ> fix error
Once you press enough Ctrl+C you can write factorial using fix point:
λ> let fact = fix $ \ f i -> if i > 1 then i * f (i - 1) else i
λ> fact <$> [1..11]
[1,2,6,24,120,720,5040,40320,362880,3628800,39916800]
Edit
It seems like a bit of expansion on the answer could be helpful.
First of all let's look at an alternative and better (due to tail recursion) implementation of fact using fix, so we can see how it compares with our implementation using loop:
factFix :: Integer -> Integer
factFix n =
fix
(\f ->
\i acc ->
if i > 0
then f (i - 1) (i * acc)
else acc)
n
1
We can see it is not far off. In both cases we get f as an argument and we return back a function that uses that f, in fact, the returned non-recursive function is identical in both cases. Just for clarity let's extract it an reuse in both places:
factNoRec :: (Ord p, Num p) => (p -> p -> p) -> p -> p -> p
factNoRec f i acc =
if i > 0
then f (i - 1) (i * acc)
else acc
factLoop :: Integer -> Integer
factLoop n = loop (\(k, f) -> (f k 1, factNoRec f)) n
factFix :: Integer -> Integer
factFix n = fix (\f -> factNoRec f) n 1
Hopefully now it is much more apparent that they are really related concepts.
Looking into implementations of fix and loop (at least for functions, cause there are also mfix and loop for Kleisli) provides even more insight into their relation:
λ> fix f = let x = f x in x
λ> loop f b = let (c,d) = f (b,d) in c
They are really close to each other.
How about type signatures:
λ> :t fix
fix :: (t -> t) -> t
λ> :t loop
loop :: ((b, d) -> (c, d)) -> b -> c
Those look different. But if you do a bit of unification in the fact case you'll see that fix and loop acquire types:
λ> :t fix :: ((a -> b -> c) -> (a -> b -> c)) -> a -> b -> c
λ> :t loop :: ((b, a -> b -> c) -> (c, a -> b -> c)) -> b -> c
All of a b and c become all Integer in the end, but looking at type variables instead gives a better insight into what's going on. And really what's going on is just recursion by the means of fixed point combinators.

Trouble explaining Haskell code with where and pattern match

I have hard time parsing how mf m y are assigned values or even why there can be 3 variables on the left side of assignment in where section.
Q: Can anyone explain what happens here in both cases? (that is for empty list and a list with some elements)
-- | A variant of 'foldl' that has no base case,
-- and thus may only be applied to non-empty structures.
--
-- #'foldl1' f = 'List.foldl1' f . 'toList'#
foldl1 :: (a -> a -> a) -> t a -> a
foldl1 f xs = fromMaybe (errorWithoutStackTrace "foldl1: empty structure")
(foldl mf Nothing xs)
where
mf m y = Just (case m of
Nothing -> y
Just x -> f x y)
(this is the source code for the foldl1 function).
Definitions in where clauses follow the same syntax as global definitions, so mf m y = ... defines a function named mf, which takes parameters named m and y.
I have hard time parsing how mf m y are assigned values or even why there can be 3 variables.
You do not define three variables here: you define a variable mf which is a function, and m and y are two arguments of the function mf.
We can make the function more elegant, and thus omit the m and y. mf can be defined as:
mf Nothing = Just . id
mf (Just x) = Just . f x
Mind that we can not simply make mf an outer function, since it uses a function f, with is a parameter of foldl1. So we put it in a where clause:
foldl1 :: (a -> a -> a) -> t a -> a
foldl1 f xs = fromMaybe (errorWithoutStackTrace "foldl1: empty structure")
(foldl mf Nothing xs)
where mf Nothing = Just . id
mf (Just x) = Just . f x
In the empty list case, foldl mf Nothing [] ~ Nothing by definition, so foldl1 will return the "empty structure" error.
When xs is not empty, then foldl1' is simply a left fold by foldl. In this case foldl has the type
foldl :: (Maybe a -> a -> Maybe a) -> Maybe a -> [a] -> Maybe a
which makes use of the combining function mf :: Maybe a -> a -> Maybe a defined in the where clause.

How to use lens set function with Maybe?

I have a tuple x and a Maybe value y
x = (1,1)
y = Just 2
I can do this
z = maybe x (\v -> x & _1 .~ v) y
Or I can create my own operator
(.~?) x y = x %~ (\v -> fromMaybe v y)
z = x & _1 .~? y
But if lens doesn't have such operator, maybe I don't need it?
So, how to use lens set function with Maybe?
It appears that you want
maybeSetFst :: (a, b) -> Maybe a -> (a, b)
which will update the first field if given an update value and will leave it alone otherwise. I think the first implementation you give is very good, but you can give it a more general type:
maybeSetFst :: Field1 s s a a => s -> Maybe a -> s
If you don't want that generality, you can skip the lenses and write (using TupleSections)
maybeSetFst p#(_,b) = maybe p (,b)
Another option is to apply maybe to get the update function:
maybeSetFst p m = maybe id (_1 .~) m p
which can be written
maybeSetFst = flip $ maybe id (_1 .~)
for point-free silliness.

Haskell "transform" function

I've written what I imagine would be a common function in Haskell, but I couldn't find it implemented anywhere. For want of a better word I've called it "transform".
What "transform" does three arguments: a list, and an initial state and a function that takes an element from the list, a state, and produces an element for an output list, and a new state. The output list is the same length as the input list.
It's kind of like "scanl" if it also took a state parameter, or like "unfoldr" if you could feed it a list.
Indeed, I've implemented this function below, in two different ways that have the same result:
transform1 :: (b -> c -> (a, c)) -> c -> [b] -> [a]
transform1 f init x = unfoldr f' (x, init)
where
f' ((l:ls), accum) = let (r, new_accum) = f l accum in Just (r, (ls, new_accum))
f' ([], _) = Nothing
transform2 :: (b -> c -> (a, c)) -> c -> [b] -> [a]
transform2 f init x = map fst $ tail $ scanl f' init' x where
f' (_,x) y = f y x
init' = (undefined, init)
This sort of operation seems relatively common though, that is, taking a list and walking through it with some state and producing a new list, so I'm wondering if there's a function that already exists and I'm reinventing the wheel. If so, I'll just use that, but if not, I might package what I've got into a (very) small library.
This is almost, but not exactly Data.List.mapAccumL. The difference is that mapAccumL also includes the final state. Also it recently got generalized to Traversable.
mapAccumL :: Traversable t => (a -> b -> (a, c)) -> a -> t b -> (a, t c)

What else can `loeb` function be used for?

I am trying to understand "Löb and möb: strange loops in Haskell", but right now the meaning is sleaping away from me, I just don't see why it could be useful. Just to recall function loeb is defined as
loeb :: Functor f => f (f a -> a) -> f a
loeb x = go where go = fmap ($ go) x
or equivalently:
loeb x = go
where go = fmap (\z -> z go) x
In the article there is an example with [] functor and spreadsheets implementation, but it is bit foreign for me just as spreadsheets themselves (never used them).
While I'm understanding that spreadsheet thing, I think it would help a lot for me and others to have more examples, despite lists. Is there any application for loeb for Maybe or other functors?
The primary source (I think) for loeb is Dan Piponi's blog, A Neighborhood of Infinity. There he explains the whole concept in greater detail. I'll replicate a little bit of that as an answer and add some examples.
loeb implements a strange kind of lazy recursion
loeb :: Functor a => a (a x -> x) -> a x
loeb x = fmap (\a -> a (loeb x)) x
Let's imagine we have a type a, where Functor a, and an a-algebra (a function of type a x -> x). You might think of this as a way of computing a value from a structure of values. For instance, here are a few []-algebras:
length :: [Int] -> Int
(!! 3) :: [a] -> a
const 3 :: Num a => [a] -> a
\l -> l !! 2 + l !! 3 :: Num a => [a] -> a
We can see that these a-algebras can use both values stored in the Functor and the structure of the Functor itself.
Another way to think of d :: a x -> x is as a value of x which requires some context–a whole Functorized value a x–in order to be computed. Perhaps this interpretation is more clearly written as Reader (a x) x, emphasizing that this is just a value of x which is delayed, awaiting the a x context to be produced.
type Delay q x = q -> x
Using these ideas we can describe loeb as follows. We're given a f-structure containing some Delayed values, where f is a Functor
Functor f, f (Delay q x)
Naturally, if we were given a q then we could convert this into a not delayed form. In fact, there's only one (non-cheating) function that does this polymorphically:
force :: Functor f => f (Delay q x) -> q -> f x
force f q = fmap ($ q) f
What loeb does is handle the extra tricky case where q is actually force f q, the very result of this function. If you're familiar with fix, this is exactly how we can produce this result.
loeb :: Functor a => a (Delay (a x) x) -> a x
loeb f = fix (force f)
So to make an example, we simply must build a structure containing Delayed values. One natural example of this is to use the list examples from before
> loeb [ length :: [Int] -> Int
, const 3 :: [Int] -> Int
, const 5 :: [Int] -> Int
, (!! 2) :: [Int] -> Int
, (\l -> l !! 2 + l !! 3) :: [Int] -> Int
]
[5, 3, 5, 5, 10]
Here we can see that the list is full of values delayed waiting on the result of evaluating the list. This computation can proceed exactly because there are no loops in data dependency, so the whole thing can just be determined lazily. For instance, const 3 and const 5 are both immediately available as values. length requires that we know the length of the list but none of the values contained so it also proceeds immediately on our fixed-length list. The interesting ones are the values delayed waiting on other values from inside our result list, but since (!! 2) only ends up depending on the third value of the result list, which is determined by const 5 and thus can be immediately available, the computation moves forward. The same idea happens with (\l -> l !! 2 + l !! 3).
So there you have it: loeb completes this strange kind of delayed value recursion. We can use it on any kind of Functor, though. All we need to do is to think of some useful Delayed values.
Chris Kuklewicz's comment notes that there's not a lot you could do interestingly with Maybe as your functor. That's because all of the delayed values over Maybe take the form
maybe (default :: a) (f :: a -> a) :: Maybe a -> a
and all of the interesting values of Maybe (Delay (Maybe a) a) ought to be Just (maybe default f) since loeb Nothing = Nothing. So at the end of the day, the default value never even gets used---we always just have that
loeb (Just (maybe default f)) == fix f
so we may as well write that directly.
You can use it for dynamic programming. The example that comes to mind is the Smith-Waterman algorithm.
import Data.Array
import Data.List
import Control.Monad
data Base = T | C | A | G deriving (Eq,Show)
data Diff = Sub Base Base | Id Base | Del Base | Ins Base deriving (Eq,Show)
loeb x = let go = fmap ($ go) x in go
s a b = if a == b then 1 else 0
smithWaterman a' b' = let
[al,bl] = map length [a',b']
[a,b] = zipWith (\l s -> array (1,s) $ zip [1..] l) [a',b'] [al,bl]
h = loeb $ array ((0,0),(al,bl)) $
[((x,0),const 0) | x <- [0 .. al]] ++
[((0,y),const 0) | y <- [1 .. bl]] ++
[((x,y),\h' -> maximum [
0,
(h' ! (x - 1,y - 1)) + s (a ! x) (b ! y),
(h' ! (x - 1, y)) + 1,
(h' ! (x, y - 1)) + 1
]
) | x <- [1 .. al], y <- [1 .. bl]]
ml l (0,0) = l
ml l (x,0) = ml (Del (a ! x): l) (x - 1, 0)
ml l (0,y) = ml (Ins (b ! y): l) (0, y - 1)
ml l (x,y) = let
(p,e) = maximumBy ((`ap` snd) . (. fst) . (const .) . (. (h !)) . compare . (h !) . fst) [
((x - 1,y),Del (a ! x)),
((y, x - 1),Ins (b ! y)),
((y - 1, x - 1),if a ! x == b ! y then Id (a ! x) else Sub (a ! x) (b ! y))
]
in ml (e : l) p
in ml [] (al,bl)
Here is a live example where it is used for: Map String Float
http://tryplayg.herokuapp.com/try/spreadsheet.hs/edit
with loop detection and loop resolution.
This program calculates speed, time and space. Each one depends on the other two. Each cell has two values: his current entered value and the expression as a function of the other cell values/expressions. circularity is permitted.
The Cell recalculation code uses the famous loeb expression by Dan Piponi in the 2006. Until now by my knowledge there haven't been any materialization of this formula on a real working spreadsheet. this one is close to it. Since loeb enters in a infinite loop when circular expressions are used, the program counts the loops and reduces complexity by progressively substituting formulas by cell values until the expression has no loops
This program is configured for immediate recalculation on cell change, but that can be adapted to allow the modification of more than one cell before recalculation by triggering it by means of a button.
This is blog pos:
http://haskell-web.blogspot.com.es/2014/09/spreadsheet-like-program-in-browser.html

Resources