[Haskell-cafe] Do expression definition

2010-09-13 Thread Alexander Kotelnikov
Hello.

http://www.haskell.org/onlinereport/exps.html#sect3.14 a obscure (to me) note 
which says

"As indicated by the translation of do, variables bound by let have fully 
polymorphic types while those defined by <- are lambda bound and are thus 
monomorphic."

What actually does it mean?

And, also, would it make any difference if


do {p <- e; stmts}  =   let ok p = do {stmts}
ok _ = fail "..."
  in e >>= ok

is redefined as "e >>= (\p -> do {stmts})"?

Thanks, Alexander

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] bug in Network.Browser

2010-08-15 Thread Alexander Kotelnikov
Hello.

Yesterday I hit a bug in Network.Browser: connection in the connection
pool is not reused if you are connecting to a destination with
qualified port (not 80 for HTTP or 80 but explicitly provided like
http://www.google.com:80). The reason for the failure is quite trivial,
but I had not found an easy fix which won't break anything.


Problem is that in TCP.hs function

isTCPConnectedTo :: HandleStream ty -> String -> IO Bool
isTCPConnectedTo conn name = do
   v <- readMVar (getRef conn)
   case v of
 ConnClosed -> return False
 _
  | map toLower (connHost v) == map toLower name ->
  catch (getPeerName (connSock v) >> return True) (const $ return False)
  | otherwise -> return False

socket's hostname, (connHost v) is compared to hostname or hostname:port
which is stored in name.

Hope this message will reach this code maintainers

Alexander

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Odd parallel haskell observations (some more numbers)

2010-08-09 Thread Alexander Kotelnikov
Hi.

> On Mon, 9 Aug 2010 09:44:00 +0200
> "JG" == Jean-Marie Gaillourdet  wrote:
JG> 
JG> I am no expert in web server tuning, but I will share my thoughts
JG> about your approach and expectations nevertheless.

I would better think about ghc than about web server. I believe, that
numbers I already provided (especially their deviation) illustrate that
sometimes ghc runtime perform quite bad. 

I also found out that it can do better than it does by default, I can
accept that runtime might be not capable to adjust itself to any taks
the best way, but then it will be nice to know, for instance, why for
such I/O that GC settings change performance in times.

To illustrate even more that httpd has nothing to do with the phenomenon
I wrote a small C application which does pretty much the same. Numbers
tells that apache can serve much faster that it was required to please
haskell version (I will remind that it was 3.4 for single-threaded
haskell and went as low as 1.9s for 4-threaded). I attached the code
just in case.

10:27 sa...@loft4633:~/work/cube-server/tests 99> for i in 1 2 3 4; do for j in 
`seq 1 5`;do ./getc $i 1;done;done
1 1.352978
1 1.34
1 1.344545
1 1.345116
1 1.189060
2 0.668219
2 0.625113
2 0.698073
2 0.732621
2 0.722310
3 0.569121
3 0.581570
3 0.563512
3 0.566186
3 0.564232
4 0.510132
4 0.496181
4 0.529212
4 0.504506
4 0.511847

# include 
# include 
# include 
# include 
# include 
# include 

# include 
# include 
 #include 

int fib(int n) {
  if ( n > 1 )
return fib(n-1) + fib(n-2);
  else
return 1;
}

# define REQ "GET / HTTP/1.1\r\n\r\n"

int get() {
  int s;
  int n;
  struct sockaddr_in sa;
  struct in_addr ia;
  char buf[1];

  sa.sin_family = AF_INET;
  if ( !inet_pton(AF_INET, "127.0.0.1", &ia) ) {
fprintf(stderr, "inet_pton\n");
exit(1);
  }
  else {
sa.sin_addr.s_addr = ia.s_addr;
  }
  sa.sin_port = htons(80);

  s = socket(AF_INET, SOCK_STREAM, 0);
  n = connect(s, (struct sockaddr*)&sa, sizeof(sa));

  send(s, REQ, strlen(REQ), 0);
  while ( (n = recv(s, buf, 1, 0)) > 0 );
  //printf("%d\n", fib(38));
  close (s);
  return 0;
}

void* nget(void* p){
  int i;
  int n = *(int*)p;
  for ( i = 0; i < n; i++ )
get();
  return NULL;
}

int main(int argc, char* argv[]) {
  int c;
  int n;
  int p;
  int i;
  double run_time;
  struct timeval start;
  struct timeval end;
  
  c = strtol(argv[1], NULL, 10);
  n = strtol(argv[2], NULL, 10);
  p = n/c;

  pthread_t *thread_ids;

  thread_ids = (pthread_t*)malloc(sizeof(pthread_t*) * c);

  gettimeofday(&start, NULL);
  for (i = 0; i < c; i++) {
pthread_create(&thread_ids[i], NULL, nget, &p);
  }

  for (i = 0; i < c; i++) {
pthread_join(thread_ids[i], NULL);
  }
  gettimeofday(&end, NULL);
  
  run_time = end.tv_sec - start.tv_sec + 1e-6 * (end.tv_usec - start.tv_usec);
  printf("%d %f\n", c, run_time);
  return 0;
}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Typo or on purpose? http://haskell.org/ghc/docs/6.12.2/html/users_guide/lang-parallel.html

2010-08-08 Thread Alexander Kotelnikov
This + 1 in (n1 + n2 + 1) what is it doing there?

import Control.Parallel

nfib :: Int -> Int
nfib n | n <= 1 = 1
   | otherwise = par n1 (pseq n2 (n1 + n2 + 1))
 where n1 = nfib (n-1)
   n2 = nfib (n-2)

BTW, same code can be found in "Seq no more: Better Strategies for
Parallel Haskell" article.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Odd parallel haskell observations

2010-08-07 Thread Alexander Kotelnikov
Hello.

I am exploring haskell features for parallel and cocurrent programming
and see something difficult to explain.

In brief - asking RTS to use more threads results in awfull drop of
performance. And according to 'top'  test programm consumes up to N CPUs
power.

Am I doing something wrong? I attached the code, but I am just issuing
thousands of HTTP GET requests in 1-4 forkIO threads. And since it looks
like local apache is faster than haskell program (which is a pity) I
expected that using more OS threads should improve performance.

Just in case:
ghc --version
The Glorious Glasgow Haskell Compilation System, version 6.12.1


import Data.List
import System.IO
import qualified System.IO.UTF8
import System.Environment (getArgs)
import Network.HTTP
import Network.URI
import System.Time
import System.IO.Unsafe
import Control.Monad
import Control.Exception
import Control.Concurrent
import Control.Concurrent.MVar

secDiff :: ClockTime -> ClockTime -> Float
secDiff (TOD secs1 psecs1) (TOD secs2 psecs2) =
fromInteger (psecs2 - psecs1) / 1e12 + fromInteger (secs2 - secs1)

-- single get
get :: Int -> IO(String)
get id = do
  res <- simpleHTTP $ getRequest "http://127.0.0.1";
  case res of
Left err -> return(show err)
Right rsp -> return(show $ rspCode rsp)


-- perform GET per each list element using c threads
doList :: [Int] -> Int -> IO()
doList ids 0 =
return()

doList [] c =
return()

doList ids c = do
forkChild $ forM_ todo get
doList later (c-1)
where (todo, later) = splitAt (length ids `div` c) ids

{-
Copied from
http://haskell.org/ghc/docs/6.12.2/html/libraries/base-4.2.0.1/Control-Concurrent.html#11
Terminating the program
-}
children :: MVar [MVar ()]
children = unsafePerformIO (newMVar [])

waitForChildren :: IO ()
waitForChildren = do
  cs <- takeMVar children
  case cs of
[]   -> return ()
m:ms -> do
putMVar children ms
takeMVar m
waitForChildren

forkChild :: IO () -> IO ThreadId
forkChild io = do
  mvar <- newEmptyMVar
  childs <- takeMVar children
  putMVar children (mvar:childs)
  forkIO (io `finally` putMVar mvar ())
-- end of copied code

main = do
  [c', n'] <- getArgs
  let 
  c = read c' :: Int
  n = read n' :: Int
  start <- getClockTime
  doList [1..n] c
  waitForChildren
  end <- getClockTime
  putStrLn $ show(c) ++ " " ++ show(secDiff start end) ++ "s"


20:31 sa...@loft4633:/tmp 21> ghc --make -threaded get.hs
[1 of 1] Compiling Main ( get.hs, get.o )
Linking get ...
20:31 sa...@loft4633:/tmp 22> ./get 1 1
1 3.242352s
20:31 sa...@loft4633:/tmp 23> ./get 2 1
2 3.08306s
20:31 sa...@loft4633:/tmp 24> ./get 2 1 +RTS -N2
2 6.898871s
20:32 sa...@loft4633:/tmp 25> ./get 3 1
3 2.950677s
20:32 sa...@loft4633:/tmp 26> ./get 3 1 +RTS -N2
3 7.381678s
20:32 sa...@loft4633:/tmp 27> ./get 3 1 +RTS -N3
3 14.683548s
20:32 sa...@loft4633:/tmp 28> ./get 4 1
4 3.332165s
20:33 sa...@loft4633:/tmp 29> ./get 4 1 +RTS -N4 -s
./get 4 1 +RTS -N4 -s
4 57.17923s
   2,147,969,912 bytes allocated in the heap
  49,059,288 bytes copied during GC
 736,656 bytes maximum residency (98 sample(s))
 486,744 bytes maximum slop
   5 MB total memory in use (0 MB lost due to fragmentation)

  Generation 0:   949 collections,   948 parallel, 76.73s, 25.67s elapsed
  Generation 1:98 collections,98 parallel,  7.70s,  2.56s elapsed

  Parallel GC work balance: 2.17 (6115428 / 2822692, ideal 4)

MUT time (elapsed)   GC time  (elapsed)
  Task  0 (worker) :1.43s( 27.76s)   6.31s(  2.12s)
  Task  1 (worker) :0.00s( 28.13s)  10.62s(  3.56s)
  Task  2 (worker) :0.37s( 28.63s)  11.06s(  3.69s)
  Task  3 (worker) :0.00s( 28.95s)   6.29s(  2.10s)
  Task  4 (worker) :   20.73s( 28.95s)   9.68s(  3.24s)
  Task  5 (worker) :0.00s( 28.95s)   0.60s(  0.20s)
  Task  6 (worker) :   21.81s( 28.95s)  11.91s(  3.97s)
  Task  7 (worker) :   18.59s( 28.95s)  13.04s(  4.36s)
  Task  8 (worker) :   17.24s( 28.96s)  14.92s(  4.99s)

  SPARKS: 0 (0 converted, 0 pruned)

  INIT  time0.00s  (  0.00s elapsed)
  MUT   time   79.23s  ( 28.95s elapsed)
  GCtime   84.43s  ( 28.23s elapsed)
  EXIT  time0.00s  (  0.01s elapsed)
  Total time  162.49s  ( 57.19s elapsed)

  %GC time  52.0%  (49.4% elapsed)

  Alloc rate27,513,782 bytes per MUT second

  Productivity  48.0% of total user, 136.5% of total elapsed

gc_alloc_block_sync: 15006
whitehole_spin: 0
gen[0].steps[0].sync_large_objects: 7617
gen[0].steps[1].sync_large_objects: 35
gen[1].steps[0].sync_large_objects: 1400
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: src/Text/XML/HaXml/Lex.hs:(156, 0)-(160, 22): Non-exhaustive patterns in function white

2010-07-21 Thread Alexander Kotelnikov
So updated to HaXml 1.20, haxr 3000.7

Simple calls (which deal with simple data types as integer or regular
string) still work.

Calls which successfully returned some binary data before do not do so
anymore. The error is:
Prelude.chr: bad argument: 1177427

Calls which complained about 'white' function now fail with:
precondition not satisfied: Posn.white c | isSpace c


My guess is that XML parser is not ready (and from XML standpoint it
might be right) that XML-RPC tries to transfer binary data as its
.

Alexander


> On Wed, 21 Jul 2010 06:04:58 -0700 (PDT)
> "mw" == malcolm wallace  wrote:
mw> 
mw> 
Ouch... I
mw>   check the version and realized that
mw>   Debian/unstable has  
version
mw>   1.13 of haxml.  
mw>   Malcolm, can you comment this Debian
mw>   changelog entry with which Debian 
 package
mw>   was downgraded from 1.19 to 1.13:
mw> 
mw>  
mw> I know nothing about Debian packaging, but it sounds like there are other 
packages that depend on
mw> the old version of HaXml, which have not yet been updated to use the 
current, slightly modified,
mw> API.  Since the new API has been available for about 4 years now, and 
officially stable for the
mw> last six months (although in fact it changed very little in those four 
years), I think it is high
mw> time those other packages were updated.
mw> Regards,
mw>  Malcolm

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: src/Text/XML/HaXml/Lex.hs:(156, 0)-(160, 22): Non-exhaustive patterns in function white

2010-07-21 Thread Alexander Kotelnikov
>>>>> On Wed, 21 Jul 2010 01:40:08 -0700 (PDT)
>>>>> "mw" == malcolm wallace  wrote:
mw> 
mw> Judging solely by the error message (non-exhaustive patterns in
mw> 'white'), it sounds like it could be a bug in HaXml that was fixed
mw> in a patch of April 2009.  Try using a more recent release of
mw> HaXml.

Ouch... I check the version and realized that Debian/unstable has
version 1.13 of haxml.

Malcolm, can you comment this Debian changelog entry with which Debian
package was downgraded from 1.19 to 1.13:

haxml (1:1.13.3-1) unstable; urgency=low

  * Switch back to the latest stable release of haxml, as to not break its
reverse build dependencies
  * Thus do not depend on polyparse, remove patch adjusting the polyparse
dependency.
  * Remove patches/09_fix-lexical-error, does not apply to this version of
HaXml

 -- Joachim Breitner   Tue, 15 Sep 2009 16:26:10 +0200


-- 
Alexander Kotelnikov
Saint-Petersburg, Russia

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: src/Text/XML/HaXml/Lex.hs:(156, 0)-(160, 22): Non-exhaustive patterns in function white

2010-07-21 Thread Alexander Kotelnikov
>>>>> On Wed, 21 Jul 2010 06:46:26 + (UTC)
>>>>> "GP" == Gracjan Polak  wrote:
GP> 
GP> Antoine Latter  gmail.com> writes:
>> Sending off to the maintainer of haxr, although it looks like it might
>> be in HaXml (from an outside guess).
GP> 
GP> Without some real example to look at it will be quite tough to proceed.
GP> 
GP> Alexander, can you send that stream of packets to me?

I attach a stream dump.



poster.dump
Description: Binary data

-- 
Alexander Kotelnikov
Saint-Petersburg, Russia
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] src/Text/XML/HaXml/Lex.hs:(156, 0)-(160, 22): Non-exhaustive patterns in function white

2010-07-20 Thread Alexander Kotelnikov
Hello.

I decided to run a couple of test XML-RPC applications using haxr.

Everything worked fine while responces from my (actually, other
people's) server were something relatively small (a number, a line), but
with larger responces (starting around couple of kilobytes) my
applications began to fail with the error I put into subject.

Sounds like XML parsing problem. Though server gives a proper responce
(I used tcpdump to see what is returned, looks like a valid XML with
methodResponce).

Any idea what is wrong and how this can be fixed?


Thanks,
Alexander




___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: simple hsql question

2009-08-17 Thread Alexander Kotelnikov
Ok, let me ask it in another way. Is there a good way to access
databases, mysql in particular, from haskell program?

>>>>> On Sun, 16 Aug 2009 18:54:32 +0400
>>>>> "AK" == Alexander Kotelnikov  wrote:
AK> 
AK> Hi
AK> I wanted to see what access to databases HSQL provides and I stumbled in
AK> the very beginning. Assume I have a table map1 with attributes "i" and "s"
AK> interger and varchar() respectively. The following code fails (with
AK> segfault) for me. And I see no other way to tell compiler that I am
AK> expecting an interger to be found as 'i' in a fetched row.
AK> 
AK> import Database.HSQL
AK> import Database.HSQL.MySQL
AK> 
AK> main :: IO ()
AK> main = do
AK> c <- connect "localhost" "tx_test" "sacha" ""
AK> s <- query c "SELECT i FROM map1"
AK> print $ getFieldsTypes s
AK> i <- (getFieldValue s "i")::IO Int
AK> print i
AK> disconnect c
AK> 
AK> -- 
AK> Alexander Kotelnikov
AK> Saint-Petersburg, Russia
AK> 
-- 
Alexander Kotelnikov
Saint-Petersburg, Russia

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] simple hsql question

2009-08-16 Thread Alexander Kotelnikov
Hi

I wanted to see what access to databases HSQL provides and I stumbled in
the very beginning. Assume I have a table map1 with attributes "i" and "s"
interger and varchar() respectively. The following code fails (with
segfault) for me. And I see no other way to tell compiler that I am
expecting an interger to be found as 'i' in a fetched row.

import Database.HSQL
import Database.HSQL.MySQL

main :: IO ()
main = do
c <- connect "localhost" "tx_test" "sacha" ""
s <- query c "SELECT i FROM map1"
print $ getFieldsTypes s
i <- (getFieldValue s "i")::IO Int
print i
disconnect c

-- 
Alexander Kotelnikov
Saint-Petersburg, Russia

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe