Re: ghc -O2 and class dictionaries

2008-12-29 Thread Dave Bayer
Yeah, I knew it was fairly unlikely that I was the first to think of  
this optimization ;-)


I just reported the "run-time performance bug" as 
http://hackage.haskell.org/trac/ghc/ticket/2902

I am using an Intel Core 2 Duo MacBook and GHC 6.10.1, OS X 10.5.6.  
For the toy example that I submitted, the difference is over a factor  
of 3x.


Thanks,
Dave

On Dec 29, 2008, at 6:23 AM, Simon Peyton-Jones wrote:

Which version of GHC are you using?  GHC 6.10 implements  
automatically precisely the transformation you give below.


If the difference shows up in GHC 6.10, could you spare a moment to  
produce a reproducible test case, and record it in GHC's bug tracker?


Thanks

Simon


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: [reactive] Re: black hole detection and concurrency

2008-12-29 Thread Isaac Dupree

Bertram Felgenhauer wrote:

Now in fact, IO actions are indistinguishable from pure computations by
the RTS, so this mechanism also makes IO actions resumable, in
principle, if you can access the corresponding thunk somehow. Normally
you can't - there is no reference to that thunk - but unsafePerformIO
gives you that reference.


I wonder if other things break in the presence of resumable 
IO computations... the first thing that comes to mind is, 
inside a "block" or "unblock" (which have to initiate, take 
down and deal with all that infrastructure -- luckily you 
only use them inside a separate thread, a forkIO within the 
unsafePerformIO... Which admittedly makes things horribly 
confusing in its own way. Also does forkIO copy any state? 
it copies blocked status now, which the unamb-calling thread 
might have...).  The state of the thread when entering the 
computation again, could be different than it was when the 
computation was first suspended, I'm guessing.  (At least 
you need to be careful about what invariants you assume; I'm 
not yet sure if it's possible to be careful enough.)


-Isaac
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: GADT Strangeness

2008-12-29 Thread Isaac Dupree

Simon Peyton-Jones wrote:

This is a nasty corner I agree.  GHC requires -XGADTs for you to *define* a 
GADT. Perhaps it should also require -XGADTs for you to *match against* one (as 
you are doing here).  That would avoid this particular hole.  If you think that 
would be a step forward, do put forward a Trac feature request, and encourage 
others to support it.


Does GHC require any flags to pattern-match against an 
existential constructor? (does it require type-system 
complication?)


(and what if GADT syntax was used for an ordinary data type? 
or for an ordinary existential?)


but I'd support requiring -XGADTs in any such pattern-match 
in which XRelaxedPolyRec could make a difference.  Somehow 
it doesn't seem fair for a module to imply that it *doesn't* 
use GADTs, if it cannot even by type-checked without 
understanding them.

also see http://hackage.haskell.org/trac/ghc/ticket/2004

-Isaac
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


ghci debugger :trace command does not always extend trace history

2008-12-29 Thread Peter Hercek

Hi,

I expected ":trace expr" to always add data to the trace history but it 
does not do so for CAFs (which are not reduced yet).
My point is that the command ":trace z" did not add anything to the 
trace history and I cannot check why value z is 2, because value of y is 
not in the trace history. Is this the expected behavior? If it is, how 
can I make ghci to extend the trace history when "forcing" variables?


Peter.

Here is the example:

status:0 pe...@metod [765] ~/tmp
% cat a.hs
test :: Int -> Int
test x =
  let y = x+1 in
  let z = y+1 in
  z
status:0 pe...@metod [766] ~/tmp
% ghci a.hs
GHCi, version 6.8.2: http://www.haskell.org/ghc/  :? for help
Loading package base ... linking ... done.
[1 of 1] Compiling Main ( a.hs, interpreted )
Ok, modules loaded: Main.
*Main> :break Main 5
Breakpoint 0 activated at a.hs:5:2
*Main> :trace test 0
Stopped at a.hs:5:2
_result :: Int = _
z :: Int = _
4let z = y+1 in
5z
6
[a.hs:5:2] *Main> :back
Logged breakpoint at a.hs:(2,0)-(5,2)
_result :: Int
1  test :: Int -> Int
2  test x =
3let y = x+1 in
4let z = y+1 in
5z
6
[-1: a.hs:(2,0)-(5,2)] *Main> :back
no more logged breakpoints
[-1: a.hs:(2,0)-(5,2)] *Main> :forward
Stopped at a.hs:5:2
_result :: Int
z :: Int
4let z = y+1 in
5z
6
[a.hs:5:2] *Main> :trace z
2
[a.hs:5:2] *Main> :back
Logged breakpoint at a.hs:(2,0)-(5,2)
_result :: Int
1  test :: Int -> Int
2  test x =
3let y = x+1 in
4let z = y+1 in
5z
6
[-1: a.hs:(2,0)-(5,2)] *Main> y
:1:0: Not in scope: `y'

[-1: a.hs:(2,0)-(5,2)] *Main> :back
no more logged breakpoints
[-1: a.hs:(2,0)-(5,2)] *Main> :forward
Stopped at a.hs:5:2
_result :: Int
z :: Int
4let z = y+1 in
5z
6
[a.hs:5:2] *Main> z
2
[a.hs:5:2] *Main> y

:1:0: Not in scope: `y'
[a.hs:5:2] *Main> :quit
Leaving GHCi.
status:0 pe...@metod [767] ~/tmp
%

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: black hole detection and concurrency

