Re: [GHC] #1781: Type equality class leads to non-termination

2007-10-18 Thread GHC
#1781: Type equality class leads to non-termination
+---
Reporter:  chak |Owner: 
Type:  bug  |   Status:  new
Priority:  normal   |Milestone: 
   Component:  Compiler (Type checker)  |  Version:  6.9
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Unknown
  Os:  Unknown  | Testcase: 
Architecture:  Unknown  |  
+---
Comment (by chak):

 This program was rejected by 6.6.1 with the message
 {{{
 /Users/chak/Code/haskell/E_Class.hs:10:0:
 The equation(s) for `plus' have two arguments,
 but its type `Int - a' has only one
 }}}
 which is arguably not the right thing to do either.

 I haven't traced this, but the problem may well be due to an interaction
 between equality constraints and FDs - at least since I fixed
 `TcUnify.subFunTys`.  The latter function will defer a wanted equality `a
 ~ (b1 - b2)`, which in principle would be entailed by the given `E a (Int
 - Int)` (with `b1, b2 := Int`).  However, the normalisation and
 entailment machinery for equalities doesn't know about FDs.  (I would
 think that should lead to an error message rather than non-termination,
 but oh well)

 Incidentally,
 {{{
 module ShouldCompile where

 plus :: (a ~ (Int - Int)) = Int - a
 plus x y = x + y
 }}}
 works fine.

 I would expect that this would be fixed as soon as we implement FDs by way
 of TFs.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1781#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


-O bug?

2007-10-18 Thread Serge D. Mechveliani
Dear GHC developers, 

The point (1) below looks like a bug  (in all GHC versions!).

(1) -O for demo-test.

Take (the public)  docon-2.10  build it under -O,  install,
and build also under  -O  its test program by
cd demotest
ghc $doconCpOpt -O --make Main

Either the latter compilation will loop forever or it will take an 
unnaturally large resource.

Yes, the functions  T_.test, T_tt  are defined in rather a particular 
way (see them). I always build this test under -Onot, because 
compiling with optimization has not much sense for this part.
But slill.


(2) -O2

In my DoCon  programs, -O2 was always worse than -O:  
the code is about 1.3 times larger and 1.2 times slower.
There are some particular points in my programs. 
For example, almost everywhere I set Integer rather than Int, 
I do not recall others, now.

In never complained on (1) and (2) because did not recall of them
and because they do not bite me in practice, so far.

-
Serge Mechveliani
[EMAIL PROTECTED]
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


6.8.1-candidate tested

2007-10-18 Thread Serge D. Mechveliani
Dear GHC developers,

I have tested  ghc-6.8.0.20071015-src.tar.bz2  on DoCon and on 
Dumatel.  
It looks all right

(except the bug-candidate for -O which is common to all GHC versions
and which I recently reported
).

On DoCon,  ghc-6.8.0.20071015  
1) builds the project 2-3 times faster than  ghc-6.6.1,  
2) its produced  .a  code is  1.6  times larger,
3) the test runs  1.4  times faster,
4) the minimal space (2500 Kb) for the test running remains. 

This looks all right.

Regards,

-
Serge Mechveliani
[EMAIL PROTECTED]
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


[GHC] #1782: gmake check-packages fails for ghc-6.8.0.20071017-src on solaris

2007-10-18 Thread GHC
#1782: gmake check-packages fails for ghc-6.8.0.20071017-src on solaris
---+
  Reporter:  guest |  Owner: 
  Type:  bug   | Status:  new
  Priority:  normal|  Milestone: 
 Component:  Compiler  |Version:  6.8
  Severity:  normal|   Keywords: 
Difficulty:  Unknown   | Os:  Solaris
  Testcase:|   Architecture:  x86
