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.  Memory usage of if-then-else vs guards
      (Miguel Angel Ordoñez Silis)
   2. Re:  Hello (First message on the mailing list) (Olivier Revollat)
   3.  2D drawing library for Beginner (Olivier Revollat)


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

Message: 1
Date: Fri, 14 Feb 2020 02:21:06 -0600
From: Miguel Angel Ordoñez Silis <miano...@ciencias.unam.mx>
To: beginners@haskell.org
Subject: [Haskell-beginners] Memory usage of if-then-else vs guards
Message-ID:
        <CAM4F45rzAkx7psKN_=yLEM5aPL_4q8-s3Qk3ceETs=kbypj...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Hí everybody,

Earlier today I was testing some code in ghci with ":set +s" enabled. For
some reason I changed an if-then-else expressions to guards and I was
surprised to find out that the memory usage declined significantly (around
20%).

Here is a function call output using if-then-else:
λ> inarow1 ls
1
(1.28 secs, 401,690,400 bytes)

And here is a function call output using guards:
λ> inarow1 ls
1
(1.18 secs, 313,690,576 bytes)

I ran both versions many times and this difference was consistent. Could
you help me understand why?

Thanks

Miguel

P.S. I don't think it should matter but maybe it does, here is the function
definition:

inarow1 :: forall a. Eq a => [a] -> Int
inarow1 []     = 0
inarow1 (x:[]) = 1
inarow1 ls     = aux 0 1 ls where
  aux :: Int -> Int -> [a] -> Int
  aux top curr (x:y:[])      = max top $ if x == y then curr + 1 else curr
  aux top curr (x:xs@(y:ys))
    | x == y    = aux top (curr + 1) xs
    | otherwise = aux (max top curr) 1 xs

And the list:
ls = [1..1000000]
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20200214/cc73028d/attachment-0001.html>

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

Message: 2
Date: Fri, 14 Feb 2020 09:37:53 +0100
From: Olivier Revollat <revol...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: Re: [Haskell-beginners] Hello (First message on the mailing
        list)
Message-ID:
        <CA+nXgrW-3B6uBDaaVN4iQVWtdBy4_awuqNYS7+cEg=gu3z3...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

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 <maydw...@gmail.com> a
écrit :

> 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 <revol...@gmail.com>
> 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
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20200214/19e3a896/attachment-0001.html>

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

Message: 3
Date: Fri, 14 Feb 2020 09:47:31 +0100
From: Olivier Revollat <revol...@gmail.com>
To: The Haskell-Beginners Mailing List - Discussion of primarily
        beginner-level topics related to Haskell <beginners@haskell.org>
Subject: [Haskell-beginners] 2D drawing library for Beginner
Message-ID:
        <ca+nxgruac82lhzm_t8fvhwvavz1buj46j7z8uclv26yfn5h...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

HI,

I would like to experiment with 2D graphics with Haskell (to do for example
generative art, ...)
I found Diagrams library which seem very powerful but I find it a bit
overwhelming for beginner, so do you have anything I can start with ? maybe
even a game engine ....

Thanks ;)
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://mail.haskell.org/pipermail/beginners/attachments/20200214/af94145a/attachment-0001.html>

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

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 7
*****************************************

Reply via email to