2008-12-29 Thread Bertram Felgenhauer
Simon Peyton-Jones wrote:
> | I have a good theory on the latter symptom (the "thread killed"
> | message). Sticking in some traces, as in my appended code, helped me
> | to see what's going on. It seems to be exactly what you describe --
> | the variable v is permanently bound to the exception it "evaluates"
> | to.  Since the right hand True portion of the unamb evaluates more
> | quickly, the spawned threads are killed and the left hand (the v)
> | "evaluates" to "thread killed".
> 
> This is odd (to me).  The "permanently bound" stuff applies only to
> *synchronous* exceptions, which thread-killing is not.  Simon M will
> have more to say when he gets back

This is true when the exception is raised the first time. However, some
exception handling functions like 'bracket' catch the exception, do
their cleanup, and then throw the exception again. This is done in
onException, and goes through throwIO and eventually raiseIO#. At this
point the originally asynchronous exception has become a synchronous
one.

As I wrote elsewhere in this thread, this should not be a problem
without unsafePerformIO.

Bertram
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: GADT Strangeness

2008-12-29 Thread Simon Peyton-Jones
| If I remove -XScopedTypeVariables from this http://hpaste.org/13230 then
| I get the following error message:
|
| > Asn1cTestNew.hs:55:27:
| > GADT pattern match in non-rigid context for `INTEGER'
| >   Solution: add a type signature
| > In the pattern: INTEGER
| > In the definition of `referenceTypeAndValAux2':
| > referenceTypeAndValAux2 ns INTEGER x
| >   = lhs ns <> text " = " <> text (show x) 
<> semi
| > Failed, modules loaded: Language.ASN1, ASNTYPE.
|
| At the very least the message is unhelpful. It was only by accident I
| decided to put in -XScopedTypeVariables.

This one had me puzzled for a while too! Here is what's happening.

You have three mutually recursive functions:
referenceTypeAndValAux1
referenceTypeAndValAux2
cSEQUENCE
In Haskell 98, typechecking mutually recursive functions is done *together*, 
with each having a momomorphic type in the other RHSs.  That leads to an 
annoying problem, that of figuring out how their polymorphic type variables 
"match up".  As a result, even the type variables in the type signature look 
non-rigid.

The solution is to use -XRelaxedPolyRec, which compiles mutually-recursive 
definitions that each have a type signature one by one.  Precisely because of 
the above infelicity, both -XGADTs and -XScopedTypeVariables imply 
-XRelaxedPolyRec.

This is a nasty corner I agree.  GHC requires -XGADTs for you to *define* a 
GADT. Perhaps it should also require -XGADTs for you to *match against* one (as 
you are doing here).  That would avoid this particular hole.  If you think that 
would be a step forward, do put forward a Trac feature request, and encourage 
others to support it.

Simon

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: ghc -O2 and class dictionaries

2008-12-29 Thread Simon Peyton-Jones
Which version of GHC are you using?  GHC 6.10 implements automatically 
precisely the transformation you give below.

If the difference shows up in GHC 6.10, could you spare a moment to produce a 
reproducible test case, and record it in GHC's bug tracker?

Thanks

Simon

| -Original Message-
| From: glasgow-haskell-users-boun...@haskell.org [mailto:glasgow-haskell-users-
| boun...@haskell.org] On Behalf Of Dave Bayer
| Sent: 28 December 2008 15:29
| To: glasgow-haskell-users@haskell.org
| Subject: ghc -O2 and class dictionaries
|
| Using "ghc -O2" while tuning a class instance for performance, I
| obtained a 13% speedup by applying the transformation
|
| >   instance (Ord a, Num b) ⇒ Sum PSum a b where
| > empty  = empty
| > insert = insert
| > union  = union
| > unions = unions
| > extractMin = extractMin
| > fromList   = fromList
| > toList = toList
| > map= map
| > mapMaybe   = mapMaybe
|
| and defining the instance functions outside the instance declaration,
| rather than inside the instance declaration.
|
| Conceptually, I understand this as follows: After this transformation,
| none of the recursive calls have to go through the class dictionary.
|
| Is this a transformation that ghc could automatically apply while
| optimizing? It is clear at compile time that the recursive calls are
| from this instance. Every 13% helps.
|
| (My example is adapting a pairing heap to sums of terms, e.g. to
| define an algebra from a small category. So far, I can't beat
| Data.Map, but I'm not done tuning. Other examples might not show the
| same performance increase from this transformation.)
|
| ___
| Glasgow-haskell-users mailing list
| Glasgow-haskell-users@haskell.org
| http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: black hole detection and concurrency