---+
 the tests in the toplevel Makefile go wrong:
 {{{
  check-packages :
 -   @for d in `cat libraries/core-packages`; do \
 +   @ds=`cat libraries/core-packages`;\
 +   for d in $$ds; do \
   if test ! -d libraries/$$d; then \
  echo Looks like you're missing libraries/$$d,; \
  echo maybe you haven't done './darcs-all get'?; \
  exit 1; \
   fi \
 done
 -   @if test ! -e libraries/base/configure; then \
 +   @if test ! -f libraries/base/configure; then \
 echo Looks like you're missing base's configure script.; \
 }}}

 sh `test` under solaris does not understand '`-e`' and '`cat libraries
 /core-packages`' is treated as a single argument if not assigned to a
 variable.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1782
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: 6.8.1-candidate tested

2007-10-18 Thread Simon Marlow

Serge D. Mechveliani wrote:

Dear GHC developers,

I have tested  ghc-6.8.0.20071015-src.tar.bz2  on DoCon and on 
Dumatel.  
It looks all right


(except the bug-candidate for -O which is common to all GHC versions
and which I recently reported
).

On DoCon,  ghc-6.8.0.20071015  
1) builds the project 2-3 times faster than  ghc-6.6.1,  
2) its produced  .a  code is  1.6  times larger,


I have noticed binary sizes increasing by around 20% on the nofib suite 
too.  We've discovered one issue with some dictionaries not being inlined 
when we would expect them to, but there may be others.  I'm investigating.


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


profiling missing from snapshot?

2007-10-18 Thread Ketil Malde

Hi,

I installed the binary ghc-6.8.0.20071017
snapshot, but when I try to compile with -prof, I get 

  % ghc --make -O2 src/Xml2Xls -o xml2xls2 -prof
  [1 of 1] Compiling Main ( src/Xml2Xls.hs, src/Xml2Xls.o )
  Linking xml2xls2 ...
  /usr/bin/ld: cannot find -lHSrts_p
  collect2: ld returned 1 exit status

'locate HSrts_p' and other searches only find some old ghc-6.6 stuff.

-k
-- 
If I haven't seen further, it is by standing in the footprints of giants
___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [GHC] #1545: GHCi debugger doesn't work on an unregisterised compiler

2007-10-18 Thread GHC
#1545: GHCi debugger doesn't work on an unregisterised compiler
+---
Reporter:  igloo|Owner:  simonmar   
Type:  bug  |   Status:  new
Priority:  normal   |Milestone:  6.10 branch
   Component:  GHCi |  Version:  6.6.1  
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Unknown
  Os:  Unknown  | Testcase: 
Architecture:  Unknown  |  
+---
Changes (by simonmar):

  * owner:  = simonmar

Comment:

 validating a fix

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1545#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


Re: profiling missing from snapshot?

2007-10-18 Thread Simon Marlow

Ketil Malde wrote:


I installed the binary ghc-6.8.0.20071017
snapshot, but when I try to compile with -prof, I get 


  % ghc --make -O2 src/Xml2Xls -o xml2xls2 -prof
  [1 of 1] Compiling Main ( src/Xml2Xls.hs, src/Xml2Xls.o )
  Linking xml2xls2 ...
  /usr/bin/ld: cannot find -lHSrts_p
  collect2: ld returned 1 exit status

'locate HSrts_p' and other searches only find some old ghc-6.6 stuff.


This one we know about:

http://hackage.haskell.org/trac/ghc/ticket/1778

Cheers,
Simon

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


[GHC] #1783: FD leads to non-termination of type checker

2007-10-18 Thread GHC
#1783: FD leads to non-termination of type checker
--+-
  Reporter:  chak |  Owner: 
  Type:  bug  | Status:  new
  Priority:  normal   |  Milestone: 
 Component:  Compiler (Type checker)  |Version:  6.9
  Severity:  normal   |   Keywords: 
Difficulty:  Unknown  | Os:  Unknown
  Testcase:   |   Architecture:  Unknown
--+-
 Here another program that causes the type checker to diverge:
 {{{
 {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies #-}
 {-# LANGUAGE PatternSignatures, ScopedTypeVariables, FlexibleContexts #-}

 module ShouldCompile where

 import Prelude hiding (foldr, foldr1)

 import Data.Maybe

 class Elem a e | a - e

 class Foldable a where
   foldr :: Elem a e = (e - b - b) - b - a - b

 --  foldr1 :: forall e. Elem a e = (e - e - e) - a - e  -- WORKS!
   foldr1 :: Elem a e = (e - e - e) - a - e
   foldr1 f xs = fromMaybe (error foldr1: empty structure)
   (foldr mf Nothing xs)
  where mf :: Elem a e = (e - Maybe e - Maybe e)
mf x Nothing  = Just x
mf x (Just y) = Just (f x y)
 }}}
 This is the FD version of #1776.  If we use lexically scoped type
 variables - i.e., the signature marked with WORKS! - everything is fine.
 However, we shouldn't have to use the scoped type variable as the FD rule
 should combine the `Elem a e` constraints in the two signatures to
 establish that the `e` in `foldr1`'s signature is the same as the `e` in
 `mf`'s signature.

 In contrast to #1781, there doesn't seem to be an equality constraint
 involved in this example.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1783
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] #1546: maessen_hashtab is broken

2007-10-18 Thread GHC
#1546: maessen_hashtab is broken
-+--
Reporter:  igloo |Owner:  simonpj   
Type:  bug   |   Status:  new   
Priority:  high  |Milestone:  6.8 branch
   Component:  Compiler  |  Version:  6.6.1 
Severity:  normal|   Resolution:
Keywords:|   Difficulty:  Unknown   
  Os:  Unknown   | Testcase:
Architecture:  Unknown   |  
-+--
Comment (by simonmar):

 The cause of the segfaults is now fixed.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1546#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


Re: [GHC] #1545: GHCi debugger doesn't work on an unregisterised compiler

2007-10-18 Thread GHC
#1545: GHCi debugger doesn't work on an unregisterised compiler
+---
Reporter:  igloo|Owner:  igloo  
Type:  merge|   Status:  new
Priority:  normal   |Milestone:  6.10 branch
   Component:  GHCi |  Version:  6.6.1  
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Unknown
  Os:  Unknown  | Testcase: 
Architecture:  Unknown  |  
+---
Changes (by simonmar):

  * owner:  simonmar = igloo
  * type:  bug = merge

Comment:

 Fixed, to merge:

 {{{
 Thu Oct 18 11:19:29 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * fix breakpoints in unregisterised mode

 Thu Oct 18 11:53:40 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * fix :print when !tablesNextToCode

 Thu Oct 18 12:06:21 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * fix -fbreak-on-exception for unregsterised
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1545#comment:2
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] #1545: GHCi debugger doesn't work on an unregisterised compiler

2007-10-18 Thread GHC
#1545: GHCi debugger doesn't work on an unregisterised compiler
+---
Reporter:  igloo|Owner:  igloo 
Type:  merge|   Status:  new   
Priority:  normal   |Milestone:  6.8 branch
   Component:  GHCi |  Version:  6.6.1 
Severity:  normal   |   Resolution:
Keywords:   |   Difficulty:  Unknown   
  Os:  Unknown  | Testcase:
Architecture:  Unknown  |  
+---
Changes (by simonmar):

  * milestone:  6.10 branch = 6.8 branch

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1545#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


Re: [GHC] #1546: maessen_hashtab is broken

2007-10-18 Thread GHC
#1546: maessen_hashtab is broken
-+--
Reporter:  igloo |Owner:  simonpj   
Type:  bug   |   Status:  new   
Priority:  high  |Milestone:  6.8 branch
   Component:  Compiler  |  Version:  6.6.1 
Severity:  normal|   Resolution:
Keywords:|   Difficulty:  Unknown   
  Os:  Unknown   | Testcase:
Architecture:  Unknown   |  
-+--
Comment (by simonmar):

 For reference, the patch that fixed the segfaults was:

 {{{
 Wed Oct 17 13:56:57 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * recordMutable: test for gen0 before calling recordMutableCap
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1546#comment:4
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] #1785: xargs failure

2007-10-18 Thread GHC
#1785: xargs failure
---+
  Reporter:  guest |  Owner: 
  Type:  bug   | Status:  new
  Priority:  normal|  Milestone: 
 Component:  Compiler  |Version:  6.8
  Severity:  normal|   Keywords: 
Difficulty:  Unknown   | Os:  Solaris
  Testcase:|   Architecture:  x86
---+
 I don't know how the file `libraries/base/GNUMakefile` is generated. Maybe
 this is a cabal bug.

 My build of ghc-6.8.0.20071017 failed as follows:

 {{{
 ...
 t/build/Unsafe/Coerce_split -name '*.o' -print) | xargs -s 3
 /usr/ccs/bin/ar
  q  dist/build/libHSbase-3.0.a
 xargs: 0  max-cmd-line-size = 2048: 3
 xargs: Usage: xargs: [-t] [-p] [-e[eofstr]] [-E eofstr] [-I replstr]
 [-i[replstr
 ]] [-L #] [-l[#]] [-n # [-x]] [-s size] [cmd [args ...]]
 gmake[2]: *** [dist/build/libHSbase-3.0.a] Error 2
 }}}

 if I replace 3 with 2048 compilation goes through, but I don't know if
 something is cut off.

 (also see  http://hackage.haskell.org/trac/hackage/ticket/98#comment:2)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1785
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] #1784: Duplicate cases for EM_AMD64 and EM_X86_64

2007-10-18 Thread GHC
#1784: Duplicate cases for  EM_AMD64 and EM_X86_64
---+
  Reporter:  guest |  Owner: 
  Type:  bug   | Status:  new
  Priority:  normal|  Milestone: 
 Component:  Compiler  |Version:  6.8
  Severity:  normal|   Keywords: 
Difficulty:  Unknown   | Os:  Solaris
  Testcase:|   Architecture:  x86
---+
 The Solaris compiler gcc_4.2.2 complained about the values EM_AMD64 and
 EM_X86_64 being identical:

 {{{
 Linker.c: In function 'ocVerifyImage_ELF':

 Linker.c:2908:0:  error: duplicate case value

 Linker.c:2905:0:  error: previously used here
 gmake[1]: *** [Linker.o] Error 1
 }}}

 As a workaround I've deleted the EM_AMD64 case in `rts/Linker.c` of the
 ghc-6.8.0.20071017 sources.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1784
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] #1652: System.Directory.copyFile breakage

2007-10-18 Thread GHC
#1652: System.Directory.copyFile breakage
---+
Reporter:  sorear  |Owner:  igloo 
Type:  merge   |   Status:  new   
Priority:  normal  |Milestone:  6.8 branch
   Component:  libraries/base  |  Version:  6.7   
Severity:  normal  |   Resolution:
Keywords:  |   Difficulty:  Unknown   
  Os:  Linux   | Testcase:
Architecture:  x86 |  
---+
Changes (by simonmar):

  * owner:  simonmar = igloo
  * type:  bug = merge

Comment:

 Fixed, thanks.

 In libraries/base:

 {{{
 Thu Oct 18 13:23:45 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * FIX #1652: openTempFile should accept an empty string for the
 directory
 }}}

 in libraries/directory:

 {{{
 Thu Oct 18 13:01:15 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * Move tests from testsuite/tests/ghc-regress/lib/Directory

 Thu Oct 18 13:14:05 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * move copyFile001 from testsuite

 Thu Oct 18 13:17:55 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * import System.Directory, not Directory

 Thu Oct 18 14:06:23 BST 2007  Simon Marlow [EMAIL PROTECTED]
   * add test for #1652
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1652#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


Re: [GHC] #1776: type families : couldn't match type Elem a against type Elem a

2007-10-18 Thread GHC
#1776: type families : couldn't match type Elem a against type Elem a
-+--
Reporter:  guest |Owner:  chak   
Type:  bug   |   Status:  closed 
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.8
Severity:  normal|   Resolution:  fixed  
Keywords:|   Difficulty:  Unknown
  Os:  Unknown   | Testcase: 
Architecture:  Unknown   |  
-+--
Changes (by chak):

  * status:  new = closed
  * resolution:  = fixed

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1776#comment:2
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] #1450: ^C doesn't result in the cost center stack being printed when running with +RTS -xc

2007-10-18 Thread GHC
#1450: ^C doesn't result in the cost center stack being printed when running 
with
+RTS -xc
---+
Reporter:  SamB|Owner:  simonmar  
Type:  bug |   Status:  new   
Priority:  normal  |Milestone:  6.8 branch
   Component:  Runtime System  |  Version:  6.6.1 
Severity:  normal  |   Resolution:
Keywords:  |   Difficulty:  Unknown   
  Os:  Unknown | Testcase:
Architecture:  Unknown |  
---+
Changes (by simonmar):

  * owner:  = simonmar

Comment:

 validating fix

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1450#comment:4
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] #1530: debugging :steps inside TH spliced code need to be bypassed

2007-10-18 Thread GHC
#1530: debugging :steps inside TH spliced code need to be bypassed
-+--
Reporter:  mnislaih  |Owner:
Type:  bug   |   Status:  new   
Priority:  normal|Milestone:  6.8 branch
   Component:  GHCi  |  Version:  6.7   
Severity:  normal|   Resolution:
Keywords:|   Difficulty:  Unknown   
  Os:  Unknown   | Testcase:  dynbrk005 
Architecture:  Unknown   |  
-+--
Changes (by simonmar):

  * owner:  [EMAIL PROTECTED] =

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1530#comment:2
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] #1786: can't build ghc-6.8.0.20071017 under Solaris using a GNU linker

2007-10-18 Thread GHC
#1786: can't build ghc-6.8.0.20071017 under Solaris using a GNU linker
---+
  Reporter:  guest |  Owner: 
  Type:  bug   | Status:  new
  Priority:  normal|  Milestone: 
 Component:  Compiler  |Version:  6.8
  Severity:  normal|   Keywords: 
Difficulty:  Unknown   | Os:  Solaris
  Testcase:|   Architecture:  x86
---+
 if I have a GNU linker first in my PATH then configure allows the -x
 option for linking, but then the stage1/ghc-inplace still uses the Solaris
 linker via gcc and fails:

 {{{
 /usr/ccs/bin/ld: illegal option -- x
 usage: ld [-6:abc:d:e:f:h:il:mo:p:rstu:z:B:CD:F:GI:L:M:N:P:Q:R:S:VY:?]
 file(s)
 [-64]   enforce a 64-bit link-edit
 [-a]create an absolute file
 [-b]do not do special PIC relocations in a.out
 [-B direct | nodirect]
 establish direct bindings, or inhibit direct
 binding
 to, the object being created
 [-B dynamic | static]
 search for shared libraries|archives
 [-B eliminate]  eliminate unqualified global symbols from the
 symbol table
 [-B group]  relocate object from within group
 [-B local]  reduce unqualified global symbols to local
 [-B reduce] process symbol reductions
 [-B symbolic]   bind external references to definitions when
 creating
 shared objects
 [-c name]   record configuration file `name'
 [-C]demangle C++ symbol name diagnostics
 [-d y | n]  operate in dynamic|static mode
 [-D token,...]  print diagnostic messages
 [-e epsym]  use `epsym' as entry point address
 [-f name]   specify library for which this file is an
 auxiliary
 filter
 [-F name]   specify library for which this file is a filter
 [-G]create a shared object
 [-h name]   use `name' as internal shared object identifier
 [-i]ignore LD_LIBRARY_PATH setting
 [-I name]   use `name' as path of interpreter
 [-l x]  search for libx.so or libx.a
 [-L path]   search for libraries in directory `path'
 [-m]print memory map
 [-M mapfile]use processing directives contained in `mapfile'
 [-N string] create a dynamic dependency for `string'
 [-o outfile]name the output file `outfile'
 [-p auditlib]   identify audit library to accompany this object
 [-P auditlib]   identify audit library for processing the
 dependencies
 of this object
 [-Q y | n]  do|do not place version information in output file
 [-r]create a relocatable object
 [-R path]   specify a library search path to be used at run
 time
 [-s]strip any symbol and debugging information
 [-S supportlib]
 specify a link-edit support library
 [-t]do not warn of multiply-defined symbols that have
 different sizes or alignments
 [-u symname]create an undefined symbol `symname'
 [-V]print version information
 [-Y P,dirlist]  use `dirlist' as a default path when searching for
 libraries
 [-z absexec]when building an executable absolute symbols
 referenced in dynamic objects are promoted to
 the executable
 [-z allextract | defaultextract | weakextract]
 extract all member files, only members that
 resolve
 undefined tor tentative symbols, or allow
 extraction of
 archive members to resolvetweak references from
 archive files
 [-z altexec64]  execute the 64-bit link-editor
 [-z combreloc]  combine multiple relocation sections
 [-z defs]   disallow undefined symbol references
 [-z direct | nodirect]
 enable|disable direct binding to shared object
 dependencies
 [-z endfiltee]  marks a filtee such that it will terminate a
 filters
 search
 [-z finiarray=function]
 name of function to be appended to the .finiarray
 [-z groupperm | nogroupperm]
 enable|disable setting of group permissions
 on dynamic dependencies
 [-z help ]  print this usage message
 [-z ignore | record]
 

Re: [GHC] #1395: let ./configure check for a GNUreadline framework

2007-10-18 Thread GHC
#1395: let ./configure check for a GNUreadline framework
+---
Reporter:  [EMAIL PROTECTED]|Owner: 
Type:  feature request  |   Status:  reopened   
Priority:  normal   |Milestone:  6.8 branch 
   Component:  Build System |  Version:  6.8
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Easy (1 hr)
  Os:  MacOS X  | Testcase: 
Architecture:  Multiple |  
+---
Changes (by guest):

  * status:  closed = reopened
 * cc: [EMAIL PROTECTED] (added)
  * version:  6.6.1 = 6.8
  * resolution:  fixed =

Comment:

 It would be nice if also the frameworks under `$HOME/Library/Frameworks`
 are checked (and used) when building ghc. This requires an extra flag
 `-F$HOME/Library/Frameworks`.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1395#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


Re: [GHC] #1785: xargs failure

2007-10-18 Thread GHC
#1785: xargs failure
-+--
Reporter:  guest |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.8
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Solaris   | Testcase: 
Architecture:  x86   |  
-+--
Comment (by guest):

 `xargs -s 3` is hard-coded in
 `libraries/Cabal/Distribution/Simple/GHC/Makefile.in`

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1785#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


Re: [GHC] #1785: xargs failure

2007-10-18 Thread GHC
#1785: xargs failure
-+--
Reporter:  guest |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone:  6.8.1  
   Component:  Compiler  |  Version:  6.8
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Solaris   | Testcase: 
Architecture:  x86   |  
-+--
Changes (by igloo):

  * milestone:  = 6.8.1

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1785#comment:2
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] #1395: let ./configure check for a GNUreadline framework

2007-10-18 Thread GHC
#1395: let ./configure check for a GNUreadline framework
+---
Reporter:  [EMAIL PROTECTED]|Owner: 
Type:  feature request  |   Status:  reopened   
Priority:  normal   |Milestone:  6.8 branch 
   Component:  Build System |  Version:  6.8
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Easy (1 hr)
  Os:  MacOS X  | Testcase: 
Architecture:  Multiple |  
+---
Comment (by igloo):

 Does this make a runtime dependency on frameworks in
 $HOME/Library/Frameworks? If so then this sounds like it could cause
 problems for a multi-user system.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1395#comment:4
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] #1395: let ./configure check for a GNUreadline framework

2007-10-18 Thread GHC
#1395: let ./configure check for a GNUreadline framework
+---
Reporter:  [EMAIL PROTECTED]|Owner: 
Type:  feature request  |   Status:  reopened   
Priority:  normal   |Milestone:  6.8 branch 
   Component:  Build System |  Version:  6.8
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Easy (1 hr)
  Os:  MacOS X  | Testcase: 
Architecture:  Multiple |  
+---
Comment (by guest):

 Replying to [comment:4 igloo]:

 Interesting question. I've created the mac binary dists with a local
 GNUreadline framework. I hope my home directory wasn't left as framework
 search path in the ghc-6.6.1 binary. man ld on Mac did not give me a
 clue about this. (There's nothing like a RUN_LIBRARY_PATH.)

 {{{
-search_paths_first
   By  default  when  the  -dynamic  flag is in effect, the -lx
 and
   -weak-lx  options  first  search  for  a  file   of   the
 form
   `libx.dylib'  in each directory in the library search path,
 then
   a file of the form `libx.a'  is  searched  for  in  the
 library
   search  paths.   This  option  changes  it  so that in each
 path
   `libx.dylib' is searched for then `libx.a' before the next
 path
   in the library search path is searched.

