[Haskell-cafe] Re: Haskell-Cafe Digest, Vol 66, Issue 71

David Yoffe yoffedavid at yahoo.com
Sat Feb 21 21:47:40 EST 2009


Hi D.R Plotkin,
 
There are some nice mailing lists in haskell.org, include HUGS

--- On Sat, 2/21/09, haskell-cafe-request at haskell.org <haskell-cafe-request at haskell.org> wrote:

From: haskell-cafe-request at haskell.org <haskell-cafe-request at haskell.org>
Subject: Haskell-Cafe Digest, Vol 66, Issue 71
To: haskell-cafe at haskell.org
Date: Saturday, February 21, 2009, 7:01 PM

Send Haskell-Cafe mailing list submissions to
	haskell-cafe at 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 at haskell.org

You can reach the person managing the list at
	haskell-cafe-owner at 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 <lambda-belka at yandex.ru>
Subject: [Haskell-cafe] controlling timeout for Network.Socket.connect
	- how?
To: haskell-cafe at haskell.org
Message-ID: <22139581.post at 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--tp22139581p22139581.html
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 <loshea at gmail.com>
Subject: [Haskell-cafe] Stacking StateTs
To: haskell-cafe at haskell.org
Message-ID: <3636FA2B-5BB1-47CC-B20F-85491A55E4F7 at 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 <pumpkingod at gmail.com>
Subject: [Haskell-cafe] Haskellers on Twitter!
To: haskell-cafe at haskell.org
Message-ID:
	<b1a8a5050902211314y74edbf39h97dcfa3188f80a60 at mail.gmail.com>
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 <alexey.skladnoy at gmail.com>
Subject: Fwd: Re: [Haskell-cafe] speed: ghc vs gcc
To: haskell-cafe at haskell.org
Message-ID: <200902220058.59198.alexey.skladnoy at 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
> <bulat.ziganshin at gmail.com
>
> > 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 <bulat.ziganshin at gmail.com>
Subject: Re: Fwd: Re: [Haskell-cafe] speed: ghc vs gcc
To: Khudyakov Alexey <alexey.skladnoy at gmail.com>
Cc: haskell-cafe at haskell.org
Message-ID: <528706754.20090222010923 at 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.

it supported in gcc4 and icl at least

> I've just remembered another but related approach to optimization. It
uses
> genetic algorithm to determine close to the best set of optimization
options.

afaik it used widely for tuning parameters of compression algorithms


-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



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

Message: 6
Date: Sun, 22 Feb 2009 02:21:09 +0300
From: Bulat Ziganshin <bulat.ziganshin at gmail.com>
Subject: Re[3]: [Haskell-cafe] Re: speed: ghc vs gcc
To: Louis Wasserman <wasserman.louis at gmail.com>
Cc: haskell-cafe at haskell.org
Message-ID: <989437740.20090222022109 at 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 at gmail.com



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

Message: 7
Date: Sat, 21 Feb 2009 17:30:23 -0600
From: Louis Wasserman <wasserman.louis at gmail.com>
Subject: Re: Re[3]: [Haskell-cafe] Re: speed: ghc vs gcc
To: Bulat Ziganshin <Bulat.Ziganshin at gmail.com>
Cc: haskell-cafe at haskell.org
Message-ID:
	<ab4284220902211530k1690103ay1a31f437a2c521f4 at mail.gmail.com>
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 at gmail.com


On Sat, Feb 21, 2009 at 5:21 PM, Bulat Ziganshin
<bulat.ziganshin at gmail.com>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 at gmail.com
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
http://www.haskell.org/pipermail/haskell-cafe/attachments/20090221/3aef994b/attachment-0001.htm

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

Message: 8
Date: Sun, 22 Feb 2009 00:36:57 +0100
From: Daniel Fischer <daniel.is.fischer at web.de>
Subject: Re: [Haskell-cafe] Re: speed: ghc vs gcc
To: Bulat Ziganshin <Bulat.Ziganshin at gmail.com>,	Louis Wasserman
	<wasserman.louis at gmail.com>
