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. Re:  Optimization Problem (Brent Yorgey)
   2.   Re: Please take the State of Haskell, 2010 survey (Johan Tibell)
   3. Fwd: [Haskell-beginners] Optimization Problem
      (200901...@daiict.ac.in)
   4.  FastCGI error (Wayne R)


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

Message: 1
Date: Mon, 9 Aug 2010 10:44:43 +0100
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Optimization Problem
To: beginners@haskell.org
Message-ID: <20100809094442.ga22...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

I don't know all that much about profiling/optimization.  But one
simple thing occurs to me -- does it help to change inDisc to

  inDisc (Disc r p1 _) p2 = (distsqr p1 p2) <= r*r

  distsqr :: Point -> Point -> Double
  distsqr (x1, y1) (x2, y2) = (x1 - x2)^2 + (y1 - y2)^2

Then you avoid using sqrt.  Also there's no need to use ** since you
are taking a positive integral power.  (^2) will optimize to just a
single multiplication, whereas I have no idea what (**2) does, it's
probably much slower.

You could even store the square of the radius in Disc, then you also
avoid having to compute r*r every time.

-Brent

On Mon, Aug 09, 2010 at 01:16:54PM +0530, 200901...@daiict.ac.in wrote:
> Optimization Problem 
> 
> I am trying to make an algorithm which solves Smallest circle problem( http 
> ://en. wikipedia .org/ wiki /Smallest_circle_problem). 
> My code takes ~3.2 sec to solve ~500 data sets of 2000 points apiece. I need 
> it to be done in less than 1 sec. 
> After profiling it seems that ~1.76 (55%) sec goes to the inDisc function and 
> ~1 (32%) sec goes into gcnts . So I am trying 
> to optimize these parts of the code. 
> 
> -- is the point p2 is inside disc? 
> inDisc :: Disc -> Point -> Bool 
> inDisc (Disc r p1 _) p2 = (distance p1 p2) <= r 
> 
> -- gives the double values in one line 
> gcnts :: IO [Double] 
> gcnts = do 
> line <- getLine 
> return (map read (words line)) 
> 
> And data and point are 
> 
> -- (x, y) 
> type Point = (Double, Double) 
> 
> - radius, center, know points in the disc 
> data Disc = Disc Double Point [Point] 
> deriving (Show) 
> 
> The relevant profiler part: 
> COST CENTRE MODULE %time % alloc 
> 
> inDisc Main 55.0 0.0 
> gcnts Main 32.5 58.1 
> 
> individual inherited 
> COST CENTRE MODULE no. entries %time % alloc %time % alloc 
> inDisc Main 247 1237577 35.6 0.0 35.6 0.0 
> inDisc Main 244 527216 11.9 0.0 11.9 0.0 
> inDisc Main 241 214076 7.5 0.0 7.5 0.0 
> gcnts Main 235 8043 31.3 58.1 31.3 58.1 
> gcnts Main 233 10 1.3 0.0 1.3 0.0 
> gcnts Main 231 1 0.0 0.0 0.0 0.0 
> 
> I have attached my code and profiler output. 
> 
> BSRK Aditya . 

> import Data.List
> 
> type Point = (Double, Double)
> data Disc = Disc Double Point [Point]
>             deriving (Show)
> 
> getRad :: Disc -> Double
> getRad (Disc r _ _) = r
> 
> getPoints :: Disc -> [Point]
> getPoints (Disc _ _ ps) = ps
> 
> getCen :: Disc -> Point
> getCen (Disc _ p _) = p
> 
> midpoint :: Point -> Point -> Point
> midpoint (x1, y1) (x2, y2) = ((x1+x2)/2, (y1+y2)/2)
> 
> distance :: Point -> Point -> Double
> distance (x1, y1) (x2, y2) = sqrt((x1 - x2)**2 + (y1 - y2)**2)
> 
> inDisc :: Disc -> Point -> Bool
> inDisc (Disc r p1 _) p2 = (distance p1 p2) <= r
> 
> appendPoint :: Disc -> Point -> Disc
> appendPoint (Disc r p ps) p2 = (Disc r p (p2:ps))
> 
> circumCenter :: Point -> Point -> Point -> Point
> circumCenter (ax, ay) (bx, by) (cx, cy)
>     =  (((ay**2+ax**2)*(by-cy)+(by**2+bx**2)*(cy-ay)+(cy**2+cx**2)*(ay-by))/d,
>        ((ay**2+ax**2)*(cx-bx)+(by**2+bx**2)*(ax-cx)+(cy**2+cx**2)*(bx-ax))/d)
>        where d = 2*(ax*(by-cy)+bx*(cy-ay)+cx*(ay-by))
> 
> mround x = (fromIntegral (round (100*x)))/100
> -- the real code
> minDisc :: [Point] -> Disc
> minDisc (p1:p2:[]) = Disc ((distance p1 p2)/2) (midpoint p1 p2) (p1:p2:[])
> minDisc (p1:p2:ps) = foldl' helper (minDisc (p2:p1:[])) ps
>    where helper d p
>            | (inDisc d p) = (appendPoint d p)
>            | otherwise = (minDiscwp (getPoints d) p)
> minDisc _ = Disc 0 (0, 0) []
> 
> minDiscwp :: [Point] -> Point -> Disc
> minDiscwp ps q = foldl' (helper q) (minDisc ((head ps):q:[])) (tail ps)
>     where helper q d p
>            | (inDisc d p) = (appendPoint d p)
>            | otherwise = (minDiscwp2 (init (getPoints d)) p q)
> 
> minDiscwp2 :: [Point] -> Point -> Point -> Disc
> minDiscwp2 ps q1 q2 = foldl' (helper q1 q2) (minDisc (q1:q2:[])) ps
>     where helper q1 q2 d p
>            | (inDisc d p) = (appendPoint d p)
>            | otherwise = Disc (distance cr p) cr (p:(getPoints d))
>                where cr = circumCenter q1 q2 p
> --IO
> 
> solver :: Double -> [(Double, Double, Double, Double)] -> Double
> solver t lst =  mround(getRad (minDisc (map (h1 t) lst)))
>     where h1 t (ix, iy, vx, vy) = (ix+vx*t, iy+vy*t)
> 
> gcnts :: IO [Double]
> gcnts = do
>           line <- getLine
>           return (map read (words line))
> 
> ecase :: Double -> IO ()
> ecase cnt
>   | cnt == 0 = do return ()
>   | otherwise = do (n:t:[]) <- gcnts
>                    pts <- gvecs n
>                    execute 1 (t + 1) pts
>                    ecase (cnt - 1)
> 
> gvecs :: Double -> IO [(Double, Double, Double, Double)]
> gvecs n
>   | n == 0 = do return ([])
>   | otherwise = do  (ix:iy:vx:vy:[]) <- gcnts
>                     nex <- gvecs (n-1)
>                     return ((ix, iy, vx, vy):nex)
> 
> execute :: Double -> Double -> [(Double, Double, Double, Double)] -> IO ()
> execute ct tt lsts
>    | ct == tt = do return ()
>    | otherwise = do putStrLn (show (solver ct lsts))
>                     execute (ct + 1) tt lsts
> 
> main :: IO ()
> main = do
>           (t:[]) <- gcnts
>           ecase t


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



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

Message: 2
Date: Mon, 9 Aug 2010 12:03:15 +0200
From: Johan Tibell <johan.tib...@gmail.com>
Subject: [Haskell-beginners]    Re: Please take the State of Haskell,
        2010 survey
To: hask...@haskell.org, haskell-cafe <haskell-c...@haskell.org>,
        beginners <beginners@haskell.org>
Message-ID:
        <aanlkti=crwnraw0yw4bwhmfjbgvne_hezs_qbwrox...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Hi all,

On Mon, Aug 2, 2010 at 3:40 PM, Johan Tibell <johan.tib...@gmail.com> wrote:

> I've put together a quick, 9-question State of Haskell, 2010 survey:
>
>     http://blog.johantibell.com/2010/08/state-of-haskell-2010-survey.html
>
> The survey will hopefully give us some insight into how people use Haskell
> and perhaps also some ideas on how Haskell tools and libraries could be
> improved.
>

The results of this survey are now available:


http://blog.johantibell.com/2010/08/results-from-state-of-haskell-2010.html

P.S. Please direct replies to this email to haskell-c...@haskell.org.

Cheers,
Johan
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100809/4e7043c0/attachment-0001.html

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

Message: 3
Date: Mon, 9 Aug 2010 16:23:23 +0530 (IST)
From: 200901...@daiict.ac.in
Subject: Fwd: [Haskell-beginners] Optimization Problem
To: Beginners@haskell.org
Message-ID:
        <462902841.79073.1281351203061.javamail.javamailu...@localhost>
Content-Type: text/plain; charset=utf-8

You were right. I have changed the code to 

distance' :: Point →  Point →  Double
distance' (x1, y1) (x2, y2) = (x1 - x2)*(x1 - x2) + (y1 - y2)*(y1 - y2)

inDisc :: Disc →  Point →  Bool
inDisc (Disc r p1 _) p2 = (distance' p1 p2) ≤ r*r

There was not any performance improvement by changing ** to ^.
Why is * faster that **2 or ^2?

Note: The change reduced run time to 1.24 sec.

----- Original Message -----
From: "Brent Yorgey" <byor...@seas.upenn.edu>
To: beginners@haskell.org
Sent: Monday, August 9, 2010 3:14:43 PM
Subject: Re: [Haskell-beginners] Optimization Problem

I don't know all that much about profiling/optimization.  But one
simple thing occurs to me -- does it help to change inDisc to

  inDisc (Disc r p1 _) p2 = (distsqr p1 p2) <= r*r

  distsqr :: Point -> Point -> Double
  distsqr (x1, y1) (x2, y2) = (x1 - x2)^2 + (y1 - y2)^2

Then you avoid using sqrt.  Also there's no need to use ** since you
are taking a positive integral power.  (^2) will optimize to just a
single multiplication, whereas I have no idea what (**2) does, it's
probably much slower.

You could even store the square of the radius in Disc, then you also
avoid having to compute r*r every time.

-Brent

On Mon, Aug 09, 2010 at 01:16:54PM +0530, 200901...@daiict.ac.in wrote:
> Optimization Problem 
> 
> I am trying to make an algorithm which solves Smallest circle problem( http 
> ://en. wikipedia .org/ wiki /Smallest_circle_problem). 
> My code takes ~3.2 sec to solve ~500 data sets of 2000 points apiece. I need 
> it to be done in less than 1 sec. 
> After profiling it seems that ~1.76 (55%) sec goes to the inDisc function and 
> ~1 (32%) sec goes into gcnts . So I am trying 
> to optimize these parts of the code. 
> 
> -- is the point p2 is inside disc? 
> inDisc :: Disc -> Point -> Bool 
> inDisc (Disc r p1 _) p2 = (distance p1 p2) <= r 
> 
> -- gives the double values in one line 
> gcnts :: IO [Double] 
> gcnts = do 
> line <- getLine 
> return (map read (words line)) 
> 
> And data and point are 
> 
> -- (x, y) 
> type Point = (Double, Double) 
> 
> - radius, center, know points in the disc 
> data Disc = Disc Double Point [Point] 
> deriving (Show) 
> 
> The relevant profiler part: 
> COST CENTRE MODULE %time % alloc 
> 
> inDisc Main 55.0 0.0 
> gcnts Main 32.5 58.1 
> 
> individual inherited 
> COST CENTRE MODULE no. entries %time % alloc %time % alloc 
> inDisc Main 247 1237577 35.6 0.0 35.6 0.0 
> inDisc Main 244 527216 11.9 0.0 11.9 0.0 
> inDisc Main 241 214076 7.5 0.0 7.5 0.0 
> gcnts Main 235 8043 31.3 58.1 31.3 58.1 
> gcnts Main 233 10 1.3 0.0 1.3 0.0 
> gcnts Main 231 1 0.0 0.0 0.0 0.0 
> 
> I have attached my code and profiler output. 
> 
> BSRK Aditya . 

> import Data.List
> 
> type Point = (Double, Double)
> data Disc = Disc Double Point [Point]
>             deriving (Show)
> 
> getRad :: Disc -> Double
> getRad (Disc r _ _) = r
> 
> getPoints :: Disc -> [Point]
> getPoints (Disc _ _ ps) = ps
> 
> getCen :: Disc -> Point
> getCen (Disc _ p _) = p
> 
> midpoint :: Point -> Point -> Point
> midpoint (x1, y1) (x2, y2) = ((x1+x2)/2, (y1+y2)/2)
> 
> distance :: Point -> Point -> Double
> distance (x1, y1) (x2, y2) = sqrt((x1 - x2)**2 + (y1 - y2)**2)
> 
> inDisc :: Disc -> Point -> Bool
> inDisc (Disc r p1 _) p2 = (distance p1 p2) <= r
> 
> appendPoint :: Disc -> Point -> Disc
> appendPoint (Disc r p ps) p2 = (Disc r p (p2:ps))
> 
> circumCenter :: Point -> Point -> Point -> Point
> circumCenter (ax, ay) (bx, by) (cx, cy)
>     =  (((ay**2+ax**2)*(by-cy)+(by**2+bx**2)*(cy-ay)+(cy**2+cx**2)*(ay-by))/d,
>        ((ay**2+ax**2)*(cx-bx)+(by**2+bx**2)*(ax-cx)+(cy**2+cx**2)*(bx-ax))/d)
>        where d = 2*(ax*(by-cy)+bx*(cy-ay)+cx*(ay-by))
> 
> mround x = (fromIntegral (round (100*x)))/100
> -- the real code
> minDisc :: [Point] -> Disc
> minDisc (p1:p2:[]) = Disc ((distance p1 p2)/2) (midpoint p1 p2) (p1:p2:[])
> minDisc (p1:p2:ps) = foldl' helper (minDisc (p2:p1:[])) ps
>    where helper d p
>            | (inDisc d p) = (appendPoint d p)
>            | otherwise = (minDiscwp (getPoints d) p)
> minDisc _ = Disc 0 (0, 0) []
> 
> minDiscwp :: [Point] -> Point -> Disc
> minDiscwp ps q = foldl' (helper q) (minDisc ((head ps):q:[])) (tail ps)
>     where helper q d p
>            | (inDisc d p) = (appendPoint d p)
>            | otherwise = (minDiscwp2 (init (getPoints d)) p q)
> 
> minDiscwp2 :: [Point] -> Point -> Point -> Disc
> minDiscwp2 ps q1 q2 = foldl' (helper q1 q2) (minDisc (q1:q2:[])) ps
>     where helper q1 q2 d p
>            | (inDisc d p) = (appendPoint d p)
>            | otherwise = Disc (distance cr p) cr (p:(getPoints d))
>                where cr = circumCenter q1 q2 p
> --IO
> 
> solver :: Double -> [(Double, Double, Double, Double)] -> Double
> solver t lst =  mround(getRad (minDisc (map (h1 t) lst)))
>     where h1 t (ix, iy, vx, vy) = (ix+vx*t, iy+vy*t)
> 
> gcnts :: IO [Double]
> gcnts = do
>           line <- getLine
>           return (map read (words line))
> 
> ecase :: Double -> IO ()
> ecase cnt
>   | cnt == 0 = do return ()
>   | otherwise = do (n:t:[]) <- gcnts
>                    pts <- gvecs n
>                    execute 1 (t + 1) pts
>                    ecase (cnt - 1)
> 
> gvecs :: Double -> IO [(Double, Double, Double, Double)]
> gvecs n
>   | n == 0 = do return ([])
>   | otherwise = do  (ix:iy:vx:vy:[]) <- gcnts
>                     nex <- gvecs (n-1)
>                     return ((ix, iy, vx, vy):nex)
> 
> execute :: Double -> Double -> [(Double, Double, Double, Double)] -> IO ()
> execute ct tt lsts
>    | ct == tt = do return ()
>    | otherwise = do putStrLn (show (solver ct lsts))
>                     execute (ct + 1) tt lsts
> 
> main :: IO ()
> main = do
>           (t:[]) <- gcnts
>           ecase t


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

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


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

Message: 4
Date: Mon, 9 Aug 2010 11:17:52 -0500
From: Wayne R <reginald.wayne.richa...@gmail.com>
Subject: [Haskell-beginners] FastCGI error
To: beginners@haskell.org
Message-ID:
        <aanlkti=qjjkajqd4qwxkszugownk6gq=va602qsns...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I'm trying to use Network.FastCGI with Apache2, but running into an error.
I'd like to believe that the web server is configured correctly, because I
can successfully view the following, compiled to <web
root>/fastcgi/test.fcgi:

#include <fcgi_stdio.h>

int main(void){
  int count = 0;
  while(FCGI_Accept()>=0){
   printf("Content-Type: text/html\r\n");
   printf("\r\n");
   printf("Hello, World: %d", count++);
  }
  return 0;
}

Now I compile Fcgi.hs to <web root>/fastcgi/test2.fcgi:

import Control.Concurrent
import Network.FastCGI

action :: CGI CGIResult
action = do
        setHeader "Content-type" "text/plain"
        tid <- liftIO myThreadId
        output $ unlines
            [ "I am a FastCGI process!"
            , "Hear me roar!"
            , ""
            , show tid
            ]

main = runFastCGIConcurrent' forkIO 10 action


When I view localhost/fastcgi/test.fcgi, I get the hello world page, but
attempting to view test2.fcgi shows an 'Internal Server Error" in firefox.
The apache error log says:

[Sun Aug 08 07:44:17 2010] [notice] Apache/2.2.14 (Ubuntu) mod_fastcgi/2.4.6
mod_lisp2/1.3.1 PHP/5.3.2-1ubuntu4.2 with Suhosin-Patch mod_ssl/2.2.14
OpenSSL/0.9.8k configured -- resuming normal operations
[Mon Aug 09 11:11:23 2010] [warn] FastCGI: (dynamic) server
"/var/www/fastcgi/test.fcgi" started (pid 20354)
[Mon Aug 09 11:11:27 2010] [warn] FastCGI: (dynamic) server
"/var/www/fastcgi/test2.fcgi" started (pid 20360)
[Mon Aug 09 11:11:31 2010] [warn] FastCGI: (dynamic) server
"/var/www/fastcgi/test2.fcgi" started (pid 20365)
[Mon Aug 09 11:11:34 2010] [warn] FastCGI: (dynamic) server
"/var/www/fastcgi/test2.fcgi" started (pid 20371)
[Mon Aug 09 11:11:37 2010] [warn] FastCGI: (dynamic) server
"/var/www/fastcgi/test2.fcgi" started (pid 20375)
[Mon Aug 09 11:11:40 2010] [warn] FastCGI: (dynamic) server
"/var/www/fastcgi/test2.fcgi" started (pid 20379)
[Mon Aug 09 11:11:43 2010] [warn] FastCGI: (dynamic) server
"/var/www/fastcgi/test2.fcgi" started (pid 20383)
[Mon Aug 09 11:11:46 2010] [warn] FastCGI: (dynamic) server
"/var/www/fastcgi/test2.fcgi" started (pid 20387)
[Mon Aug 09 11:11:49 2010] [warn] FastCGI: (dynamic) server
"/var/www/fastcgi/test2.fcgi" started (pid 20391)
[Mon Aug 09 11:11:52 2010] [warn] FastCGI: (dynamic) server
"/var/www/fastcgi/test2.fcgi" started (pid 20395)
[Mon Aug 09 11:11:55 2010] [warn] FastCGI: scheduled the start of the last
(dynamic) server "/var/www/fastcgi/test2.fcgi" process: reached
dynamicMaxClassProcs (10)
[Mon Aug 09 11:11:55 2010] [warn] FastCGI: (dynamic) server
"/var/www/fastcgi/test2.fcgi" started (pid 20399)
[Mon Aug 09 11:12:01 2010] [error] [client 127.0.0.1] FastCGI: comm with
(dynamic) server "/var/www/fastcgi/test2.fcgi" aborted: (first read) idle
timeout (30 sec)
[Mon Aug 09 11:12:01 2010] [error] [client 127.0.0.1] FastCGI: incomplete
headers (0 bytes) received from server "/var/www/fastcgi/test2.fcgi"

I've tried Fcgi.hs with two different sample FastCGI programs with the same
results.  Any suggestions?

Wayne
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100809/b7cd406e/attachment.html

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

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


End of Beginners Digest, Vol 26, Issue 20
*****************************************

Reply via email to