Re: how dynamic stack approximation works

2009-02-17 Thread Simon Marlow

Peter Hercek wrote:

pepe wrote:
Having (a kind of messy approximation of) a dynamic stack is possible 
with a variant of the cost center stacks mechanism used for profiling. 
But the downside is that code and libraries would need to be compiled 
for debugging.
Is there any info somewhere why the approximation of the dynamic stack 
needs libraries to be recompiled for debugging? I thought about it but I 
could not figure out why it would be needed. Here is what I thought is 
the way it works:


I have the feeling that pepe is talking about *lexical* call stacks, rather 
than *dynamic* call stacks.  Cost-centre-stacks try to give you the lexcial 
call stack (but sadly don't always work properly, and as I've said before 
we don't fully understand how to do it, or indeed whether it can be done at 
all...).  It probably *would* require recompiling the libraries, though.


Perhaps you're already aware of this wiki page, but I'll post the link anyway:

http://hackage.haskell.org/trac/ghc/wiki/ExplicitCallStack

The dynamic call stack is already present, in the form of the runtime 
execution stack.  For debugging you might want to track more information 
than we store on this stack, however.


You seem to have a plan for maintaining a dynamic stack for debugging, 
perhaps you could flesh out the details in a wiki page, mainly to ensure 
that we're discussing the same thing?


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


Re: [Haskell-cafe] Gtk2HS 0.10.0 Released

2009-02-17 Thread Simon Marlow

Duncan Coutts wrote:

On Thu, 2009-02-12 at 10:11 +0100, Christian Maeder wrote:

Duncan Coutts wrote:

On Wed, 2009-02-11 at 15:49 +0100, Lennart Augustsson wrote:

Does this version work from ghci?

  -- Lennart

Specifically I believe Lennart is asking about Windows. It's worked in
ghci in Linux for ages and it worked in ghci in Windows prior to the
0.9.13 release.

In the 0.9.13 release on Windows there was something funky with linking
(possibly due to using a newer mingw) and ghci's linker could not
understand was was going on and could not load the packages.

I'm having trouble
http://hackage.haskell.org/trac/ghc/ticket/2615
(cairo depends on pthread, which has a linker script)
Is there an easy workaround?


The way it used to work was that the Gtk2Hs ./configure script just
filtered out pthread on linux systems. Of course that's just a hack.


Maybe that ticket can be considered in Plans for GHC 6.10.2


Maybe. Dealing with linker scripts properly is probably rather tricky
and we get it for free when we switch to shared libraries.


I don't follow this last point - how does switching to shared libraries for 
Haskell code change things here?


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


Re: [Haskell-cafe] Gtk2HS 0.10.0 Released

2009-02-17 Thread Duncan Coutts
On Tue, 2009-02-17 at 08:47 +, Simon Marlow wrote:
 Duncan Coutts wrote:

  Maybe. Dealing with linker scripts properly is probably rather tricky
  and we get it for free when we switch to shared libraries.
 
 I don't follow this last point - how does switching to shared libraries for 
 Haskell code change things here?

It means that ghci will not need to link to system shared libs except
when someone uses -lblah on the ghci command line. That's because when
we link a Haskell package as a shared lib the system linker interprets
any linker scripts and embeds the list of dependencies on other shared
libs (other Haskell packages and system libs). Then ghci just dlopens
the shared libs for the directly used Haskell packages that that
automatically resolves all their deps on other Haskell and system shared
libs.

Duncan

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


Building GHC on Windows

2009-02-17 Thread Felix Martini
Hi all,

Simon Marlow has recently posted a patch that adds Unicode support to
Handle I/O. He mentioned that it didn't work yet on Windows so i was
thinking of looking at the source code to see how the new Unicode
support works and perhaps try to make it work on Windows.

I have built GHC from source in the past on Windows and the process
was cumbersome compared to building it on Linux. But i was curious to
see if it has gotten easier.

After reading the Wiki i decided to get the source with Git as Darcs
was slow with remote downloads. Ok, that was a lot quicker than
before! Let's see, i need to run sync-all to get the core libraries. I
remember that i used to use darcs-all so it must be a new script.
Sync-all doesn't have an extension so i probably need to run it with
msys. That doesn't work, somehow my msys environment does not find
git. So let's try the Git Bash environment which also uses msys (and
does not have bash). Now i get a cryptic error: at ./sync-all line
99, IN line 19. It seems the script cannot determine the default
remote repo. The top line shows that it is a Perl script and i don't
know Perl enough to see what is wrong. I have Perl installed on this
Windows pc so let's try to run the script directly. That doesn't work
either: the Perl script wants to use grep and sed.

All this is likely trivial to fix but at the same time these little
roadblocks may also explain why few developers on Windows contribute
code to GHC and Haskell.

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


Compiler optimizations questions for ghc 6.10...

