[Haskell-cafe] Maybe won't let me count

CASANOVA Juan Juan.Casanova at ed.ac.uk
Mon Mar 29 06:11:36 UTC 2021


As others explained, you still can't do (1 + whereIsBM Ix), you need to unwrap the whereIsBM value or use fmap (<$>).

Here, let me give you a small modification on your code that will do it:

whereIsBM boiList = case boiList of
                      Nothing -> Nothing
                      Just (Cons idx lx)
                        | (idx == Bacon) -> Just 1
                        | otherwise -> (1 +) <$> (whereIsBM lx)

And as others have explained, what this does is take the result of (whereIsBM Ix), which is a Maybe-wrapped value, and apply the function ((1 +) <$>) (alternatively, (fmap (1 +))), which basically just takes the function (1 +) (add 1 to a number) and applies it to whatever is wrapped inside the Maybe (your numbers), while keeping the Maybe structure. So if the result of (whereIsBM x) is Nothing, then applying ((1 +) <$>) will return Nothing because there's nothing wrapped, whereas if (whereIsBM x) is (Just n), then applying ((1 + ) <$>) to it will return (Just (1 + n)).

You could also, as others explained, case match on the result of (whereIsBM Ix), but that would be more verbose and probably just confuse you. But it is, ultimately, what fmap is actually doing. Unwrapping and re-wrapping.
________________________________
From: Haskell-Cafe <haskell-cafe-bounces at haskell.org> on behalf of Galaxy Being <borgauf at gmail.com>
Sent: 29 March 2021 05:27
To: haskell-cafe <haskell-cafe at haskell.org>
Subject: Re: [Haskell-cafe] Maybe won't let me count

This email was sent to you by someone outside the University.
You should only click on links or attachments if you are certain that the email is genuine and the content is safe.
I'm not getting past

whereIsBM boiList = case boiList of
                      Nothing -> Nothing
                      Just (Cons idx lx)
                        | (idx == Bacon) -> Just 1
                        | otherwise -> Just (1 + whereIsBM lx)

...and a few other attempts.

On Sun, Mar 28, 2021 at 10:37 PM Jon Purdy <evincarofautumn at gmail.com<mailto:evincarofautumn at gmail.com>> wrote:
‘whereIsBM’ returns a Maybe-wrapped value, so applying ‘1 + …’ to it would require ‘Maybe a’ to be in ‘Num’, hence the error message. ‘FlexibleContexts’ (ditto ‘FlexibleInstances’) is a pretty benign extension, but it won’t help here, since it just kicks the error down the road a bit.

The basic thing you need to do is match on the Maybe and return ‘Nothing’ if it was ‘Nothing’, or ‘Just (1 + x)’ if it was ‘Just x’ for some x. That can be written quite literally as a ‘case’ expression:

case whereIsBM lx of
  Just x -> Just (1 + x)
  Nothing -> Nothing

Which could also be written with ‘do’:

do
  x <- whereIsBM lx
  pure (1 + x)

But this pattern is very common, so it’s already packaged up and generalised as ‘fmap’, a.k.a. ‘<$>’

fmap (1 +) (whereIsBM lx)
-- or
(1 +) <$> whereIsBM lx

On Sun, Mar 28, 2021, 8:13 PM Galaxy Being <borgauf at gmail.com<mailto:borgauf at gmail.com>> wrote:
I've got this

import Data.Maybe

data MyList a = Empty | Cons a (MyList a) deriving (Eq,Ord,Show)
data BaconOrIndex = Bacon | Indx Int deriving (Eq,Ord,Show)

whereIsBM Empty = Nothing
whereIsBM (Cons idx lx) = if (idx == Bacon) then Just 1 else (whereIsBM lx)

which I would like to tell me where the Bacon is (index), not just if there's Bacon, which is what it does now. That is, I need this to happen

> whereIsBM (Cons (Indx 5) (Cons Bacon (Cons (Indx 2) (Cons (Indx 8) Empty))))
Just 2

So I need to traverse a BaconOrIndex list and count how deep I went to find the Bacon variable. I get the above code to evaluate error-free, but obviously I'm only returning a Just 1 when it sees Bacon. What I need is to have the last part be

 . . . else (1 + whereIsBM lx)

 work; but it keeps giving the error

Non type-variable argument in the constraint: Num (Maybe a)
      (Use FlexibleContexts to permit this)
    • When checking the inferred type
        whereIsBM :: forall a.
                     (Num a, Num (Maybe a)) =>
                     MyList BaconOrIndex -> Maybe a

I haven't a clue what this means. Eventually, I'll wrap this in something that handles the Nothing and  does fromJust on the alternative. This whole effort is because if I didn't use the Maybe strategy, and said

whereIsBM Empty = 0
...

it would never give back 0 if it didn't find Bacon, rather, it would simply return the whole countdown to Empty. What can I do to make Maybe work here?

LB
_______________________________________________
Haskell-Cafe mailing list
To (un)subscribe, modify options or view archives go to:
http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
Only members subscribed via the mailman list are allowed to post.
The University of Edinburgh is a charitable body, registered in Scotland, with registration number SC005336. Is e buidheann carthannais a th’ ann an Oilthigh Dhùn Èideann, clàraichte an Alba, àireamh clàraidh SC005336.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20210329/b747ff4b/attachment.html>


More information about the Haskell-Cafe mailing list