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

Antonio Regidor Garcia chikitosan at gmail.com
Mon Mar 29 07:36:16 UTC 2021


A simple solution:

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

whereIsBM = whereIsBM' 0

whereIsBM' _ Empty = Nothing
whereIsBM' !n (Cons Bacon _) = Just n
whereIsBM' !n (Cons _ lx) = whereIsBM' (succ n) lx

You can omit the ! if you want. The result will be the same, but the computation will use more memory because the program will first construct the unevaluated data structure (called 'thunk') suc (suc (suc (... 0) ...)) and then compute it instead of computing succ 0 to 1, then succ 1 to 2, etc., step by step, in constant memory.

succ n is n+1 but faster than the function (+).

Best,

Antonio Regidor Garcia

El Sun, Mar 28, 2021 at 11:27:48PM -0500, Galaxy Being escribió:
> 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>
> 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> 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.
> >
> >

> _______________________________________________
> 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.



More information about the Haskell-Cafe mailing list