Re: [GHC] #2297: Profiler is inconsistent about biography for GHC's heap

2009-03-17 Thread GHC
#2297: Profiler is inconsistent about biography for GHC's heap
-+--
Reporter:  igloo |Owner:  
Type:  bug   |   Status:  closed  
Priority:  normal|Milestone:  6.10.2  
   Component:  Profiling |  Version:  6.9 
Severity:  normal|   Resolution:  fixed   
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by simonmar):

  * status:  new = closed
  * resolution:  = fixed

Comment:

 optimistically assuming this is fixed by the fix for #3039.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2297#comment:8
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2297: Profiler is inconsistent about biography for GHC's heap

2008-12-01 Thread GHC
#2297: Profiler is inconsistent about biography for GHC's heap
-+--
Reporter:  igloo |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  6.10.2  
   Component:  Profiling |  Version:  6.9 
Severity:  normal|   Resolution:  
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by simonpj):

  * priority:  high = normal

Comment:

 Decreasing priority.  (High cost-to-benefit ratio!)  Simon  Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2297#comment:7
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2297: Profiler is inconsistent about biography for GHC's heap

2008-10-04 Thread GHC
#2297: Profiler is inconsistent about biography for GHC's heap
--+-
 Reporter:  igloo |  Owner:  
 Type:  bug   | Status:  new 
 Priority:  high  |  Milestone:  6.10.2  
Component:  Profiling |Version:  6.9 
 Severity:  normal| Resolution:  
 Keywords:| Difficulty:  Unknown 
 Testcase:|   Architecture:  Unknown/Multiple
   Os:  Unknown/Multiple  |  
--+-
Changes (by igloo):

  * milestone:  6.10.1 = 6.10.2

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2297#comment:6
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2297: Profiler is inconsistent about biography for GHC's heap

2008-07-14 Thread GHC
#2297: Profiler is inconsistent about biography for GHC's heap
---+
 Reporter:  igloo  |  Owner: 
 Type:  bug| Status:  new
 Priority:  high   |  Milestone:  6.10.1 
Component:  Profiling  |Version:  6.9
 Severity:  normal | Resolution: 
 Keywords: | Difficulty:  Unknown
 Testcase: |   Architecture:  Unknown
   Os:  Unknown|  
---+
Changes (by simonmar):

  * milestone:  6.10 branch = 6.10.1

Comment:

 Needed for further profiling of GHC, we should investigate for 6.10.1 if
 possible.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2297#comment:3
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #2297: Profiler is inconsistent about biography for GHC's heap

2008-05-19 Thread GHC
#2297: Profiler is inconsistent about biography for GHC's heap
--+-
Reporter:  igloo  |   Owner: 
Type:  bug|  Status:  new
Priority:  normal |   Milestone:  6.10 branch
   Component:  Profiling  | Version:  6.9
Severity:  normal |Keywords: 
  Difficulty:  Unknown|Testcase: 