Cc: haskell-cafe at haskell.org
Message-ID: <200902220036.57182.daniel.is.fischer at web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Sonntag, 22. Februar 2009 00:21 schrieb Bulat Ziganshin:
> 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

You're referring to the freak result of Dan Doel?
Come on, be serious, please. I have a Haskell result that runs in 7ms, too. 
Just use a rewrite rule and hey presto :)

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

Bulat, your obsession has become obnoxious and ridiculous.

>
> > 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! :)

Apparently not :(


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

Message: 9
Date: Sun, 22 Feb 2009 02:35:29 +0300
From: Bulat Ziganshin <bulat.ziganshin at gmail.com>
Subject: Re[5]: [Haskell-cafe] Re: speed: ghc vs gcc
To: Louis Wasserman <wasserman.louis at gmail.com>
Cc: Bulat Ziganshin <Bulat.Ziganshin at gmail.com>,
	haskell-cafe at haskell.org
Message-ID: <136796235.20090222023529 at gmail.com>
Content-Type: text/plain; charset=iso-8859-1

Hello Louis,

Sunday, February 22, 2009, 2:30:23 AM, you wrote:

yes, you are right. Don also compared results of 64x-reduced
computation with full one. are you think that these results are more
fair?

> 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 at gmail.com
>  

> On Sat, Feb 21, 2009 at 5:21 PM, Bulat Ziganshin
> <bulat.ziganshin at gmail.com> 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 at gmail.com
>  
>  

>   


-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



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

Message: 10
Date: Sat, 21 Feb 2009 18:37:36 -0500
From: David Menendez <dave at zednenem.com>
Subject: Re: [Haskell-cafe] Stacking StateTs
To: "Luis O'Shea" <loshea at gmail.com>
Cc: haskell-cafe at haskell.org
Message-ID:
	<49a77b7a0902211537s78bc7f8cq8ab5a50962c98cc8 at mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Sat, Feb 21, 2009 at 3:33 PM, Luis O'Shea <loshea at gmail.com>
wrote:
> I've been experimenting with the state monad and with StateT, and have
some
> questions about how to combine one state with another.

<snip>

>> test3 :: Monad m => String -> StateT Integer m String
>> test3 s = do
>>   modify (+ 1)
>>   a <- get
>>   return $ s ++ (show a)

A style point: It's often better to specify what operations test3
uses, rather than requiring a specific family of monads.

test3 :: MonadState Integer m => String -> m String

> 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

You don't really need to jump all the way out of the state
transformer. Something like this would work just as well:

test5a = flip execStateT 0 $ do
    s1 <- test3 ""
    modify $ \x -> 2 * x + 1
    s2 <- test3 s1
    modify $ \x -> x * x
    test3 s2

Contrast this with your test6.

Now, if you want to avoid passing the strings around explicitly, you
could add another state transformer. For example, we could layer a
String transformer on top of the underlying monad with this fairly
general combinator:

modifyM :: (Monad m) => (s -> m s) -> StateT s m ()
modifyM f = StateT $ \s -> f s >>= \s' -> return
((),s')

test5b = flip execStateT 0 . flip evalStateT "" $ do
    modifyM test3
    lift $ modify $ \x -> 2 * x + 1
    modifyM test3
    lift $ modify $ \x -> x * x
    modifyM test3

Note that modifyM works on the top-level state, whereas lift . modify
works on the inner state.

Or, you can put the state transformer on the bottom by taking
advantage of the fact that test3 is polymorphic in any underlying
monad.

test3' = lift get >>= test3 >>= lift . put   -- this is
essentially
modifyT test3

test5c = flip evalState "" . flip execStateT 0 $ do
    test3'
    modify $ \x -> 2*x+1
    test3'
    modify $ \x -> x * x
    test3'

But this only really makes sense if you expect the String state to
last at least as long as the Integer state.

Of my three alternatives, test5a actually seems the most idiomatic to
me, followed by test5b and then test5c. It's possible to write test5a
in a way that avoids explicitly passing the strings around, but the
result doesn't end up looking much better.


PS. Here are two functions that I ended up not using in my examples,
but which may come in handy when dealing with nested applications of
StateT:

curryStateT :: (Monad m) => StateT (s,t) m a -> StateT s (StateT t m) a
curryStateT m = StateT $ \s -> StateT $ \t ->
	runStateT m (s,t) >>= \ ~(a,(s,t)) -> return ((a,s),t)

uncurryStateT :: (Monad m) => StateT s (StateT t m) a -> StateT (s,t) m a
uncurryStateT m = StateT $ \ ~(s,t) ->
	runStateT (runStateT m s) t >>= \ ~((a,s),t) -> return (a,(s,t))

-- 
Dave Menendez <dave at zednenem.com>
<http://www.eyrie.org/~zednenem/>


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

Message: 11
Date: Sun, 22 Feb 2009 02:50:39 +0300
From: Bulat Ziganshin <bulat.ziganshin at gmail.com>
Subject: Re[2]: [Haskell-cafe] Re: speed: ghc vs gcc
To: Daniel Fischer <daniel.is.fischer at web.de>
Cc: Bulat Ziganshin <Bulat.Ziganshin at gmail.com>,
	haskell-cafe at haskell.org,	Louis Wasserman <wasserman.louis at gmail.com>
Message-ID: <715268448.20090222025039 at gmail.com>
Content-Type: text/plain; charset=us-ascii

Hello Daniel,

Sunday, February 22, 2009, 2:36:57 AM, you wrote:

> You're referring to the freak result of Dan Doel?
> Come on, be serious, please. I have a Haskell result that runs in 7ms,
too.
> Just use a rewrite rule and hey presto :)

Dan, why you have not said the same about test where ghc becomes 4x
faster than gcc?

> Bulat, your obsession has become obnoxious and ridiculous.

i really, really wonder why cheating on gcc side is "obsession that
become obnoxious and ridiculous" while cheating on ghc side is ok for
you. can you explain?


-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



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

Message: 12
Date: Sat, 21 Feb 2009 17:54:53 -0600
From: Louis Wasserman <wasserman.louis at gmail.com>
Subject: Re: Re[5]: [Haskell-cafe] Re: speed: ghc vs gcc
To: Bulat Ziganshin <Bulat.Ziganshin at gmail.com>
Cc: haskell-cafe at haskell.org
Message-ID:
	<ab4284220902211554r6c1cc2f5x114dde89d3ed7210 at mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I said nothing about fairness, and *never at any point said I thought Don's
results were more useful or fair.*  What makes you think that's what I
meant
to imply?

You have not responded to my separate concern that
> 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.

Rather than accusing me of taking sides, if you'd take an actual
apples-to-apples comparison, citing the best Haskell results and best GCC
results -- without using examples from either language which performed
computation at compile-time that would not be possible in everyday programs
-- my original claims were true: that GHC code is frequently within 3x the
speed of GCC code, and hacked-up GHC code can reach and match GCC
performance -- though I agree those hacks require an impractical blowup in
code size.  (Depending on your individual interpretation of what an average
Haskell program looks like, I concede that 3x might be off by a factor of 2
or so -- but not the factor of 50 you claimed.)

Don's "-D64" results, while *not* a useful gcc-vs-ghc comparison,
are
relevant if really determined Haskellers are interested in learning how to
obtain the absolute optimal perfection from their code.  Don's results
*are*
useful, but not in the way you say we're claiming.

Louis Wasserman
wasserman.louis at gmail.com


On Sat, Feb 21, 2009 at 5:35 PM, Bulat Ziganshin
<bulat.ziganshin at gmail.com>wrote:

> Hello Louis,
>
> Sunday, February 22, 2009, 2:30:23 AM, you wrote:
>
> yes, you are right. Don also compared results of 64x-reduced
> computation with full one. are you think that these results are more
> fair?
>
> > 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 at gmail.com
> >
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
http://www.haskell.org/pipermail/haskell-cafe/attachments/20090221/91ab0294/attachment-0001.htm

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

Message: 13
Date: Sat, 21 Feb 2009 23:55:38 +0000
From: Sebastian Sylvan <sylvan at student.chalmers.se>
Subject: Re: Re[5]: [Haskell-cafe] Re: speed: ghc vs gcc
To: Bulat Ziganshin <Bulat.Ziganshin at gmail.com>
Cc: Louis Wasserman <wasserman.louis at gmail.com>,
	haskell-cafe at haskell.org
Message-ID:
	<3d96ac180902211555w12b7730cqfa6b6966fc185d44 at mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

On Sat, Feb 21, 2009 at 11:35 PM, Bulat Ziganshin <bulat.ziganshin at gmail.com
> wrote:

> Hello Louis,
>
> Sunday, February 22, 2009, 2:30:23 AM, you wrote:
>
> yes, you are right. Don also compared results of 64x-reduced
> computation with full one. are you think that these results are more
> fair?


Yes. Clearly so.
It still computes the result from scratch - it just uses a trick which
generates better code. This is clearly a useful and worthwhile exercise as
it shows A) A neat trick with TH, B) A reasonably practical way to produce
fast code for the critical parts of a Haskell app, C) a motivating example
for implementing a compiler optimization to do it automatically.

Just outputting the precomputed result means nothing.



-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
http://www.haskell.org/pipermail/haskell-cafe/attachments/20090221/8861a70f/attachment-0001.htm

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

Message: 14
Date: Sat, 21 Feb 2009 15:59:04 -0800
From: John Meacham <john at repetae.net>
Subject: Re: [Haskell-cafe] Help using catch in 6.10
To: haskell-cafe at haskell.org
Message-ID: <20090221235904.GU22261 at sliver.repetae.net>
Content-Type: text/plain; charset=utf-8

On Sat, Feb 21, 2009 at 01:54:52PM +0000, Ian Lynagh wrote:
> On Sat, Feb 21, 2009 at 01:18:35AM +0100, Martijn van Steenbergen wrote:
> > 
> > You now need to specify the exact type of the exception you wish to 
> > catch. For example, to catch any exception:
> > 
> > action `catch` (\(e :: SomeException) -> handler)
> > 
> > For more information, see:
> > 
> > http://www.haskell.org/~simonmar/papers/ext-exceptions.pdf
> 
> See also
> 
> "Catching all exceptions"
>
http://www.haskell.org/ghc/dist/stable/docs/libraries/base/Control-Exception.html#4

It is too bad we didn't name SomeException to just be Exception, then it
would be quite straightforward to write code that cleanly compiles on
6.8 and 6.10. As it is,