-framework name[,suffix]
   Specifies  a  framework  to link against. Frameworks are
 dynamic
   shared libraries, but they are stored  in  different
 locations,
   and therefore must be searched for differently. When this
 option
   is specified, ld searches  for  framework
 `name.framework/name'
   first  in  any directories specified with the -F option,
 then in
   the standard framework  directories  /Library/Frameworks,
 /Net-
   work/Library/Frameworks,  and  /System/Library/Frameworks.
 The
   placement of the -framework option is significant, as it
 deter-
   mines  when  and how the framework is searched.  If the
 optional
   suffix is specified the framework is first searched for the
 name
   with the suffix and then without.

-weak_framework name[,suffix]
   This  is the same as the -framework name[,suffix] but forces
 the
   framework and all references to it to be marked as weak
 imports.
   Care  must  be  taken when using this as the use of the non-
 weak
   symbol references in an object file may  cause  the  program
 to
   crash  when  the symbol or framework is not present at
 execution
   time.

-Fdir  Add dir to the list of directories in which to search for
 frame-
   works.   Directories  specified  with -F are searched before
 the
   standard framework directories.
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1395#comment:5
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] #1395: let ./configure check for a GNUreadline framework

2007-10-18 Thread GHC
#1395: let ./configure check for a GNUreadline framework
+---
Reporter:  [EMAIL PROTECTED]|Owner: 
Type:  feature request  |   Status:  reopened   
Priority:  normal   |Milestone:  6.8 branch 
   Component:  Build System |  Version:  6.8
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Easy (1 hr)
  Os:  MacOS X  | Testcase: 
Architecture:  Multiple |  
+---
Comment (by guest):

 I didn't find any dependencies in my binaries created with local
 frameworks (using grep and otool).
 Christian

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1395#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: bug 1711 revisited

2007-10-18 Thread Hal Perkins

Hi Ian -

Here's what I've found:

- libraries/haskell-src/Language/Haskell/Parser.hs still exists at  
the point the build stopped, with the original Oct.15 timestamp.


- the suggested make.rebuild... command fails with the same problem.   
Console output:


 make rebuild.library.haskell-src
rm -f -f stamp/configure.library.*.haskell-src haskell-src/unbuildable
cd haskell-src  setup/Setup clean
cleaning...
rm -f -rf haskell-src/setup
rm -f haskell-src/GNUmakefile haskell-src/Makefile.local
rm -f -rf haskell-src/setup
mkdir haskell-src/setup
cp haskell-src/Setup.*hs haskell-src/setup
cd haskell-src/setup  /usr/local/bin/ghc -Wall -cpp --make  
Setup.*hs -o Setup \
  -i../../bootstrapping.Cabal -i../../ 
bootstrapping.filepath

[42 of 42] Compiling Main ( Setup.hs, Setup.o )
Linking Setup ...
rm -f -f stamp/configure.library.*.haskell-src haskell-src/unbuildable
( cd haskell-src  setup/Setup configure \
--enable-library-profiling --enable-split-objs \
   --prefix=/NONEXISTANT \
   --bindir=/NONEXISTANT \
   --libdir=/NONEXISTANT \
   --libsubdir='$pkgid' \
   --libexecdir=/NONEXISTANT \
   --datadir=/NONEXISTANT \
   --docdir=/NONEXISTANT \
   --htmldir=/NONEXISTANT \
   --with-compiler=../../compiler/stage1/ghc-inplace \
   --with-hc-pkg=../../utils/ghc-pkg/ghc-pkg-inplace \
   --with-hsc2hs=../../utils/hsc2hs/hsc2hs-inplace \
   --with-ld=/usr/bin/ld \
   --haddock-options=--use-contents=../index.html \
   --use-index=../doc-index.html \
  \
   --configure-option=--with-cc=gcc ) \
   touch stamp/configure.library.build-profiling- 
splitting.haskell-src || touch haskell-src/unbuildable

Configuring haskell-src-1.0.1...
rm -f haskell-src/GNUmakefile
cp Makefile.local haskell-src
if ifBuildable/ifBuildable haskell-src; then \
   cd haskell-src  setup/Setup makefile -f GNUmakefile; \
fi
Preprocessing library haskell-src-1.0.1...
Setup: happy command not found
make: *** [haskell-src/GNUmakefile] Error 1


- I couldn't find a Parser.y file in haskell-src/Language/Haskell,  
but there was a Parser.ly file.  When I removed that and reran the  
make command it ran for a while and eventually completed with:


== Finished recursively making `all' for ways: p ...
Registering haskell-src-1.0.1...
Reading package info from dist/inplace-pkg-config ... done.
Saving old package config file... done.
Writing new package config file... done.

which looks like success.

Once that worked, I changed to the main directory (..) and ran make  
from there to continue the build, and that appears to have completed  
normally.


Hope that gives you some clues about what to do next.

Thanks

Hal



On Oct 17, 2007, at 11:33 AM, Ian Lynagh wrote:



Hi Hal,

On Tue, Oct 16, 2007 at 09:54:32PM -0700, Hal Perkins wrote:

Sorry to revive a dead horse, but there's still a bit of a problem
with building ghc on os x because of missing files that need to be
created by happy.  I downloaded the current stable sources yesterday
(ghc-6.8.0.20071015-src.tar.bz2 and ghc-6.8.0.20071015-src-
extralibs.tar.bz2)


OK, ghc-6.8.0.20071015-src-extralibs.tar.bz2 definitely includes

libraries/haskell-src/Language/Haskell/Parser.hs


Preprocessing library haskell-src-1.0.1...
Setup: happy command not found
make[1]: *** [haskell-src/GNUmakefile] Error 1


Does the above file still exist at this point?

If so, does
cd libraries
touch haskell-src/Language/Haskell/Parser.hs
make rebuild.library.haskell-src
work?

If that doesn't do it, what about if you delete
haskell-src/Language/Haskell/Parser.y
and then try
make rebuild.library.haskell-src
?


Thanks
Ian




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


[GHC] #1787: Test.QuickCheck does not install (unbuildable) in HEAD

2007-10-18 Thread GHC
#1787: Test.QuickCheck does not install (unbuildable) in HEAD
+---
  Reporter:  guest  |  Owner: 
  Type:  bug| Status:  new
  Priority:  normal |  Milestone: 
 Component:  libraries (other)  |Version:  6.9
  Severity:  major  |   Keywords: 
Difficulty:  Unknown| Os:  Unknown
  Testcase: |   Architecture:  Unknown
+---
 Title says it all.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1787
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] #1429: debugger src locations break with lhs files

2007-10-18 Thread GHC
#1429: debugger src locations break with lhs files
-+--
Reporter:  mnislaih  |Owner:
Type:  bug   |   Status:  reopened  
Priority:  normal|Milestone:  6.8 branch
   Component:  GHCi  |  Version:  6.7   
Severity:  minor |   Resolution:
Keywords:  debugger  |   Difficulty:  Unknown   
  Os:  Unknown   | Testcase:
Architecture:  Unknown   |  
-+--
Changes (by mnislaih):

  * status:  closed = reopened
  * resolution:  invalid =
  * severity:  major = minor

Old description:

 Probably srclocs being used by the debugger are those of the unlit-ed
 source tree.

 Things that fail include
  * :break line sets the breakpoint in the wrong place
  * :list
  * the ghci prompt

