Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/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.  Warp and Yesod benchmark puzzle (Lorenzo Bolla)
   2.  factorial question (KMandPJLynch)
   3. Re:  factorial question (Brandon Allbery)
   4. Re:  factorial question (Nick Vanderweit)
   5. Re:  Warp and Yesod benchmark puzzle (Bryce)
   6. Re:  A simple function V2 (Brent Yorgey)
   7.  joining lists sharing multiple type classes (Christopher Howard)
   8. Re:  A simple function V2 (Ertugrul S?ylemez)


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

Message: 1
Date: Fri, 31 Aug 2012 15:24:19 +0100
From: Lorenzo Bolla <lbo...@gmail.com>
Subject: [Haskell-beginners] Warp and Yesod benchmark puzzle
To: beginners@haskell.org
Message-ID:
        <CADjgTRwWdzvSQ1Zxmk6zkvrsGeRdAeL++CBkRm=un-3i_+m...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

Hi all,

This is a question specific to the Yesod framework, but simple enough
(I hope) to be considered a beginner question...

I am puzzled by the performance of these two very simple web-servers,
one written in Warp and another written in Yesod:

=== YESOD ===

{-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses,
TemplateHaskell #-}
import Yesod

data HelloWorld = HelloWorld

mkYesod "HelloWorld" [parseRoutes|
/ HomeR GET
|]

instance Yesod HelloWorld

getHomeR :: Handler RepHtml
getHomeR = defaultLayout [whamlet|$newline always
Hello World!
|]

main :: IO ()
-- main = warpDebug 3000 HelloWorld
main = warp 3000 HelloWorld

=== WARP ===

{-# LANGUAGE OverloadedStrings #-}

import Network.Wai
import Network.HTTP.Types
import Network.Wai.Handler.Warp (run)
import Data.ByteString.Lazy.Char8 ()

app :: Application
app _ = return $ responseLBS
    status200
    [("Content-Type", "text/html")]
    "Hello, Warp!"

main :: IO ()
main = do
    putStrLn "http://localhost:8080/";
    run 8080 app

===

I've tested both using httperf:
$> httperf --hog --client=0/1 --server=localhost --port=3000 --uri=/
--rate=1000 --send-buffer=4096 --recv-buffer=16384 --num-conns=100
--num-calls=100 --burst-length=20

and I got very different results:

YESOD: Request rate: 4048.0 req/s (0.2 ms/req)
WARP: Request rate: 33656.2 req/s (0.0 ms/req)

Now, I understand that Yesod is expected to be slower than the "raw"
Warp, but I wasn't expecting a 10x slowdown, especially for such a
trivial Yesod app (no db, no auth, etc.).

[
Compilation command was: ghc -Wall -O2 --make yesod.hs
$ yesod version
yesod-core version:1.1.0
]

What is going on?

Thanks,
L.



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

Message: 2
Date: Fri, 31 Aug 2012 12:23:24 -0400
From: KMandPJLynch <kmandpjly...@verizon.net>
Subject: [Haskell-beginners] factorial question
To: beginners@haskell.org
Message-ID: <e6b7f256-fc25-4755-a3a7-384379421...@verizon.net>
Content-Type: text/plain; charset="us-ascii"

Good afternoon,

I'm going thru Graham Hutton's book "Programming in Haskell" [and am viewing 
the associated online lectures by Erik Meijer and Graham].
I find both to be excellent.
My problem is with the following statements:

factorial'      :: Int -> Int
factorial'  0    = 1
factorial' (n+1) = (n+1)*factorial' n

When I load this into GHC I get the following error:

pihch01.hs:128:13: Parse error in pattern: n + 1

I'd appreciate any advice.

Good day
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120831/f6939097/attachment-0001.htm>

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

Message: 3
Date: Fri, 31 Aug 2012 12:30:34 -0400
From: Brandon Allbery <allber...@gmail.com>
Subject: Re: [Haskell-beginners] factorial question
To: KMandPJLynch <kmandpjly...@verizon.net>
Cc: beginners@haskell.org
Message-ID:
        <CAKFCL4ULTGxrWbScJVnDUN_G1SFNX5==nbuqzvbzd4n7s77...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

On Fri, Aug 31, 2012 at 12:23 PM, KMandPJLynch <kmandpjly...@verizon.net>wrote:

> *factorial'      :: Int -> Int*
> *factorial'  0    = 1*
> *factorial' (n+1) = (n+1)*factorial' n*
>

n+k patterns were removed from Haskell 2010.  You can re-enable them in GHC
with

{-# LANGUAGE NPlusKPatterns #-}

or

{-# LANGUAGE Haskell98 #-}

as the first line of the source file.

-- 
brandon s allbery                                      allber...@gmail.com
wandering unix systems administrator (available)     (412) 475-9364 vm/sms
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120831/745221c4/attachment-0001.htm>

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

Message: 4
Date: Fri, 31 Aug 2012 10:52:45 -0600
From: Nick Vanderweit <nick.vanderw...@gmail.com>
Subject: Re: [Haskell-beginners] factorial question
To: beginners@haskell.org
Message-ID: <1585000.VWN9Bu1rJa@euler>
Content-Type: text/plain; charset="us-ascii"

You probably don't want to use n+k patterns. Here is a clearer way to write 
it:

factorial' :: Int -> Int
factorial'  0 = 1
factorial'  n = n*factorial' (n-1)


Nick

On Friday, August 31, 2012 12:30:34 PM Brandon Allbery wrote:
> On Fri, Aug 31, 2012 at 12:23 PM, KMandPJLynch 
<kmandpjly...@verizon.net>wrote:
> > *factorial'      :: Int -> Int*
> > *factorial'  0    = 1*
> > *factorial' (n+1) = (n+1)*factorial' n*
> 
> n+k patterns were removed from Haskell 2010.  You can re-enable them in GHC
> with
> 
> {-# LANGUAGE NPlusKPatterns #-}
> 
> or
> 
> {-# LANGUAGE Haskell98 #-}
> 
> as the first line of the source file.



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

Message: 5
Date: Fri, 31 Aug 2012 10:14:06 -0700
From: Bryce <bryceverd...@gmail.com>
Subject: Re: [Haskell-beginners] Warp and Yesod benchmark puzzle
To: beginners@haskell.org
Message-ID: <5040f0de.1000...@gmail.com>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

I'll admit to only recently starting to play with Yesod, but I'll take a 
stab at what I think is going on. Someone else can agree or disagree 
with my response later ;)

I believe that the slowness comes from the extra overhead of using more 
libraries. getHomeR has to process text in hamlet before it can pass 
that onto defaultLayout and forward from there. I believe you might be 
able to speed things up by using RepPlain. I would try this instead:

getHomeR = return . RepPlain . toContent $ "Hello World"

and see if that improves your speed at all.

Also, you are running warp in debug mode. That might have something to 
do with it as well.

Bryce


On 08/31/2012 07:24 AM, Lorenzo Bolla wrote:
> Hi all,
>
> This is a question specific to the Yesod framework, but simple enough
> (I hope) to be considered a beginner question...
>
> I am puzzled by the performance of these two very simple web-servers,
> one written in Warp and another written in Yesod:
>
> === YESOD ===
>
> {-# LANGUAGE TypeFamilies, QuasiQuotes, MultiParamTypeClasses,
> TemplateHaskell #-}
> import Yesod
>
> data HelloWorld = HelloWorld
>
> mkYesod "HelloWorld" [parseRoutes|
> / HomeR GET
> |]
>
> instance Yesod HelloWorld
>
> getHomeR :: Handler RepHtml
> getHomeR = defaultLayout [whamlet|$newline always
> Hello World!
> |]
>
> main :: IO ()
> -- main = warpDebug 3000 HelloWorld
> main = warp 3000 HelloWorld
>
> === WARP ===
>
> {-# LANGUAGE OverloadedStrings #-}
>
> import Network.Wai
> import Network.HTTP.Types
> import Network.Wai.Handler.Warp (run)
> import Data.ByteString.Lazy.Char8 ()
>
> app :: Application
> app _ = return $ responseLBS
>      status200
>      [("Content-Type", "text/html")]
>      "Hello, Warp!"
>
> main :: IO ()
> main = do
>      putStrLn "http://localhost:8080/";
>      run 8080 app
>
> ===
>
> I've tested both using httperf:
> $> httperf --hog --client=0/1 --server=localhost --port=3000 --uri=/
> --rate=1000 --send-buffer=4096 --recv-buffer=16384 --num-conns=100
> --num-calls=100 --burst-length=20
>
> and I got very different results:
>
> YESOD: Request rate: 4048.0 req/s (0.2 ms/req)
> WARP: Request rate: 33656.2 req/s (0.0 ms/req)
>
> Now, I understand that Yesod is expected to be slower than the "raw"
> Warp, but I wasn't expecting a 10x slowdown, especially for such a
> trivial Yesod app (no db, no auth, etc.).
>
> [
> Compilation command was: ghc -Wall -O2 --make yesod.hs
> $ yesod version
> yesod-core version:1.1.0
> ]
>
> What is going on?
>
> Thanks,
> L.
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners




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

Message: 6
Date: Fri, 31 Aug 2012 14:59:43 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] A simple function V2
To: beginners@haskell.org
Message-ID: <20120831185943.ga5...@seas.upenn.edu>
Content-Type: text/plain; charset=iso-8859-1

On Fri, Aug 31, 2012 at 04:15:38PM +0200, Ertugrul S?ylemez wrote:
> Brent Yorgey <byor...@seas.upenn.edu> wrote:
> 
> > > *intercalate :: (Eq t) => [t] -> [t] -> [t]*
> > > *intercalate (x:xs) (y:ys)*
> > > * | xt == [] = []*
> > > * | yt == [] = []*
> > > * | otherwise = x : y : intercalate xs ys*
> > > * where xt=(x:xs)*
> > > *            yt=(y:ys)*
> >
> > I should also point out that the tests xt == [] and yt == [] will
> > never be true!  That is because xt is defined to be (x:xs) and yt is
> > (y:ys).
> 
> That's actually not true.  See his 'where' clause at the bottom.

That's exactly what I was looking at.  Can you clarify what you mean?
Which part of what I said is not true?

-Brent



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

Message: 7
Date: Fri, 31 Aug 2012 11:34:40 -0800
From: Christopher Howard <christopher.how...@frigidcode.com>
Subject: [Haskell-beginners] joining lists sharing multiple type
        classes
To: Haskell Beginners <beginners@haskell.org>
Message-ID: <504111d0.5010...@frigidcode.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi. I've got two data structures, Star and Asteroid (eventually I'll
make more) that both belong to the following type classes: Locatable,
and Animation. I wanted to do something like so in part of the code:

code:
--------
let stars = ... in      -- of type [Star]
let asteroids = ... in  -- of type [Asteroid]
let visibleObjects = do visibleObject <- (stars ++ asteroids)
                        ... -- prep each object for graphics system
                            -- using funcs from both type classes
... -- feed visibleObjects to graphics system
--------

However, this does not work because the two lists are not automatically
downgraded when joined together by (++). The compiler complains about
"asteroids" not being of type [Star]. What is the simplest way to do
what I am trying to do? I tried this, but I think my syntax is off:

code:
--------
let visibleObjects =
  do visibleObject <- ((stars :: [(Locatable a, Animation a) => a)
                      ++ (asteroids :: [(Locatable a, Animation a) => a)
                      )
--------

Compiler complains about "Illegal polymorphic or qualified type".


-- 
frigidcode.com
indicium.us

-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 554 bytes
Desc: OpenPGP digital signature
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120831/4861e910/attachment-0001.pgp>

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

Message: 8
Date: Fri, 31 Aug 2012 22:25:09 +0200
From: Ertugrul S?ylemez <e...@ertes.de>
Subject: Re: [Haskell-beginners] A simple function V2
To: beginners@haskell.org
Message-ID: <20120831222509.40c4b...@angst.streitmacht.eu>
Content-Type: text/plain; charset="us-ascii"

Brent Yorgey <byor...@seas.upenn.edu> wrote:

> That's exactly what I was looking at.  Can you clarify what you mean?
> Which part of what I said is not true?

My bad.  I retract my statement.  Sorry. =)


Greets,
Ertugrul

-- 
nightmare = unsafePerformIO (getWrongWife >>= sex)
http://ertes.de/
-------------- next part --------------
A non-text attachment was scrubbed...
Name: signature.asc
Type: application/pgp-signature
Size: 836 bytes
Desc: not available
URL: 
<http://www.haskell.org/pipermail/beginners/attachments/20120831/a2aedc27/attachment.pgp>

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

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 50, Issue 41
*****************************************

Reply via email to