Architecture:  Unknown|  Os:  Unknown
--+-
 My slightly modified `rnBind` has this clause (`i` is an `Int`):
 {{{
 rnBind sig_fn
trim
i
(L loc (FunBind { fun_id = name,
  fun_infix = inf,
  fun_matches = matches,
  -- no pattern FVs
  bind_fvs = _
}))
-- invariant: no free vars here when it's a FunBind
   = i `seq` setSrcSpan loc $
 do  { let plain_name = unLoc name

 ; (matches', fvs) - bindSigTyVarsFV (sig_fn plain_name) $
 -- bindSigTyVars tests for Opt_ScopedTyVars
  rnMatchGroup (FunRhs plain_name inf) matches

 ; checkPrecMatch inf plain_name matches'

 ; return
 (L loc (trace (Using FunBind for  ++ show i)
 (FunBind { fun_id = name,
   fun_infix = inf,
   fun_matches = matches',
  bind_fvs = trim fvs,
   fun_co_fn = idHsWrapper,
   fun_tick = Nothing })),
   [plain_name],
   fvs)
   }
 }}}
 If I comment out the trace and run
 {{{
 ghc --make J -fforce-recomp +RTS -p -hcrnBind -hyHsBindLR -hb
 }}}
 then I get `notrace.png`, all VOID. However, with the trace I get
 `trace.png`, LAG turning into DRAG. The two graphs are also a slightly
 different shape, which is curious.

 Also attached is the core for with and without the tracing. I think the
 only interesting difference is
 {{{
 -  a30_ [ALWAYS Just L] :: NameSet.FreeVars
 +  a30_ [ALWAYS Just L] :: HsBinds.HsBindLR Name.Name Name.Name
[Str: DmdType]
 -  a30_ = w1_ ww3_ } in
 -let {
 -  a31_ :: HsBinds.HsWrapper
 -  []
 -  a31_ =
 -__scc {rnBind ghc-6.9.20080517:RnBinds !}
 -__scc {idHsWrapper ghc-6.9.20080517:HsBinds} HsBinds.WpHole } in
 -let {
 -  a32_ :: HsBinds.HsWrapper
 -  []
 -  a32_ =
 -__scc {rnBind ghc-6.9.20080517:RnBinds !}
 -__scc {idHsWrapper ghc-6.9.20080517:HsBinds} HsBinds.WpHole } in
 -let {
 -  a33_ :: HsBinds.HsBindLR Name.Name Name.Name
 -  [Str: DmdType]
 -  a33_ =
 -HsBinds.FunBind
 -  @ Name.Name
 -  @ Name.Name
 -  name_
 -  inf_
 -  ww2_
 -  a32_
 -  a30_
 -  (Data.Maybe.Nothing @ (GHC.Base.Int, [Name.Name])) } in
 +  a30_ =
 +Debug.Trace.trace
 +  @ (HsBinds.HsBindLR Name.Name Name.Name)
 +  lvl45_
 +  (HsBinds.FunBind
 + @ Name.Name
 + @ Name.Name
 + name_
 + inf_
 + ww2_
 + (__scc {rnBind ghc-6.9.20080517:RnBinds !}
 +  __scc {idHsWrapper ghc-6.9.20080517:HsBinds}
 HsBinds.WpHole)
 + (w1_ ww3_)
 + (Data.Maybe.Nothing @ (GHC.Base.Int, [Name.Name]))) } in
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2297
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #2297: Profiler is inconsistent about biography for GHC's heap

2008-05-19 Thread GHC
#2297: Profiler is inconsistent about biography for GHC's heap
---+
 Reporter:  igloo  |  Owner: 
 Type:  bug| Status:  new
 Priority:  normal |  Milestone:  6.10 branch
Component:  Profiling  |Version:  6.9
 Severity:  normal | Resolution: 
 Keywords: | Difficulty:  Unknown
 Testcase: |   Architecture:  Unknown
   Os:  Unknown|  
---+
Comment (by igloo):

 In case this doesn't get sorted soon, I think these are all the relevant
 changes I've made:
 {{{
 hunk ./compiler/rename/RnBinds.lhs 40
 -import Digraph ( SCC(..), stronglyConnComp )
 +import Digraph
 hunk ./compiler/rename/RnBinds.lhs 45
 -import Util( filterOut )
 -import Monad   ( foldM, unless )
 +import Util
 +import Monad
 +import Control.Exception
 +import Debug.Trace
 hunk ./compiler/rename/RnBinds.lhs 321
 -   binds_w_dus - mapBagM (rnBind (mkSigTvFn sigs') trim) mbinds
 +   xs - zipWithM (rnBind (mkSigTvFn sigs') trim) [1..] (bagToList
 mbinds)
 +   let binds_w_dus = listToBag xs
 hunk ./compiler/rename/RnBinds.lhs 498
 +   - Int
 hunk ./compiler/rename/RnBinds.lhs 501
 -rnBind _ trim (L loc (PatBind { pat_lhs = pat,
 -pat_rhs = grhss,
 --- pat fvs were stored here while
 --- processing the LHS
 -bind_fvs=pat_fvs }))
 +rnBind _ trim i (L loc (PatBind { pat_lhs = pat,
 +  pat_rhs = grhss,
 +  -- pat fvs were stored here while
 +  -- processing the LHS
 +  bind_fvs=pat_fvs }))
 hunk ./compiler/rename/RnBinds.lhs 519
 -   trim
 +   trim
 +   i
 hunk ./compiler/rename/RnBinds.lhs 528
 -  = setSrcSpan loc $
 +  = i `seq` setSrcSpan loc $
 hunk ./compiler/rename/RnBinds.lhs 537
 -   ; return (L loc (FunBind { fun_id = name,
 +   ; return
 +(L loc (trace (Using FunBind for  ++ show i)
 +(FunBind { fun_id = name,
 hunk ./compiler/rename/RnBinds.lhs 544
 -  fun_tick = Nothing }),
 +  fun_tick = Nothing })),
 hunk ./compiler/rename/RnBinds.lhs 549
 -rnBind _ _ b = pprPanic rnBind (ppr b)
 +rnBind _ _ _ b = pprPanic rnBind (ppr b)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2297#comment:1
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs