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

Galaxy Being borgauf at gmail.com
Mon Mar 29 17:12:59 UTC 2021


A bit of post-mortem...

I got this

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

import Data.Maybe
whereIsBM = whereIsBM' 1
whereIsBM' _ Empty = Nothing
whereIsBM' !n (Cons Bacon _) = Just n
whereIsBM' !n (Cons _ lx) = whereIsBM' (succ n) lx

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

to work. Unfortunately, I couldn't get this

whereIsBM boiList = go 0
  where
    go !_ Empty = Nothing
    go !acc (Cons idx lx) | (idx == Bacon) = Just acc
                          | otherwise = go (acc + 1) lx

to work. Both are nearly identical, but the latter gives this error

> whereIsBM (Cons (Indx 5) (Cons (Indx 13) (Cons (Indx 2) (Cons (Indx 8)
Empty))))
No instance for (Show (MyList BaconOrIndex -> Maybe Integer))
:         arising from a use of `print'

This also failed

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

Couldn't match type `Maybe (MyList BaconOrIndex)'
                   with `MyList BaconOrIndex'
    Expected type: MyList BaconOrIndex -> Maybe a
      Actual type: Maybe (MyList BaconOrIndex) -> Maybe a

Not sure why this didn't work. Would like to understand the whole fmap idea
as applied here, though.








On Mon, Mar 29, 2021 at 4:04 AM Henning Thielemann <
lemming at henning-thielemann.de> wrote:

>
> On Mon, 29 Mar 2021, Viktor Dukhovni wrote:
>
> > Thus I applaud Michael Snoyman's quest to address the absense of a basic
> > array type in the `base` library.  Perhaps more users would stop abusing
> > lists (memoisable iterators) as an indexed store.
>
> Data.Array actually _was_ part of base-3.
>
> However, I think we should split 'base' in more smaller parts rather than
> making it bigger.
> _______________________________________________
> 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.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20210329/a8faa118/attachment.html>


More information about the Haskell-Cafe mailing list