2008-12-29 Thread Simon Peyton-Jones
| I have a good theory on the latter symptom (the "thread killed"
| message). Sticking in some traces, as in my appended code, helped me
| to see what's going on. It seems to be exactly what you describe --
| the variable v is permanently bound to the exception it "evaluates"
| to.  Since the right hand True portion of the unamb evaluates more
| quickly, the spawned threads are killed and the left hand (the v)
| "evaluates" to "thread killed".

This is odd (to me).  The "permanently bound" stuff applies only to 
*synchronous* exceptions, which thread-killing is not.  Simon M will have more 
to say when he gets back

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: black hole detection and concurrency

2008-12-29 Thread Simon Peyton-Jones
I have not followed the details of this thread, but Simon Marlow will be back 
in action on 5 Jan and he should know.

What I do know is that this is supposed to happen:

* If a *synchronous* exception S is raised when evaluating a thunk, the 
thunk is permanently updated to "throw S".

* If an *asynchronous* exception A is raised when evaluating  a thunk, 
the stack is copied into the heap, and the thunk is updated with a new thunk 
that, when evaluated, will resume evaluation where it left off.

But there may be some funny interactions with unsafePerformIO.

Simon

From: glasgow-haskell-users-boun...@haskell.org 
[mailto:glasgow-haskell-users-boun...@haskell.org] On Behalf Of Conal Elliott
Sent: 26 December 2008 06:15
To: glasgow-haskell-users@haskell.org
Subject: black hole detection and concurrency

I'm looking for information about black hole detection with ghc.  I'm getting 
"<>" where I don't think there is an actual black hole.  I get this 
message sometimes with the unamb package, which is implemented with 
unsafePerformIO, concurrency, and killThread, as described in 
http://conal.net/blog/posts/functional-concurrency-with-unambiguous-choice/ and 
http://conal.net/blog/posts/smarter-termination-for-thread-racing/ .

Suppose I have a definition 'v = unsafePerformIO ...', and v is used more than 
once.   Evaluation (to whnf) of v is begun and the evaluation thread gets 
killed before evaluation is complete.  Then the second use begins.  Will the 
second evaluation be (incorrectly) flagged as a black hole?

I haven't found a simple, reproducible example of incorrect black-hole 
reporting.  My current examples are tied up with the Reactive library.  I do 
have another strange symptom, which is "thread killed" message.  I wonder if 
it's related to the <> message.  Code below.

Thanks,  - Conal


import Prelude hiding (catch)
import System.IO.Unsafe
import Control.Concurrent
import Control.Exception


-- *** Exception: thread killed
main :: IO ()
main = print $ f (f True) where f v = (v `unamb` True) `seq` v

-- | Unambiguous choice operator.  Equivalent to the ambiguous choice
-- operator, but with arguments restricted to be equal where not bottom,
-- so that the choice doesn't matter.  See also 'amb'.
unamb :: a -> a -> a
unamb a b = unsafePerformIO (evaluate a `race` evaluate b)

-- | Race two actions against each other in separate threads, and pick
-- whichever finishes first.  See also 'amb'.
race :: IO a -> IO a -> IO a
race a b = do
v <- newEmptyMVar
let t x = x >>= putMVar v
withThread (t a) $ withThread (t b) $ takeMVar v
 where
   withThread u v = bracket (forkIO u) killThread (const v)
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


RE: length of module name affecting performance??

2008-12-29 Thread Simon Peyton-Jones
| Subject: Re: length of module name affecting performance??
|
| That's a truly awesome feature!  I'll shorten all my module names to
| single letters tomorrow.

Awesome indeed :-).  Try shortening all your variable names to single letters 
to, to see if that helps.  Oh, and delete all comments.

I recall that you and Thomas followed both these precepts rigorously when 
writing the LML compiler. I well remember trying to understand the lambda 
lifter, which was a miracle of compact programming: it did a *lot* in a single 
page of code, but all function definitions were equally impenetrable
   f x p l g i n = (g l [p], h i (i+p))


What a great bug -- I would never have predicted it, but in retrospect it makes 
perfect sense. Record selectors had better get fixed.

Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users