Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1.  Hello (First message on the mailing list) (Olivier Revollat)
   2. Re:  Hello (First message on the mailing list) (Francesco Ariis)


----------------------------------------------------------------------

Message: 1
Date: Mon, 10 Feb 2020 10:56:40 +0100
From: Olivier Revollat <revol...@gmail.com>
To: beginners@haskell.org
Subject: [Haskell-beginners] Hello (First message on the mailing list)
Message-ID:
        <ca+nxgrxjjpqeycsuw-ayjiuza9ofmgag3fx8nvs9xvguk1j...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hi everybody,
it's my first message on this ML :)

I don't know if it's appropriate to post this here but I would like to have
some feedback with one of my first Haskell code.
I've been inspired by a recent Numberphile video (
https://www.youtube.com/watch?v=HJ_PP5rqLg0) how explain the "Russian
Peasant" algorithm to do multiplication (here in a nutshell :
https://www.wikihow.com/Multiply-Using-the-Russian-Peasant-Method)

So I decided I give it a go in Haskell, here is my solution, I appreciate
if you give me some feedback on how to improve this code (make it more
"idiomatic Haskell")

NB : I apologize if it's not the right place to ask this kind of review ...
in that case, where can I post this ?

Thanks !

module DivRusse where

main :: IO ()
main = do
putStrLn "13 x 12 is"
print $ russmul 13 12

russmul :: Int -> Int -> Int
russmul a b =
let filteredPair = filter (\pair -> (fst pair) `mod` 2 /= 0 ) $ (a,b) :
russmulList a b
in foldr (\pair acc -> snd pair + acc) 0 filteredPair


russmulList :: Int -> Int -> [(Int, Int)]
russmulList 1 _ = []
russmulList a b =
let a' = a `div` 2
b' = b * 2
in (a', b') : russmulList a' b'
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20200210/5cfd9404/attachment-0001.html>

------------------------------

Message: 2
Date: Mon, 10 Feb 2020 12:53:14 +0100
From: Francesco Ariis <fa...@ariis.it>
To: beginners@haskell.org
Subject: Re: [Haskell-beginners] Hello (First message on the mailing
        list)
Message-ID: <20200210115314.GB1097@aspire.station>
Content-Type: text/plain; charset=us-ascii

Hello Olivier,

On Mon, Feb 10, 2020 at 10:56:40AM +0100, Olivier Revollat wrote:
> I don't know if it's appropriate to post this here but I would like to have
> some feedback with one of my first Haskell code.

It is an appropriate post in the appropriate list!

> So I decided I give it a go in Haskell, here is my solution, I appreciate
> if you give me some feedback on how to improve this code (make it more
> "idiomatic Haskell")

Ok, the problems I see with russmulList are:

> russmulList :: Int -> Int -> [(Int, Int)]
> russmulList 1 _ = []
> russmulList a b =
>       let a' = a `div` 2
>           b' = b * 2
>       in (a', b') : russmulList a' b'

- russmulList does not handle 0 gracefully (try `russmulList 0 10`)
- russmulList should _not_ discard the factors from the top of the list
  (or you have to awkwardly re-add them as you did in filteredPair)

This or similar will do:

    russmulList :: Int -> Int -> [(Int, Int)]
    russmulList 0 b = []
    russmulList a b =
            let a' = a `div` 2
                b' = b * 2
            in (a, b) : russmulList a' b'


Now let's go through `russmul`:

> russmul :: Int -> Int -> Int
> russmul a b =
>   let filteredPair = filter (\pair -> (fst pair) `mod` 2 /= 0 ) $ (a,b) :
>                             russmulList a b
>   in foldr (\pair acc -> snd pair + acc) 0 filteredPair

- `(a,b) :` is needed no more
- in filteredPair you can drop the parentheses around `fst pair`
- use `odd` instead of "`mod` 2 /= 0`"
- in any case you should express the predicate in point-free style as
  `even . fst`
- `foldr` part can be made much clearer with sum (map snd ...)

So:

    russmul :: Int -> Int -> Int
    russmul a b =
        let filteredPair = filter (odd . fst) (russmulList a b)
        in sum (map snd filteredPair)


Was this clear/useful? If not, fire again and welcome to the functional
world!
-F


------------------------------

Subject: Digest Footer

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners


------------------------------

End of Beginners Digest, Vol 140, Issue 4
*****************************************

Reply via email to