#if __GLASGOW_HASKELL__ < 610
type SomeException = Exception
#endif

does the trick, but no one likes CPP...

        John


-- 
John Meacham - ⑆repetae.net⑆john⑈


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

Message: 15
Date: Sat, 21 Feb 2009 17:59:05 -0600
From: Louis Wasserman <wasserman.louis at gmail.com>
Subject: Re: Re[5]: [Haskell-cafe] Re: speed: ghc vs gcc
To: Sebastian Sylvan <sylvan at student.chalmers.se>
Cc: Bulat Ziganshin <Bulat.Ziganshin at gmail.com>,
	haskell-cafe at haskell.org
Message-ID:
	<ab4284220902211559i62648cabi697317bb33a5def5 at mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

Sebastian, that's not Bulat's point.  He's saying that if we make
that
optimization in Haskell, we should at least make the same optimization in
GCC for fair comparison.  (Though I'm not entirely sure that that
optimization would be of any use to GCC, but that's a linguistic concern,
no
more.)

His point is valid.  But Don's results *not* obtained by optimizing in this
fashion are valid comparisons, and the results obtained with this
optimization are useful for other reasons.

Louis Wasserman
wasserman.louis at gmail.com


On Sat, Feb 21, 2009 at 5:55 PM, Sebastian Sylvan <
sylvan at student.chalmers.se> wrote:

