Hello (First message on the mailing list)

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'

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

Hello Francesco,
This is very clear. Thanks for your help !
Your version is much more readable and elegant !
Le lun. 10 févr. 2020 à 12:53, Francesco Ariis
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 _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Hi Olivier,
I had a quick look, I think it's a great first try. Here are my thoughts!
module DivRusse where
{-
Comments:
* This seems unsafe in that it doesn't handle negative numbers well.
* This can be evidenced by needing a guard on our property.
* Could be addressed by using a safe newtype.
* Define properties and use quickcheck to test them.
* Favor pattern-matching over use of `fst`, `snd`.
* Use `where` over `let` to highlight what the final result is.
* Rewrite folds to more wholemeal approach. e.g. `sum $ map snd
filteredPair`
* Use standard functions and composition to eliminate lambdas like this:
`(\(x, _) -> x `mod` 2 /= 0 )` = `(odd . fst)`.
* `russmulList` could go into an infinite loop for negative numbers.
Either prevent this with types (preferred), or return an error somehow.
-}
main :: IO ()
main = do
putStrLn "13 x 12 is"
print $ russmul 13 12
-- Property: Does russmul = *?
prop_russmul :: Int -> Int -> Bool
prop_russmul a b
| a > 0 && b > 0 = russmul a b == a * b
| otherwise = True
russmul :: Int -> Int -> Int
russmul a b = sum $ map snd filteredPair
where
filteredPair = filter (odd . fst) $ (a,b) : russmulList a b
russmulList :: Int -> Int -> [(Int, Int)]
russmulList 1 _ = []
russmulList a b = (a', b') : russmulList a' b'
where
a' = a `div` 2
b' = b * 2
Warm Regards,
- Lyndon
On Mon, Feb 10, 2020 at 8:55 PM Olivier Revollat
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'
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

Thank you Lyndon,
Your comments will help me a lot !
I'm glad the haskell community is kind with beginner !
Le jeu. 13 févr. 2020 à 05:25, Lyndon Maydwell
Hi Olivier,
I had a quick look, I think it's a great first try. Here are my thoughts!
module DivRusse where
{- Comments:
* This seems unsafe in that it doesn't handle negative numbers well. * This can be evidenced by needing a guard on our property. * Could be addressed by using a safe newtype. * Define properties and use quickcheck to test them. * Favor pattern-matching over use of `fst`, `snd`. * Use `where` over `let` to highlight what the final result is. * Rewrite folds to more wholemeal approach. e.g. `sum $ map snd filteredPair` * Use standard functions and composition to eliminate lambdas like this: `(\(x, _) -> x `mod` 2 /= 0 )` = `(odd . fst)`. * `russmulList` could go into an infinite loop for negative numbers. Either prevent this with types (preferred), or return an error somehow.
-}
main :: IO () main = do putStrLn "13 x 12 is" print $ russmul 13 12
-- Property: Does russmul = *? prop_russmul :: Int -> Int -> Bool prop_russmul a b | a > 0 && b > 0 = russmul a b == a * b | otherwise = True
russmul :: Int -> Int -> Int russmul a b = sum $ map snd filteredPair where filteredPair = filter (odd . fst) $ (a,b) : russmulList a b
russmulList :: Int -> Int -> [(Int, Int)] russmulList 1 _ = [] russmulList a b = (a', b') : russmulList a' b' where a' = a `div` 2 b' = b * 2
Warm Regards,
- Lyndon
On Mon, Feb 10, 2020 at 8:55 PM Olivier Revollat
wrote: 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'
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners
participants (3)
-
Francesco Ariis
-
Lyndon Maydwell
-
Olivier Revollat