2009-02-17 Thread Tyson Whitehead
(compiled with ghc 6.10 with options -O2 -ddump-simpl)

I was wondering why lvl_s1mF is not being inlined into a_s1Gv in the core at 
the bottom of this email as that is the only place it is ever referenced.

It also seems the extra levels of indirection are defeating the strictness 
analyzer on eta_s1CN in a_s1Gv as all code branches either directly force it 
or ultimately pass it to digit_s1l3 as in the included branch.

Also, why isn't digit_s1l3 optimized to take its first parameter unboxed?  It 
is strict in its first argument, and grepping the core shows that it is only 
ever used like in lvl_s1mF (i.e., passed things like lvl_s1mG).

Thanks!  -Tyson

PS:  Is there any way to get better control over the loop breaker choice?  For 
a slightly simpler digit function, it is not chosen, and great code is 
produced.  I've tried using INLINE on digit, but that seems to result in the 
monad bind operator not being inlined, which produces even worse code.

.
.
.
letrec {
  lvl_s1mF :: Control.Monad.State.Strict.StateT
GHC.Types.Int
(Control.Monad.State.Strict.StateT
   GHC.Types.Int
   (Control.Monad.Error.ErrorT
  GHC.Base.String Control.Monad.Identity.Identity))
GHC.Types.Int
  [Str: DmdType {s1l3-C(S)}]
  lvl_s1mF = digit_s1l3 lvl_s1mG;
  .
  .
  .
  a_s1Gv :: GHC.Types.Int
- GHC.Types.Int
- Control.Monad.Error.ErrorT
 [GHC.Types.Char]
 Control.Monad.Identity.Identity
 ((GHC.Types.Int, GHC.Types.Int), GHC.Types.Int)
  [Arity 2
   Str: DmdType U(L)L {a1hP-U(TTTL) s1ka-U(L)}]
  a_s1Gv =

  a_s1Gv =
\ (eta_a1px [ALWAYS Just U(L)] :: GHC.Types.Int)
  (eta_s1CN [ALWAYS Just L] :: GHC.Types.Int) -
.
.

  GHC.Bool.True -
(((lvl_s1mF
   `cast` (... ~
  GHC.Types.Int
  - Control.Monad.State.Strict.StateT
   GHC.Types.Int
   (Control.Monad.Error.ErrorT
  GHC.Base.String Control.Monad.Identity.Identity)
   (GHC.Types.Int, GHC.Types.Int)))
(GHC.Types.I# (GHC.Prim.+# x_a1tl 1)))
 `cast` (... ~
GHC.Types.Int
- Control.Monad.Error.ErrorT
 GHC.Base.String
 Control.Monad.Identity.Identity
 ((GHC.Types.Int, GHC.Types.Int), GHC.Types.Int)))
  eta_s1CN

.
.
  .
  .
  .
  digit_s1l3 [ALWAYS LoopBreaker Nothing]
 :: GHC.Types.Int
- Control.Monad.State.Strict.StateT
 GHC.Types.Int
 (Control.Monad.State.Strict.StateT
GHC.Types.Int
(Control.Monad.Error.ErrorT
   GHC.Base.String
   Control.Monad.Identity.Identity))
 GHC.Types.Int
  [Arity 1
   Str: DmdType U(L)]
  digit_s1l3 =
\ (x_aqR [ALWAYS Just U(L)] ::GHC.Types.Int) -
  case x_aqR
  of x_XsO [ALWAYS Just A] { GHC.Types.I# ipv_s1bt [ALWAYS Just L] -
  let {
.
.
.
  } in
  (\ (eta_X1sC [ALWAYS Just L] :: GHC.Types.Int)
 (eta_s1FE [ALWAYS Just U(L)] :: GHC.Types.Int) -
.
.
. )
  `cast` (... ~
 Control.Monad.State.Strict.StateT
   GHC.Types.Int
   (Control.Monad.State.Strict.StateT
  GHC.Types.Int
  (Control.Monad.Error.ErrorT
 GHC.Base.String Control.Monad.Identity.Identity))
   GHC.Types.Int)
  .
  .
  .
}
.
.
.
lvl_s1mG :: GHC.Types.Int
[Str: DmdType m]
lvl_s1mG = GHC.Types.I# 0

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


Re: my experience with ghci debugger extensions

2009-02-17 Thread Peter Hercek

Pepe Iborra wrote:

- Regarding your :logLocal, you should rename it to :stepLocal, open a
ticket, and attach your patch. We should really try to get this into
6.10.2.
  
Ach, I missed I'm supposed to do this first time I read the message. 
I'll get to it at worst during this weekend.



Finallly, please do not forget to add a link to this in the GHCi
Debugger wiki page at

http://haskell.org/haskellwiki/GHC/GHCi_debugger

and/or at the debugging page at

http://haskell.org/haskellwiki/Debugging
  
Ok, I found a note in HWN that Ashley Yakeley can create a wiki account. 
He kindly did it for me so I updated the second page.


Also there does not seem to be a demand for ghciext package so I'm not 
going to advertise it any more but I'll keep the latest version here (if 
anybody would be interested):

http://www.hck.sk/users/peter/pub/

Peter.

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


Re: Compiler optimizations questions for ghc 6.10...

2009-02-17 Thread Max Bolingbroke
2009/2/17 Tyson Whitehead twhiteh...@gmail.com:
 (compiled with ghc 6.10 with options -O2 -ddump-simpl)

 I was wondering why lvl_s1mF is not being inlined into a_s1Gv in the core at
 the bottom of this email as that is the only place it is ever referenced.

The relevant GHC code is SimplUtils.preInlineUnconditionally. It looks
like it dosen't get inlined for two reasons:
1) It's not a manifest lambda (it's an application) so inlining inside
another lambda would change the number of times the FVs of lvl_s1mF
might occur
2) I'm not sure if the use-context is considered interesting by GHC
because the application of the function might be hidden by the cast.
Not sure about this one.

