Hi D.R Plotkin,
There are some nice mailing lists in haskell.org, include HUGS
--- On Sat, 2/21/09, haskell-cafe-request@haskell.org wrote:
From: haskell-cafe-request@haskell.org
Subject: Haskell-Cafe Digest, Vol 66, Issue 71
To: haskell-cafe@haskell.org
Date: Saturday, February 21, 2009, 7:01 PM
Send Haskell-Cafe mailing list submissions to
haskell-cafe@haskell.org
To subscribe or unsubscribe via the World Wide Web, visit
http://www.haskell.org/mailman/listinfo/haskell-cafe
or, via email, send a message with subject or body 'help' to
haskell-cafe-request@haskell.org
You can reach the person managing the list at
haskell-cafe-owner@haskell.org
When replying, please edit your Subject line so it is more specific
than "Re: Contents of Haskell-Cafe digest..."
Today's Topics:
1. controlling timeout for Network.Socket.connect - how? (Belka)
2. Stacking StateTs (Luis O'Shea)
3. Haskellers on Twitter! (Daniel Peebles)
4. Fwd: Re: [Haskell-cafe] speed: ghc vs gcc (Khudyakov Alexey)
5. Re: Fwd: Re: [Haskell-cafe] speed: ghc vs gcc (Bulat Ziganshin)
6. Re[3]: [Haskell-cafe] Re: speed: ghc vs gcc (Bulat Ziganshin)
7. Re: Re[3]: [Haskell-cafe] Re: speed: ghc vs gcc (Louis Wasserman)
8. Re: Re: speed: ghc vs gcc (Daniel Fischer)
9. Re[5]: [Haskell-cafe] Re: speed: ghc vs gcc (Bulat Ziganshin)
10. Re: Stacking StateTs (David Menendez)
11. Re[2]: [Haskell-cafe] Re: speed: ghc vs gcc (Bulat Ziganshin)
12. Re: Re[5]: [Haskell-cafe] Re: speed: ghc vs gcc (Louis Wasserman)
13. Re: Re[5]: [Haskell-cafe] Re: speed: ghc vs gcc (Sebastian Sylvan)
14. Re: Help using catch in 6.10 (John Meacham)
15. Re: Re[5]: [Haskell-cafe] Re: speed: ghc vs gcc (Louis Wasserman)
16. The community is more important than the product (Don Stewart)
17. Re: Re[5]: [Haskell-cafe] Re: speed: ghc vs gcc (Sebastian Sylvan)
18. Re: Re: speed: ghc vs gcc (Daniel Fischer)
19. Re[7]: [Haskell-cafe] Re: speed: ghc vs gcc (Bulat Ziganshin)
20. Template Haskell compilation error on Windows (was Re: speed:
ghc vs gcc) (Peter Verswyvelen)
----------------------------------------------------------------------
Message: 1
Date: Sat, 21 Feb 2009 11:26:51 -0800 (PST)
From: Belka
Subject: [Haskell-cafe] controlling timeout for Network.Socket.connect
- how?
To: haskell-cafe@haskell.org
Message-ID: <22139581.post@talk.nabble.com>
Content-Type: text/plain; charset=us-ascii
Hello, communion people!
I have a problem and ask for an advice.
I'm dealing with sockets on *Linux* platform (Network.Socket). The problem
is that I can't fully control timeout for (connect :: Socket -> SockAddr
->
IO ()) operation.
On my system the timeout is - 3 seconds - I want to be able to change that
in run-time. Well I managed to find out how to make it LESS THAN 3 seconds -
using System.Timeout. But how to make timeout bigger (for example 9 seconds)
is a mystery.
(Notice: in order to achieve 9 seconds timeout - just repeating *connect* 3
times won't be effective for long-slow-way-connections. So it's not a
solution.)
The source code of Network.Socket.connect, taken from darcs:
---------------------------------
-- Connecting a socket
--
-- Make a connection to an already opened socket on a given machine
-- and port. assumes that we have already called createSocket,
-- otherwise it will fail.
--
-- This is the dual to $bindSocket$. The {\em server} process will
-- usually bind to a port number, the {\em client} will then connect
-- to the same port number. Port numbers of user applications are
-- normally agreed in advance, otherwise we must rely on some meta
-- protocol for telling the other side what port number we have been
-- allocated.
connect :: Socket -- Unconnected Socket
-> SockAddr -- Socket address stuff
-> IO ()
connect sock@(MkSocket s _family _stype _protocol socketStatus) addr = do
modifyMVar_ socketStatus $ \currentStatus -> do
if currentStatus /= NotConnected
then
ioError (userError ("connect: can't peform connect on socket in
status "
++
show currentStatus))
else do
withSockAddr addr $ \p_addr sz -> do
let connectLoop = do
r <- c_connect s p_addr (fromIntegral sz)
if r == -1
then do
rc <- c_getLastError
case rc of
10093 -> do -- WSANOTINITIALISED
withSocketsDo (return ())
r <- c_connect s p_addr (fromIntegral sz)
if r == -1
then (c_getLastError >>= throwSocketError "connect")
else return r
_ -> throwSocketError "connect" rc
else return r
connectBlocked = do
#if !defined(__HUGS__)
threadWaitWrite (fromIntegral s)
#endif
err <- getSocketOption sock SoError
if (err == 0)
then return 0
else do ioError (errnoToIOError "connect"
(Errno (fromIntegral err))
Nothing Nothing)
connectLoop
return Connected
---------------------------------
I know that controlling timeout is somehow connected to select(2) (I'm
currently investigating this matter...), but it's not in the Network or
Network.Socket libs (but in the libs that they FFI with).
Hope I won't have to rewrite these low-level functions.... >__<
Could anybody, please share some experience on how to adjust timeout for
*connect*?
Thanks in advance,
Best regards,
Belka
--
View this message in context:
http://www.nabble.com/controlling-timeout-for-Network.Socket.connect---how--...
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.
------------------------------
Message: 2
Date: Sat, 21 Feb 2009 15:33:28 -0500
From: Luis O'Shea
Subject: [Haskell-cafe] Stacking StateTs
To: haskell-cafe@haskell.org
Message-ID: <3636FA2B-5BB1-47CC-B20F-85491A55E4F7@gmail.com>
Content-Type: text/plain; charset=US-ASCII; delsp=yes; format=flowed
I've been experimenting with the state monad and with StateT, and
have some questions about how to combine one state with another.
This email is literate Haskell tested on GHCi, version 6.10.1. Also,
sigfpe's post on monad transformers (http://blog.sigfpe.com/2006/05/
grok-haskell-monad-transformers.html) was very helpful.
import Control.Monad.State
My question is basically whether the function modifyT (below) makes
sense, whether some form of it already exists in a standard library,
and (most importantly) whether it actually indicates that I'm
thinking about StateT all wrong.
modifyT :: Monad m =>
(s -> StateT t m s)
-> StateT t (StateT s m) ()
modifyT f = do
x <- get
y <- lift get
(y',x') <- lift $ lift $ runStateT (f y) x
lift $ put y'
put x'
Some context may be useful, so here is how I ended up thinking I
needed modifyT.
The state monad makes it easy to write stateful computations. For
example here is a computation that has an Integer as its state and
returns a String:
test1 :: State Integer String
test1 = do
modify (+ 1)
a <- get
return $ "foobar" ++ (show a)
If the computation wants to do some IO then it makes sense to start
with the IO monad and then apply the StateT transformer to it:
test2 :: StateT Integer IO String
test2 = do
modify (+ 1)
a <- get
lift $ print a
return $ "foobar" ++ (show a)
So from now on I won't actually do any IO and will replace IO with an
arbitrary monad m. Also instead of the fixed string "foobar"
I'll
have it take a String as a parameter:
test3 :: Monad m => String -> StateT Integer m String
test3 s = do
modify (+ 1)
a <- get
return $ s ++ (show a)
A nice feature of all this is that it is easy to combine these
computations:
test4 :: Monad m => StateT Integer m (String,String)
test4 = do
s1 <- test3 "foo"
s2 <- test3 "bar"
return $ (s1,s2)
Now seeing as test3 takes a String and returns another String you can
imagine using it to transform a String state. (I'm also going to
assume that test3 is in another library so we don't want to alter how
it's written.) So here is how you could use test3 in a computation
that has (String,Integer) as its state:
test5 :: (Monad m) => m Integer
test5 = do
(s1,x1) <- runStateT (test3 "") 0
(s2,x2) <- runStateT (test3 s1) (2*x1 + 1)
(s3,x3) <- runStateT (test3 s2) (x2*x2)
return x3
Then running test5 >>= print gives 17. The problem with test5, of
course, is that we have manually threaded the state, with all the
problems that implies. For example nothing prevents you from
erroneously misthreading the state:
test5bad :: (Monad m) => m Integer
test5bad = do
(s1,x1) <- runStateT (test3 "") 0
(s2,x2) <- runStateT (test3 s1) (2*x1 + 1)
(s3,x3) <- runStateT (test3 s1) (x2*x1)
return x3
Running test5bad >>= print gives 5. Obviously we want operate in a
State monad with more state. One way to do this is to stack two
StateTs on top of m. This is, finally, where I need the modifyT that
we defined above -- it lets us "lift" test3 to a function that
modifies the state of the top *two* StateTs. Now let's use it to
rewrite test5:
test6 :: (Monad m) => StateT Integer (StateT String m) Integer
test6 = do
modifyT test3
modify $ \x -> 2*x + 1
modifyT test3
modify $ \x -> x*x
modifyT test3
x <- get
return x
test7 :: (Monad m) => m Integer
test7 = evalStateT (evalStateT test6 0) ""
As expected, running test7 >>= print gives 17.
So, given that modifyT seems to be useful, does it, or something like
it, already exists in the standard libraries? More likely, am I
making a mountain of a molehill and is there a better way to
structure all this?
Thanks,
Luis
main = do
test5 >>= print
test5bad >>= print
test7 >>= print
------------------------------
Message: 3
Date: Sat, 21 Feb 2009 16:14:15 -0500
From: Daniel Peebles
Subject: [Haskell-cafe] Haskellers on Twitter!
To: haskell-cafe@haskell.org
Message-ID:
Content-Type: text/plain; charset=UTF-8
Hi all,
I liked Brian O'Sullivan's blog post on twitter
(http://www.serpentine.com/blog/2008/12/05/functional-programmers-on-twitter/),
so I moved the Haskell subset of his list (along with a couple of
additions) onto the haskell wiki, to make it easier for people to
update. You can find the page at
http://haskell.org/haskellwiki/Twitter. Please update with yourself or
any other Haskellers we may have missed.
Cheers,
Dan
------------------------------
Message: 4
Date: Sun, 22 Feb 2009 00:58:59 +0300
From: Khudyakov Alexey
Subject: Fwd: Re: [Haskell-cafe] speed: ghc vs gcc
To: haskell-cafe@haskell.org
Message-ID: <200902220058.59198.alexey.skladnoy@gmail.com>
Content-Type: Text/Plain; charset="iso-8859-1"
Oh I've again sent mail to wrong address
---------- Forwarded Message ----------
On Saturday 21 February 2009 02:42:11 you wrote:
On Sat, Feb 21, 2009 at 12:22 AM, Bulat Ziganshin
wrote:
Hello Khudyakov,
Saturday, February 21, 2009, 2:07:39 AM, you wrote:
I have another question. Why shouldn't compiler realize that
`sum
[1..10^9]'
is constant and thus evaluate it at compile time?
since we expect that compilation will be done in reasonable amount of
time. you cannot guarantee this for list-involving computation
it would be nice to have a compiler that can run forever, incrementally
generating faster and faster versions of the same program, until you press
a key or a timeout is reached.
then you just let it run before you get to bed ;-)
you could even pass it in a test data set to which it must be optimized;
after the program is compiled, the compiler runs and profiles it, measures
the results, and does another pass to make it faster.
I've just remembered another but related approach to optimization. It uses
genetic algorithm to determine close to the best set of optimization options.
Alternatively it could be used to find badly interacting options,
pessimizations.
Implementation for gcc is here:
http://www.coyotegulch.com/products/acovea/
In fact I didn't tried it but I liked the idea.
--
Khudaykov Alexey
------------------------------
Message: 5
Date: Sun, 22 Feb 2009 01:09:23 +0300
From: Bulat Ziganshin
Subject: Re: Fwd: Re: [Haskell-cafe] speed: ghc vs gcc
To: Khudyakov Alexey
Cc: haskell-cafe@haskell.org
Message-ID: <528706754.20090222010923@gmail.com>
Content-Type: text/plain; charset=us-ascii
Hello Khudyakov,
Sunday, February 22, 2009, 12:58:59 AM, you wrote:
you could even pass it in a test data set to which it must be
optimized;
after the program is compiled, the compiler runs and profiles it,
measures
the results, and does another pass to make it faster.
I've just remembered another but related approach to optimization. It
uses
genetic algorithm to determine close to the best set of optimization
it supported in gcc4 and icl at least
options.
afaik it used widely for tuning parameters of compression algorithms
--
Best regards,
Bulat mailto:Bulat.Ziganshin@gmail.com
------------------------------
Message: 6
Date: Sun, 22 Feb 2009 02:21:09 +0300
From: Bulat Ziganshin
Subject: Re[3]: [Haskell-cafe] Re: speed: ghc vs gcc
To: Louis Wasserman
Cc: haskell-cafe@haskell.org
Message-ID: <989437740.20090222022109@gmail.com>
Content-Type: text/plain; charset=us-ascii
Hello Louis,
Saturday, February 21, 2009, 4:16:10 AM, you wrote:
In the meantime, a brief summary:
a minor correction: the best gcc result shown in the thread was 50x
faster than Don's one, so you need to miltiple all ratios by a factor
of 50
Straightforward and simple Haskell code, written by an individual
aware of issues with tail recursion and stream fusion, is frequently
within 3x the speed of GCC code when compiled with appropriate
optimizations in GHC.
yes, within 150x margin
When performance is an absolute necessity,
Haskell code can sometimes be manually modified (e.g. with manual
loop unrolls) to equal GCC in performance.
yes, to make it only 50x slower while being only 7 times larger (i
mean source lines)
Can we move on?
yes, we can! :)
--
Best regards,
Bulat mailto:Bulat.Ziganshin@gmail.com
------------------------------
Message: 7
Date: Sat, 21 Feb 2009 17:30:23 -0600
From: Louis Wasserman
Subject: Re: Re[3]: [Haskell-cafe] Re: speed: ghc vs gcc
To: Bulat Ziganshin
Cc: haskell-cafe@haskell.org
Message-ID:
Content-Type: text/plain; charset="iso-8859-1"
Observation:
The best gcc result shown in the thread, if I recall, precomputed the result
of the full computation at compiletime and simply outputted it, when we
looked at the assembly.
While I will accept that this could be seen as an optimization GHC should
have made, I do not accept that this will be the case with most everyday
code a programmer writes, as most code is not used to simply compute
arithmetic constants.
For code that actively requires computation at runtime, I have seen no
examples of an instance where well-optimized GHC is actually dozens or
hundreds of times slower than GCC output.
Louis Wasserman
wasserman.louis@gmail.com
On Sat, Feb 21, 2009 at 5:21 PM, Bulat Ziganshin
wrote:
Hello Louis,
Saturday, February 21, 2009, 4:16:10 AM, you wrote:
In the meantime, a brief summary:
a minor correction: the best gcc result shown in the thread was 50x
faster than Don's one, so you need to miltiple all ratios by a factor
of 50
Straightforward and simple Haskell code, written by an individual
aware of issues with tail recursion and stream fusion, is frequently
within 3x the speed of GCC code when compiled with appropriate
optimizations in GHC.
yes, within 150x margin
When performance is an absolute necessity,
Haskell code can sometimes be manually modified (e.g. with manual
loop unrolls) to equal GCC in performance.
yes, to make it only 50x slower while being only 7 times larger (i
mean source lines)
Can we move on?
yes, we can! :)
--
Best regards,
Bulat mailto:Bulat.Ziganshin@gmail.com