[Haskell-beginners] Are these soloutions all valid and a good use of Haskell

Roelof Wobben r.wobben at home.nl
Mon Nov 10 19:59:40 UTC 2014


Stefan Höck schreef op 10-11-2014 20:47:
> Let's do this step by step. We use the following list: [1,2,3]
>
> foldr takes three arguments:
>
>    foldr :: (a -> b -> b) -> b -> [a] -> b
>
> The last of the three has type [a].
> This means, the fold expects a list as an argument here. The
> lower case letter `a` is the type of the items in the list. In
> our case this is `Int`, but we could pass it other lists with
> other element types.
>
> The second argument of the fold has type `b`, this is the result
> type we'd like to get from the fold. In our case this is `Maybe Int`
> since we want to know from the result, whether the list was empty
> or not. Nothing in case of an empty list, Just x with x being the
> right-most item in the non-empty case.
>
> The first argument of the fold is a higher order function. It
> accepts an argument of type `a` (the element type of the list)
> and of type `b` (the result type of the fold) and should return
> a value of type `b`. In our example, `a` is equal to `Int` and b
> is equal to `Maybe Int`.
>
> Therefore, the following cannot possibly work:
>
>>     acc a acc  = if null a then Nothing else if (null (tail a)) then (Just
> the first argument of acc (the value `a` in your implementation) has
> type `a` (note the distinction between a value and a type, both have
> the same name here, but that doesn't need to be the case. You could
> rename the value to x or foo or whatever). In our case, the type
> `a` is `Int` since we fold over a list of Ints. If we were to fold
> over a list of Strings, type `a` would be equal to `String`. Note
> however, that since `a` can be anything (Int, String etc, depending
> on the element type of your list), you cannot possibly call `null`
> on it. null takes a list as an argument, but `a` is not necessarily a
> list. It's the type of the list's elements, not the whole list.
> You do not pass the whole list to the accumulator. You only pass it
> the list's element in single file.
>
> Now, what happens, when we fold over the list? Since we fold from the
> right, our accumulator is passed two arguments: The last value of the
> list and the initial value of type `b` (in our case `Nothing`).
>
> acc 3 Nothing = ???
>
> What should be the result of this? Clearly you'd like to keep the 3 as
> it is actually the result you are looking for. But you cannot return the
> 3 directly. The return type of our function must be `Maybe Int` and the
> type of `3` is `Int`. We first must wrap the `3` in a `Maybe`. There
> is only one way to do that:
>
>    acc 3 Nothing = Maybe 3
>
> (This is pseudocode an will not compile. The real implementation follows
> below)
>
> Now comes the next item in the list: `2`. Function acc gets called
> again, this time with `2` as its first argument, and the result of
> our fold so far which is `Just 3`
>
>    acc 2 (Just 3) = ???
>
> Clearly we do not want to lose the `3`, it's the result we are looking
> for after all!
>
>    acc 2 (Just 3) = Just 3
>
> Finally, the last item (from the right) in the list comes along:
>
>    acc 1 (Just 3) = Just 3
>
> Again we let it pass and get Just 3 as the result.
>
> This is how foldr works. Every element of the list starting with the
> rightmost is passed as an argument to the accumulator function together
> with the value accumulated so far (for which you must provide an initial
> value).
>
> Now, the implementation. We have seen, that we want to get hold of
> the very first value that comes from the list and ignore everything
> else that comes after it.
>
>    acc :: a -> Maybe a -> Maybe a    # This is the function's type signature
>    acc x Nothing  = Just x           # We wrap the first value ...
>    acc x (Just y) = Just y           # and keep hold of it
>
> When we now use this accumulator in our fold, it gets first called with
> arguments `3` and `Nothing` so the first pattern matches. Variable x
> is assigned the value `3` and the result is `Just 3`.
>
> The function gets called again with the second value `2` and `Just 3`,
> the result from the first call. This time, the first pattern does not
> match (Nothing does not match `Just 3`), but the second does. `x` is
> assigned the value `2`, `y` is assigned the value `3` (the one wrapped
> in the `Just`) and the result is `Just 3`. Same for the last element.
>
> Here is the complete implementation:
>
>    last5 :: [a] -> Maybe a
>    last5 = foldr acc Nothing where
>        acc x Nothing  = Just x
>        acc x (Just y) = Just y
>
> Or better
>
>    last5 :: [a] -> Maybe a
>    last5 = foldr acc Nothing where
>        acc x Nothing  = Just x
>        acc _ j        = j
>
> Or even (this one will be harder to figure out)
>    last5 :: [a] -> Maybe a
>    last5 = foldr acc Nothing where
>        acc x = maybe (Just x) Just
>
> Cheers, Stefan
>
>

I understand the theory but i loose it on the implementation.

Lets take the better variant.

last5 :: [a] -> Maybe a
   last5 = foldr acc Nothing where
       acc x Nothing  = Just x
       acc _ j        = j


Let's say we have [1,2,3]

Do I understand that acc = Nothing. and x = 3 ?
and after  acc x Nothing = Just x  acc get's the value 3

But how does x get's the value 3 or does foldr takes care of that ?

Roelof



More information about the Beginners mailing list