New description:

 A bang pattern in a .lhs file confuses :list by one line

Comment:

 I found it, it is a bang pattern in a .lhs file.
 Try with the usual suspect, a Setup.lhs file.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1429#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


Re: [GHC] #1429: :list gets confused by bang patterns in .lhs files

2007-10-18 Thread GHC
#1429: :list gets confused by bang patterns in .lhs files
-+--
Reporter:  mnislaih  |Owner:
Type:  bug   |   Status:  reopened  
Priority:  normal|Milestone:  6.8 branch
   Component:  GHCi  |  Version:  6.7   
Severity:  minor |   Resolution:
Keywords:  debugger  |   Difficulty:  Unknown   
  Os:  Unknown   | Testcase:
Architecture:  Unknown   |  
-+--
Changes (by mnislaih):

  * summary:  debugger src locations break with lhs files = :list gets
  confused by bang patterns in .lhs files

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1429#comment:4
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] #1788: panic with Template Haskell splicing/quoting

2007-10-18 Thread GHC
#1788: panic with Template Haskell splicing/quoting
---+
  Reporter:  guest |  Owner: 
  Type:  bug   | Status:  new
  Priority:  normal|  Milestone: 
 Component:  Compiler  |Version:  6.6.1  
  Severity:  normal|   Keywords: 