>
>
> On Sat, Feb 21, 2009 at 11:35 PM, Bulat Ziganshin <
> bulat.ziganshin at gmail.com> wrote:
>
>> Hello Louis,
>>
>> Sunday, February 22, 2009, 2:30:23 AM, you wrote:
>>
>> yes, you are right. Don also compared results of 64x-reduced
>> computation with full one. are you think that these results are more
>> fair?
>>
>
> Yes. Clearly so.
> It still computes the result from scratch - it just uses a trick which
> generates better code. This is clearly a useful and worthwhile exercise as
> it shows A) A neat trick with TH, B) A reasonably practical way to produce
> fast code for the critical parts of a Haskell app, C) a motivating example
> for implementing a compiler optimization to do it automatically.
>
> Just outputting the precomputed result means nothing.
>
>
>
> --
> Sebastian Sylvan
> +44(0)7857-300802
> UIN: 44640862
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
http://www.haskell.org/pipermail/haskell-cafe/attachments/20090221/d81c03fc/attachment-0001.htm

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

Message: 16
Date: Sat, 21 Feb 2009 15:59:54 -0800
From: Don Stewart <dons at galois.com>
Subject: [Haskell-cafe] The community is more important than the
	product
To: haskell-cafe at haskell.org
Message-ID: <20090221235954.GZ19753 at whirlpool.galois.com>
Content-Type: text/plain; charset=us-ascii

http://haskell.org/haskellwiki/Protect_the_community

Random notes on how to maintain tone, focus and productivity in an
online community I took a few years ago.

Might be some material there if anyone's seeking to help ensure
we remain a constructive, effective community.

-- Don

P.S. release some code on hackage.haskell.org.


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

Message: 17
Date: Sun, 22 Feb 2009 00:02:05 +0000
From: Sebastian Sylvan <sylvan at student.chalmers.se>
Subject: Re: Re[5]: [Haskell-cafe] Re: speed: ghc vs gcc
To: Louis Wasserman <wasserman.louis at gmail.com>
Cc: Bulat Ziganshin <Bulat.Ziganshin at gmail.com>,
	haskell-cafe at haskell.org
Message-ID:
	<3d96ac180902211602p5516d7aeh59dd27abbb90c6c4 at mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

No, he asked if comparing the D64 version with the straight gcc one was
"more fair" then comparing a version that precomputes the result with
one
that doesn't. That's what I responded to.

On Sat, Feb 21, 2009 at 11:59 PM, Louis Wasserman <wasserman.louis at gmail.com
> wrote:

> Sebastian, that's not Bulat's point.  He's saying that if we
make that
> optimization in Haskell, we should at least make the same optimization in
> GCC for fair comparison.  (Though I'm not entirely sure that that
> optimization would be of any use to GCC, but that's a linguistic
concern, no
> more.)
>
> His point is valid.  But Don's results *not* obtained by optimizing in
this
> fashion are valid comparisons, and the results obtained with this
> optimization are useful for other reasons.
>
> Louis Wasserman
> wasserman.louis at gmail.com
>
>
> On Sat, Feb 21, 2009 at 5:55 PM, Sebastian Sylvan <
> sylvan at student.chalmers.se> wrote:
>
>>
>>
>> On Sat, Feb 21, 2009 at 11:35 PM, Bulat Ziganshin <
>> bulat.ziganshin at gmail.com> wrote:
>>
>>> Hello Louis,
>>>
>>> Sunday, February 22, 2009, 2:30:23 AM, you wrote:
>>>
>>> yes, you are right. Don also compared results of 64x-reduced
>>> computation with full one. are you think that these results are
more
>>> fair?
>>>
>>
>> Yes. Clearly so.
>> It still computes the result from scratch - it just uses a trick which
>> generates better code. This is clearly a useful and worthwhile
exercise as
>> it shows A) A neat trick with TH, B) A reasonably practical way to
produce
>> fast code for the critical parts of a Haskell app, C) a motivating
example
>> for implementing a compiler optimization to do it automatically.
>>
>> Just outputting the precomputed result means nothing.
>>
>>
>>
>> --
>> Sebastian Sylvan
>> +44(0)7857-300802
>> UIN: 44640862
>>
>
>


-- 
Sebastian Sylvan
+44(0)7857-300802
UIN: 44640862
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
http://www.haskell.org/pipermail/haskell-cafe/attachments/20090222/65ad0a79/attachment-0001.htm

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

Message: 18
Date: Sun, 22 Feb 2009 01:11:19 +0100
From: Daniel Fischer <daniel.is.fischer at web.de>
Subject: Re: [Haskell-cafe] Re: speed: ghc vs gcc
To: Bulat Ziganshin <Bulat.Ziganshin at gmail.com>
Cc: Bulat Ziganshin <Bulat.Ziganshin at gmail.com>,
	haskell-cafe at haskell.org,	Louis Wasserman <wasserman.louis at gmail.com>
Message-ID: <200902220111.19929.daniel.is.fischer at web.de>
Content-Type: text/plain;  charset="iso-8859-1"

Am Sonntag, 22. Februar 2009 00:50 schrieb Bulat Ziganshin:
> Hello Daniel,
>
> Sunday, February 22, 2009, 2:36:57 AM, you wrote:
> > You're referring to the freak result of Dan Doel?
> > Come on, be serious, please. I have a Haskell result that runs in
7ms,
> > too. Just use a rewrite rule and hey presto :)
>
> Dan, why you have not said the same about test where ghc becomes 4x
> faster than gcc?

Because, as has been explained several times to you, it was not a test of 
ghc's code generation vs. gcc's, and it was NOT meant to be. It was 
explicitely an investigation of how effective an improvement loop-unrolling 
could be.

>
> > Bulat, your obsession has become obnoxious and ridiculous.
>
> i really, really wonder why cheating on gcc side is "obsession that
> become obnoxious and ridiculous" while cheating on ghc side is ok for
> you. can you explain?

Seriously????

You have one case where gcc calculated the result for an extremely simple 
programme during the compilation and you use that to say that gcc's code is

routinely 50-150 times faster than ghc's. Very convincing.



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

Message: 19
Date: Sun, 22 Feb 2009 03:10:31 +0300
From: Bulat Ziganshin <bulat.ziganshin at gmail.com>
Subject: Re[7]: [Haskell-cafe] Re: speed: ghc vs gcc
To: Sebastian Sylvan <sylvan at student.chalmers.se>
Cc: Bulat Ziganshin <Bulat.Ziganshin at gmail.com>,
	haskell-cafe at haskell.org,	Louis Wasserman <wasserman.louis at gmail.com>
Message-ID: <561497165.20090222031031 at gmail.com>
Content-Type: text/plain; charset=us-ascii

Hello Sebastian,

Sunday, February 22, 2009, 2:55:38 AM, you wrote:
>  yes, you are right. Don also compared results of 64x-reduced
>  computation with full one. are you think that these results are more
>  fair?

> Yes. Clearly so.
> It still computes the result from scratch - it just uses a trick
> which generates better code. This is clearly a useful and worthwhile
> exercise as it shows A) A neat trick with TH, B) A reasonably
> practical way to produce fast code for the critical parts of a
> Haskell app, C) a motivating example for implementing a compiler
> optimization to do it automatically.

yes, but does you know why his last program is 64x faster than simple
code? it's because *gcc* optimize it this way. the first program i
published there does it by mistake, then i fixed it by using 'xor'
instead of (+) and published here that i've considered most fair
comparison

OTOH Don used this gcc optimization to generate faster code for
haskell. he doesn't used this trick for C++ and doesn't omitted
unoptimized gcc results from the chart. as a result people who don't
analyzed details made conclusion that ghc outperformed gcc here

so i have made experiment with cheating the same way, but in more
obvious manner. and i got 3 angry answers in 5 minutes. so what are
the difference? you don't catched details of Don comparison or you
bothered only by gcc-related cheating?

-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



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

Message: 20
Date: Sun, 22 Feb 2009 01:12:13 +0100
From: Peter Verswyvelen <bugfact at gmail.com>
Subject: [Haskell-cafe] Template Haskell compilation error on Windows
	(was	Re: speed: ghc vs gcc)
