Probably not a bug ... rather user manual omission.

1998-02-26 Thread David Plume


ghc-3.10, Solaris 2.5.1

The compiler doesn't appear to link programs compiled with the
-prof -auto options if the -O flag is set. 

As far as I can make out that's just fine, as long as it says
so in the 'Compiling programs for profiling' section of the user
manual - but I couldn't find it.

Can send more info if you like ...

   Cheers,

 Dave
  




Re: is this a bug?

1998-02-26 Thread Simon Marlow

Marko Schuetz [EMAIL PROTECTED] writes:

 ghc-3.01 complains about a syntax error in the following cut down
 program:
 
  module Fehler where
 
  data Constr 
   = (:-:) { expr :: LambdaCExpr, context :: ContextTerm }
 
 kinetic% ghc Fehler.hs
 Fehler.hs:4:12: parse error on input: "{"

Yes, it looks like a bug.  The following patch should fix it:

*** hsparser.y  1998/01/21 17:37:09 1.16
--- hsparser.y  1998/02/26 10:47:34
***
*** 755,761 
|  OPAREN qconsym CPAREN batypes{ $$ = mkconstrpre($2,$4,hsplineno); }
  
  /* Con { op1 :: Int } */
!   |  gtycon OCURLY fields CCURLY  { $$ = mkconstrrec($1,$3,hsplineno); }
;
/* 1 S/R conflict on OCURLY - shift */
  
--- 755,762 
|  OPAREN qconsym CPAREN batypes{ $$ = mkconstrpre($2,$4,hsplineno); }
  
  /* Con { op1 :: Int } */
!   | qtycon OCURLY fields CCURLY   { $$ = mkconstrrec($1,$3,hsplineno); }
!   | OPAREN qconsym CPAREN OCURLY fields CCURLY { $$ = 
mkconstrrec($2,$5,hsplineno); }
;
/* 1 S/R conflict on OCURLY - shift */
  

Cheers,
Simon

-- 
Simon Marlow [EMAIL PROTECTED]
University of Glasgow   http://www.dcs.gla.ac.uk/~simonm/
finger for PGP public key



Re: Probably not a bug ... rather user manual omission.

1998-02-26 Thread Sigbjorn Finne


David Plume writes:
 
 ghc-3.10, Solaris 2.5.1
 
 The compiler doesn't appear to link programs compiled with the
 -prof -auto options if the -O flag is set. 
 

Hi,

profiling optimised programs is legal - what's the linker errors
you're getting? 

--Sigbjorn



Re: Probably not a bug ... rather user manual omission.

1998-02-26 Thread Sigbjorn Finne



David Plume writes:
 
 
 
 Resent: Apologies if this arrives twice... 
 Mailer at dcs.gla.ac.uk didn't like my MIME attached files, so they're
 just appended to this message.
 
 Dave

Thanks, will have a look. There's been a couple of people reporting
problems with mailing MIME attachements to g-h-b, so if you've got
the bounce still lying in your inbox, could you mail it to me so
that we can have a go at fixing this?

Thanks,
--Sigbjorn



Re: Probably not a bug ... rather user manual omission.

1998-02-26 Thread Sigbjorn Finne


David Plume writes:

   
   The compiler doesn't appear to link programs compiled with the
   -prof -auto options if the -O flag is set. 
   
  
  Hi,
  
  profiling optimised programs is legal - what's the linker errors
  you're getting? 
 
 I've attached the output of the make process and a copy of my rather
 obscure makefile.
 

Thanks, this was readily reproduceable. The appended 3.01 source patch
should fix it..

--Sigbjorn

*** profiling/CostCentre.lhs1998/02/09 12:53:44 1.18
--- profiling/CostCentre.lhs1998/02/26 13:29:01
***
*** 386,394 
module_kind = do_caf is_caf (moduleString mod_name ++ '/':
   basic_kind)
! grp_str   = if (_NULL_ grp_name) then mod_name else grp_name
! full_kind = do_caf is_caf
!(moduleString mod_name  ++ 
! ('/' : _UNPK_ grp_str) ++ 
! ('/' : basic_kind))
in
  if (friendly_sty sty) then
--- 386,401 
module_kind = do_caf is_caf (moduleString mod_name ++ '/':
   basic_kind)
! grp_str = [] 
! {- TODO: re-instate this once interface file lexer
!  handles groups.
!   grp_str = 
!  if (_NULL_ grp_name) then 
!   [] 
!else 
!   '/' : (_UNPK_ grp_name)
!   -}
! full_kind   = do_caf is_caf
!(moduleString mod_name  ++ 
! grp_str ++ ('/' : basic_kind))
in
  if (friendly_sty sty) then
***
*** 407,412 
  
do_kind (UserCC name) = _UNPK_ name
!   do_kind (AutoCC id)   = do_id id ++ (if (friendly_sty sty) then "/AUTO" else 
"")
!   do_kind (DictCC id)   = do_id id ++ (if (friendly_sty sty) then "/DICT" else 
"")
  
  {-
--- 414,419 
  
do_kind (UserCC name) = _UNPK_ name
!   do_kind (AutoCC id)   = do_id id ++ (if (debugStyle sty) then "/AUTO" else "")
!   do_kind (DictCC id)   = do_id id ++ (if (debugStyle sty) then "/DICT" else "")
  
  {-