Difficulty:  Unknown   | Os:  Unknown
  Testcase:|   Architecture:  Unknown
---+
 I got a panic when quoting a name in some qualified module.  The
 demonstration code is at http://hpaste.org/3380.  See
 http://hpaste.org/3380/diff?old=1new=2 for the diff between the panicky
 and non-panicky versions.

 This looks very similar to bug #1755, but shachaf in #haskell says it
 affects GHC 6.9.20071012.

 #haskell discussion log, search for 'panic' around 00:29:
 http://ircbrowse.com/channel/haskell/20071019

 -- Nicholas Messenger ([EMAIL PROTECTED], omnId on #haskell)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1788
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] #1786: can't build ghc-6.8.0.20071017 under Solaris using a GNU linker

2007-10-18 Thread GHC
#1786: can't build ghc-6.8.0.20071017 under Solaris using a GNU linker
-+--
Reporter:  guest |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone:  6.8.1  
   Component:  Compiler  |  Version:  6.8
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Solaris   | Testcase: 
Architecture:  x86   |  
-+--
Comment (by duncan):

 This is a Cabal bug. See:
 http://hackage.haskell.org/trac/hackage/ticket/98

 Distribution/Simple/GHC.hs line 374:
 {{{
   ldArgs = [-r]
 ++ [-x] -- FIXME: only some systems's ld support the -x flag
 ++ [-o, ghciLibName . tmp]
 }}}

 We could fix this with a test during the configure step, or we could hack
 it and assume that if we're on Solaris then we never use -x. The latter is
 easy, the former is better.

 Probably the right thing to do is in the configure step (in the
 Distribution.Simple.Configure.configure function) is after all the known
 programs have been configured, to run ld and test if it supports -x. If it
 does, use lookupProgram/updateProgram to update the ProgramConfiguration
 with the configured ld program modified to have programArgs = [-x].

 Any volunteers?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1786#comment:2
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] #1787: Test.QuickCheck does not install (unbuildable) in HEAD