To: Don Stewart <dons at galois.com>
Cc: Claus Reinke <claus.reinke at talk21.com>, haskell-cafe at haskell.org,
	Bulat Ziganshin <Bulat.Ziganshin at gmail.com>
Message-ID:
	<a88790d10902211612m52ff9145lb522577611b76779 at mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I tried to compile the template Haskell loop unrolling trick from Claus
Reinke on my machine which is running Windows and GHC 6.10.1, and I got
linker errors.
(note that compiling *without* -fvia-C works fine)

Compiling under Cygwin did not solve it. Any ideas how I could get this
working? I have no experience with TH yet so I might be missing something
essential...

Thanks,
Peter

c:\temp>ghc -O2 -fvia-C -optc-O3 -fforce-recomp Apply.hs
Apply.o:ghc6140_0.hc:(.text+0x7d): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarP_con_info'
Apply.o:ghc6140_0.hc:(.text+0x10d): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarE_con_info'
Apply.o:ghc6140_0.hc:(.text+0x19d): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarP_con_info'
Apply.o:ghc6140_0.hc:(.text+0x571): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarP_con_info'
Apply.o:ghc6140_0.hc:(.text+0x609): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarE_con_info'
Apply.o:ghc6140_0.hc:(.text+0x6c9): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarE_con_info'
Apply.o:ghc6140_0.hc:(.text+0x789): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarE_con_info'
Apply.o:ghc6140_0.hc:(.text+0x82c): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziLib_a23_closure'
Apply.o:ghc6140_0.hc:(.text+0x868): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziLib_a23_closure'
Apply.o:ghc6140_0.hc:(.text+0x891): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarP_con_info'
Apply.o:ghc6140_0.hc:(.text+0xd81): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarP_con_info'
Apply.o:ghc6140_0.hc:(.text+0xe19): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarE_con_info'
Apply.o:ghc6140_0.hc:(.text+0xed9): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarE_con_info'
Apply.o:ghc6140_0.hc:(.text+0xf99): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarE_con_info'
Apply.o:ghc6140_0.hc:(.text+0x103c): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziLib_a23_closure'
Apply.o:ghc6140_0.hc:(.text+0x1078): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziLib_a23_closure'
Apply.o:ghc6140_0.hc:(.text+0x10a1): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziSyntax_VarP_con_info'
Apply.o:ghc6140_0.hc:(.text+0x14d0): undefined reference to
`__stginit_templatezmhaskell_LanguageziHaskellziTHziSyntax_'
Apply.o:ghc6140_0.hc:(.text+0x292): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziLib_lamE_info'
Apply.o:ghc6140_0.hc:(.text+0x6ab): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziLib_a23_info'
Apply.o:ghc6140_0.hc:(.text+0x76b): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziLib_a23_info'
Apply.o:ghc6140_0.hc:(.text+0x9bc): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziLib_lamE_info'
Apply.o:ghc6140_0.hc:(.text+0xebb): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziLib_a23_info'
Apply.o:ghc6140_0.hc:(.text+0xf7b): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziLib_a23_info'
Apply.o:ghc6140_0.hc:(.text+0x11cc): undefined reference to
`templatezmhaskell_LanguageziHaskellziTHziLib_lamE_info'
C:\app\ghc-6.10.1/libHSrts.a(Main.o):Main.c:(.text+0x7): undefined
reference
to `__stginit_ZCMain'
C:\app\ghc-6.10.1/libHSrts.a(Main.o):Main.c:(.text+0x36): undefined
reference to `ZCMain_main_closure'
collect2: ld returned 1 exit status



>
-------------- next part --------------
An HTML attachment was scrubbed...
URL:
http://www.haskell.org/pipermail/haskell-cafe/attachments/20090222/bff4135e/attachment.htm

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

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe at haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


End of Haskell-Cafe Digest, Vol 66, Issue 71
********************************************



      
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090221/e9067e2b/attachment-0001.htm


More information about the Haskell-Cafe mailing list