So it looks like the problem stems from digit_s1l3 having arity 1
rather than arity 3. You could try and force it into a higher arity
somehow, but I can't say exactly how you might do that without seeing
the rest of the Core (and in particular the part under the first
lambda in the definition of digit).

In general, the -ddump-inlinings flag is useful for working out why
something wasn't inlined - but it wouldn't have helped you in this
case, because it only dumps information about inlining at call sites,
and you actually want an unconditional inlining to occur.

 It also seems the extra levels of indirection are defeating the strictness
 analyzer on eta_s1CN in a_s1Gv as all code branches either directly force it
 or ultimately pass it to digit_s1l3 as in the included branch.

 Also, why isn't digit_s1l3 optimized to take its first parameter unboxed?  It
 is strict in its first argument, and grepping the core shows that it is only
 ever used like in lvl_s1mF (i.e., passed things like lvl_s1mG).

Yeah, that's weird. I don't know the answer to this. Have you actually
got to the worker-wrapper stage at the point you copied this core?

 Thanks!  -Tyson

 PS:  Is there any way to get better control over the loop breaker choice?  For
 a slightly simpler digit function, it is not chosen, and great code is
 produced.  I've tried using INLINE on digit, but that seems to result in the
 monad bind operator not being inlined, which produces even worse code.

GHC won't inline inside functions marked with INLINE pragmas, for
various very good reasons. I don't know how you could change the loop
breaker given the current state of technology, but SPJ has a patch for
GHC in the works that revamps the treatment of INLINE pragmas and
which should (if my understanding of his patch is correct) solve the
issue with = not being inlined within an inlineable digit.

Sorry I can't be more helpful. It's possible I could make some more
concrete suggestions if you posted the complete code somewhere.
Max
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Compiler optimizations questions for ghc 6.10...

2009-02-17 Thread Tyson Whitehead
On February 17, 2009 19:24:44 Max Bolingbroke wrote:
 2009/2/17 Tyson Whitehead twhiteh...@gmail.com:
  It also seems the extra levels of indirection are defeating the
  strictness analyzer on eta_s1CN in a_s1Gv as all code branches either
  directly force it or ultimately pass it to digit_s1l3 as in the included
  branch.
 
  Also, why isn't digit_s1l3 optimized to take its first parameter unboxed?
   It is strict in its first argument, and grepping the core shows that it
  is only ever used like in lvl_s1mF (i.e., passed things like lvl_s1mG).

 Yeah, that's weird. I don't know the answer to this. Have you actually
 got to the worker-wrapper stage at the point you copied this core?

Yes.  You are right.  Contrary to what the top of the email said, I created 
that output with -ddump-stranal, and -dshow-passes indicates that the worker-
wrapper stage comes next.  If I dump it (or just the final core with -ddump-
simpl), digit* is entirely replaced with a first-argument-unboxed $wdigit*.

The inner lambdas (i.e., the second and third arguments) remain boxed.

It seems I should have just used the -ddump-simpl output instead of the -
ddump-stranal output.  I had just got thinking the the -ddump-simpl output did 
not include strictness analysis because I didn't see it on a bunch of the code 
(in retrospect, that was because that code was created by later stages)

Cheers!  -Tyson



signature.asc
Description: This is a digitally signed message part.
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Compiler optimizations questions for ghc 6.10...

2009-02-17 Thread Tyson Whitehead
On February 17, 2009 19:24:44 Max Bolingbroke wrote:
 2009/2/17 Tyson Whitehead twhiteh...@gmail.com:
  (compiled with ghc 6.10 with options -O2 -ddump-simpl)

That should have been -ddump-stranal instead of -ddump-simpl.

  I was wondering why lvl_s1mF is not being inlined into a_s1Gv in the core
  at the bottom of this email as that is the only place it is ever
  referenced.

 The relevant GHC code is SimplUtils.preInlineUnconditionally. It looks
 like it dosen't get inlined for two reasons:
 1) It's not a manifest lambda (it's an application) so inlining inside
 another lambda would change the number of times the FVs of lvl_s1mF
 might occur

I have to confess my ignorance here as my google fu failed and so I still 
don't know what a manifest lambda is (other than not a application).  : )

 2) I'm not sure if the use-context is considered interesting by GHC
 because the application of the function might be hidden by the cast.
 Not sure about this one.

I was wondering about that, which is why I didn't remove all the cast noise.

 So it looks like the problem stems from digit_s1l3 having arity 1
 rather than arity 3. You could try and force it into a higher arity
 somehow, but I can't say exactly how you might do that without seeing
 the rest of the Core (and in particular the part under the first
 lambda in the definition of digit).

The thing is that the inner lambdas come from inlining that StateT monad 
transformers in a StateT q (StateT Int (ErrorT String Identity)) monad (i.e., 
the first one is the q state -- which works out to an Int -- and the second is 
the Int state).  I guess I could explicitly pass them around, but that would 
seem to defeat the purpose of having StateT.

The actual routines under this implement part of a FSM for (hopefully) 
efficiently extracting an Int from a ByteString (or a uvector UArr -- source 
of the Step data type).  The relevant part of the actual code, which is a bit 
hacked up with ! patterns from my attempts to get better code, is as follows.

type ParseInt q a = StateT q (StateT Int (ErrorT String Identity)) a

next :: q - Step q Word8
next i | i==n  = Done
   | otherwise = Yield (bs `BS.unsafeIndex` i) (i+1)

wrap :: Monad m = (Word8 - StateT q m a) - StateT q m a - StateT q m a
wrap yield (done::StateT q m a) = loop
where loop :: StateT q m a
  loop = do q - get
case next q of
  Yield x q' - put q'  yield x
  Skipq' - put q'  loop
  Done   - done
s2 :: ParseInt q Int
s2 = wrap yield done
where yield :: Word8 - StateT q (StateT Int (ErrorT String Identity)) Int
  yield x | x==48 = digit 0
  | x==49 = digit 1
  | x==50 = digit 2
  | x==51 = digit 3
  | x==52 = digit 4
  | x==53 = digit 5
  | x==54 = digit 6
  | x==55 = digit 7
  | x==56 = digit 8
  | x==57 = digit 9
  | otherwise = do !y - lift get
   return y
  where digit :: Int - ParseInt q Int
digit !x = do !y - lift get
  ( if y = (maxBound-9)`quot`10 || y = 
(maxBound-x)`div`10
then let !y' = y*10+x in (lift $ put y') 
 s2
else throwError integer overflow )
  done :: ParseInt q Int
  done= do !y - lift get
   return y

I just finished adding the Parse q Int type to help with email line wrapping.  
As I alluded to in my original email, if I don't have the Int overflow check 
in digit, it is not chosen as the loop breaker, all the StateT stuff is 
compiled away, and you get a really nice efficient assembler loop (which is 
important because the final FSM has to actually chew through GBs of data).

The part of the code under the first lambda in digit is as follows (I didn't 
keep the original dump, so the uniques have changed here).  It's the second 
part of the Int overflow bounds check (i.e., y = (maxBound-x)`div`10), and, 
indeed, something you don't want to compute unless the easy check fails.

digit_s1lk =
  \ (x_aqR [ALWAYS Just U(L)] :: GHC.Types.Int) -
case x_aqR
of x_XsQ [ALWAYS Just A] { GHC.Types.I# ipv_s1bD [ALWAYS Just L] -
let {
  lvl_s1my [ALWAYS Just D(T)] :: GHC.Types.Int
  [Str: DmdType]
  lvl_s1my =
case GHC.Prim.-# 9223372036854775807 ipv_s1bD
of wild2_a1xi [ALWAYS Just L] {
  __DEFAULT -
case GHC.Base.divInt# wild2_a1xi 10
of wild21_a1xj [ALWAYS Just L] { __DEFAULT -
GHC.Types.I# wild21_a1xj
};
  (-9223372036854775808) -
case GHC.Base.divInt# (-9223372036854775808) 10
of wild21_a1xl [ALWAYS Just L] { __DEFAULT -
   

Re: my experience with ghci debugger extensions

2009-02-17 Thread Simon Michael

Peter Hercek wrote:
Also there does not seem to be a demand for ghciext package so I'm not 


Hi Peter.. just to note that I haven't had the need/time yet to try it, 
but I'm very thankful for the work you and Pepe are doing to make ghci 
more powerful. It's a very useful tool for learning about Haskell and 
figuring out perplexing behaviours in real-world programs.


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