2007-10-18 Thread GHC
#1787: Test.QuickCheck does not install (unbuildable) in HEAD
--+-
Reporter:  guest  |Owner:  duncan 
Type:  bug|   Status:  new
Priority:  normal |Milestone: 
   Component:  libraries (other)  |  Version:  6.9
Severity:  major  |   Resolution: 
Keywords: |   Difficulty:  Unknown
  Os:  Unknown| Testcase: 
Architecture:  Unknown|  
--+-
Changes (by duncan):

  * owner:  = duncan

Comment:

 This is my fault and it should be fixed now, though that needs to be
 confirmed.

 I was updating ghc-6.8 to bootstrap cabal correctly and then taking
 advantage of that fix to update several packages to use cabal-1.2 features
 and add the cabal-version: =1.2 to the .cabal files of those libs.
 Cabal needs to be bootstraped correctly for this to work, otherwise it
 does not know it's own version number and will barf when it tries to check
 cabal-version: =1.2.

 So I fixed that in ghc-6.8 and updated a bunch of packages and validated.
 However many of those packages are aliased to packages used by ghc HEAD.
 QuickCheck is one of them. So in the mean time ghc HEAD was still not
 bootstrapping Cabal correctly so it fell over when it found
 QuickCheck.cabal specified cabal-version: =1.2. That's why it was
 unbuildable.

 I've now validated and pushed the same fix to bootstrap Cabal in ghc HEAD
 (and updated Cabal to match Cabal HEAD while I was at it).

 So it should now be fixed.

 It's amazing, I validated dozens of patches today and still managed to
 break ghc HEAD once and ghc-6.8 three times. I broke ghc-6.8 twice (with
 the same mistake of tabs in .cabal files which I still don't know how it
 got through) and once due to breaking windows which I didn't pick up with
 validating on linux (that should also be fixed). Then as I said, I broke
 ghc HEAD without ever touching it, but because parts of it are aliased
 with parts from the ghc-6.8 which I was modifying.

 The good news is that almost every core and extralib package builds with
 ghc-6.6 and 6.8 (where it makes sense for them to build with 6.6) and many
 also build with 6.4.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1787#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


Re: -O in 6.8.1-candidate

2007-10-18 Thread Duncan Coutts
On Thu, 2007-10-18 at 11:02 +0400, Serge D. Mechveliani wrote: 
 On Oct 17, 2007, Don Stewart and Duncan Coutts wrote: 
 
   [..]
   By default cabal uses ghc -O to build projects, so you won't see any
   difference if you comment it out of the cabal file. You will however
   if you explicitly turn off optimisations:
   
   ghc-options: -Onot
  
  or:
  
  cabal-setup configure --disable-optimization
  
  since the default is --enable-optimization which with ghc uses -O

 For GHC, it is necessary for the  .cabal  file to provide the field
 `ghc-options:',
 and the optimization keys are of this field.
 Hence, is not this confusing to allow the optimization keys anywhere 
 else?
 Also seeing `--enable-optimization' the user needs also to recall of what 
 kind of optimization is it.

The ghc-options field allows you to pass anything flags you like to ghc.
That does not mean that you should! :-)

Cabal is supposed to be portable between Haskell implementations and to
allow packages to also be portable. Some Haskell implementations provide
a notion of optimisation and so Cabal supports that with the
--enable-optimization flag.

There's an additional advantage here, we can let the user decide if they
want to build with or without optimization. With the ghc-options field,
only the developer gets to decide.

So, in summary it's much better not* to use lines like:

ghc-options: -O

and to let the user manage that with Cabal's --enable-optimization flag
(which is on by default).

If you have specific ghc optimisations that you really need to be
applied, then it's ok to use the ghc-options: field. For example we use
that in bytestring.

The --enable-optimization flag also applies to other things, like
compiling C code and in principle could apply to other tools like
happy/alex, though at the moment it does not.

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