[GHC] #4984: OS X: ld: warning: -read_only_relocs cannot be used with x86_64

2011-02-26 Thread GHC
#4984: OS X: ld: warning: -read_only_relocs cannot be used with x86_64
-+--
Reporter:  igloo |Owner:  
Type:  bug   |   Status:  new 
Priority:  high  |Milestone:  7.0.3   
   Component:  Compiler  |  Version:  7.0.1   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
 From http://www.haskell.org/pipermail/glasgow-haskell-
 users/2011-February/020086.html

 {{{
 I'm getting a warning from the linker when building programs using the
 64-bit
 version of the release candidate on Mac OS X 10.6.

 $ cat Hello.hs
 module Main where
 main = putStrLn "Hello, World"

 $ ~/ghc-7/bin/ghc -fforce-recomp Hello.hs
 [1 of 1] Compiling Main ( Hello.hs, Hello.o )
 Linking Hello ...
 ld: warning: -read_only_relocs cannot be used with x86_64

 It doesn't seem to cause a problem when actually running the programs,
 from what
 I have seen so far.
 }}}

-- 
Ticket URL: 
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] #4982: ghc-7.0.1: make install sets not enough permissions on library documentation

2011-02-26 Thread GHC
#4982: ghc-7.0.1: make install sets not enough permissions on library
documentation
-+--
Reporter:  Lemming   |Owner:   
Type:  bug   |   Status:  new  
Priority:  high  |Milestone:  7.0.3
   Component:  Build System  |  Version:  7.0.1
Keywords:| Testcase:   
   Blockedby:|   Difficulty:   
  Os:  Linux | Blocking:   
Architecture:  x86   |  Failure:  Installing GHC failed
-+--
Changes (by igloo):

  * priority:  normal => high
  * milestone:  => 7.0.3


Comment:

 Thanks for the report. Confirmed with 7.0.2 RC 2:
 {{{
 $ umask
 077
 $ ./configure --prefix=`pwd`/inst
 [...]
 $ make install
 [...]
 $ ls -l inst/share/doc/ghc/html/libraries
 total 3644
 drwx-- 3 ian ian   12288 Feb 26 21:25 Cabal-1.10.1.0
 drwx-- 3 ian ian4096 Feb 26 21:25 array-0.3.0.2
 drwx-- 3 ian ian   20480 Feb 26 21:25 base-4.3.1.0
 drwx-- 3 ian ian4096 Feb 26 21:25 bin-package-db-0.0.0.0
 drwx-- 3 ian ian4096 Feb 26 21:25 bytestring-0.9.1.10
 drwx-- 3 ian ian4096 Feb 26 21:25 containers-0.4.0.0
 drwx-- 3 ian ian4096 Feb 26 21:25 directory-1.1.0.0
 -rw-r--r-- 1 ian ian3437 Feb 26 21:25 doc-index-124.html
 -rw-r--r-- 1 ian ian4650 Feb 26 21:25 doc-index-33.html
 -rw-r--r-- 1 ian ian4269 Feb 26 21:25 doc-index-36.html
 [...]
 }}}

-- 
Ticket URL: 
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] #4983: Warning about redundant import is wrong when hiding identifiers in order to avoid export ambiguities

2011-02-26 Thread GHC
#4983: Warning about redundant import is wrong when hiding identifiers in order 
to
avoid export ambiguities
+---
  Reporter:  Lemming|  Owner:   
   
  Type:  bug| Status:  closed   
   
  Priority:  normal |  Milestone:   
   
 Component:  Compiler   |Version:  7.0.1
   
Resolution:  wontfix|   Keywords:   
   
  Testcase: |  Blockedby:   
   
Difficulty: | Os:  
Unknown/Multiple
  Blocking: |   Architecture:  
Unknown/Multiple
   Failure:  Incorrect warning at compile-time  |  
+---
Changes (by igloo):

  * status:  new => closed
  * resolution:  => wontfix


Comment:

 I think the warning is OK in this case: You've explicitly imported the
 `Prelude` and then used nothing from it. You need to do
 {{{
 import Prelude ()
 }}}
 if you want to explicitly import it (which you need to do to avoid the
 name collision), but import nothing from it.

-- 
Ticket URL: 
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] #4981: inconsistent class requirements with TypeFamilies and FlexibleContexts

2011-02-26 Thread GHC
#4981: inconsistent class requirements with TypeFamilies and FlexibleContexts
-+--
Reporter:  ganesh|   Owner:   
Type:  bug   |  Status:  new  
Priority:  normal|   Component:  Compiler (Type checker)  
 Version:  7.0.1 |Keywords:   
Testcase:|   Blockedby:   
  Os:  Unknown/Multiple  |Blocking:   
Architecture:  Unknown/Multiple  | Failure:  GHC rejects valid program
-+--
Changes (by dimitris):

  * component:  Compiler => Compiler (Type checker)


Comment:

 Right, I know what's going on. The problem we are solving is:
 {{{
   [Given] Conflict (OnPrim p),
  + its superclass: [Given] (PatchInspect (PrimOf (FL (OnPrim p
   [Given]  PrimOf (OnPrim p) ~ WithName (PrimOf p)
   [Wanted] Conflict (FL (OnPrim p))
 }}}
 Now, we apply the instance to get new work:
 {{{
   [Wanted] Conflict (OnPrim p)
   [Wanted] PatchInspect (PrimOf (FL (OnPrim p)))
 }}}
 The second guy is the "silent parameter" wanted. Now, the Conflict wanted
 can be
 readily discharged so let's not worry about him. However:
 {{{
   [Wanted] PatchInspect (PrimOf (FL (OnPrim p))) ~~>
  [Wanted] PatchInspect (PrimOf (OnPrim p))
 }}}
 Now, this ''could'' be readily discharged by the given but instead what
 happens
 is that it gets rewritten with the given equality to:
 {{{
[Wanted] PatchInspect (WithName (PrimOf p))
 }}}
 Then the instance triggers, and we get:
 {{{
[Wanted] PatchInspect (PrimOf p)
 }}}
 which is the error we see.

 So indeed this program is in muddy territory where givens (superclasses of
 givens, actually!) overlap with top-level instances.

 I know why GHC is not picking the given up: it has to do with the fact
 that we have
 not saturated all possible equalities before we look for instances, but
 luckily this
 is something Simon and I are planning to fix pretty soon. The other thing
 that we should also do is remove these silent superclass parameters --
 they used to exist
 for reasons related to recursive dictionaries but they are not necessary
 any more
 the way we have dealt with recursive dictionaries at the end.

-- 
Ticket URL: 
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] #4385: Type-level natural numbers

2011-02-26 Thread GHC
#4385: Type-level natural numbers
+---
Reporter:  diatchki |Owner:  diatchki
Type:  feature request  |   Status:  new 
Priority:  normal   |Milestone:  7.2.1   
   Component:  Compiler (Type checker)  |  Version:  
Keywords:   | Testcase:  
   Blockedby:   |   Difficulty:  
  Os:  Unknown/Multiple | Blocking:  
Architecture:  Unknown/Multiple |  Failure:  None/Unknown
+---
Changes (by djahandarie):

 * cc: djahandarie@… (added)


-- 
Ticket URL: 
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] #4983: Warning about redundant import is wrong when hiding identifiers in order to avoid export ambiguities

2011-02-26 Thread GHC
#4983: Warning about redundant import is wrong when hiding identifiers in order 
to
avoid export ambiguities
-+--
Reporter:  Lemming   |   Owner: 
  
Type:  bug   |  Status:  new
  
Priority:  normal|   Component:  Compiler   
  
 Version:  7.0.1 |Keywords: 
  
Testcase:|   Blockedby: 
  
  Os:  Unknown/Multiple  |Blocking: 
  
Architecture:  Unknown/Multiple  | Failure:  Incorrect warning at 
compile-time
-+--
 Although warnings about redundant imports are almost perfect since
 GHC-6.12, I have a corner case, where the warning about a redundant import
 is wrong.
 Consider the module
 {{{
 module Data.Monoid.HT (cycle, ) where

 import Data.Monoid (Monoid, mappend, )
 import Data.Function (fix, )

 import Prelude hiding (cycle, )

 {- |
 Generalization of 'Data.List.cycle' to any monoid.
 -}
 cycle :: Monoid m => m -> m
 cycle x =
fix (mappend x)
 }}}

 GHC says:
 {{{
 src/Data/Monoid/HT.hs:6:1:
 Warning: The import of `Prelude' is redundant
except perhaps to import instances from `Prelude'
  To import instances alone, use: import Prelude()
 }}}

 I have to hide 'cycle' from Prelude if I want to export it unqualified.

 I have several work-arounds: Export 'cycle' with qualification, use no
 export list at all, import from Prelude by enumeration of needed
 functions. I think this problem has low priority. I report it just for the
 case that someone claims that Haskell's module system is simple and could
 be more complicated. ;-)

-- 
Ticket URL: 
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] #4982: ghc-7.0.1: make install sets not enough permissions on library documentation

2011-02-26 Thread GHC
#4982: ghc-7.0.1: make install sets not enough permissions on library
documentation
+---
Reporter:  Lemming  |   Owner:   
Type:  bug  |  Status:  new  
Priority:  normal   |   Component:  Build System 
 Version:  7.0.1|Keywords:   
Testcase:   |   Blockedby:   
  Os:  Linux|Blocking:   
Architecture:  x86  | Failure:  Installing GHC failed
+---
Changes (by Lemming):

  * failure:  None/Unknown => Installing GHC failed


-- 
Ticket URL: 
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] #4982: ghc-7.0.1: make install sets not enough permissions on library documentation

2011-02-26 Thread GHC
#4982: ghc-7.0.1: make install sets not enough permissions on library
documentation
+---
Reporter:  Lemming  |   Owner:  
Type:  bug  |  Status:  new 
Priority:  normal   |   Component:  Build System
 Version:  7.0.1|Keywords:  
Testcase:   |   Blockedby:  
  Os:  Linux|Blocking:  
Architecture:  x86  | Failure:  None/Unknown
+---

Comment(by Lemming):

 I think we already had this problem in an earlier release: #2781

-- 
Ticket URL: 
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] #4982: ghc-7.0.1: make install sets not enough permissions on library documentation

2011-02-26 Thread GHC
#4982: ghc-7.0.1: make install sets not enough permissions on library
documentation
+---
Reporter:  Lemming  |   Owner:  
Type:  bug  |  Status:  new 
Priority:  normal   |   Component:  Build System
 Version:  7.0.1|Keywords:  
Testcase:   |   Blockedby:  
  Os:  Linux|Blocking:  
Architecture:  x86  | Failure:  None/Unknown
+---

Comment(by Lemming):

 The same applies to the files in
 /usr/local/lib/ghc-7.0.1/package.conf.d/
 and the library directories in
 /usr/local/lib/ghc-7.0.1/
 such as
 {{{
 /usr/local/lib/ghc-7.0.1/array-0.3.0.2/
 /usr/local/lib/ghc-7.0.1/base-4.3.0.0/
 ...
 }}}

-- 
Ticket URL: 
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] #4982: ghc-7.0.1: make install sets not enough permissions on library documentation

2011-02-26 Thread GHC
#4982: ghc-7.0.1: make install sets not enough permissions on library
documentation
+---
Reporter:  Lemming  |   Owner:  
Type:  bug  |  Status:  new 
Priority:  normal   |   Component:  Build System
 Version:  7.0.1|Keywords:  
Testcase:   |   Blockedby:  
  Os:  Linux|Blocking:  
Architecture:  x86  | Failure:  None/Unknown
+---
 I have installed GHC-7.0.1 from
 http://www.haskell.org/ghc/dist/7.0.1/ghc-7.0.1-i386-unknown-linux.tar.bz2
 and installed it with 'configure' and 'sudo make install'.
 I get:

 {{{
 $ ls -l /usr/local/share/doc/ghc/html/libraries/
 drwx--  3 root root   4096 2011-02-26 20:23 array-0.3.0.2
 drwx--  3 root root  16384 2011-02-26 20:22 base-4.3.0.0
 drwxr-xr-x  3 root root   4096 2011-02-26 20:23 bin-package-db-0.0.0.0
 drwx--  3 root root   4096 2011-02-26 20:23 bytestring-0.9.1.8
 drwx--  3 root root  12288 2011-02-26 20:23 Cabal-1.10.0.0
 ...
 }}}

 {{{
 $ ls -l /usr/local/share/doc/ghc/html/
 drwxr-xr-x  2 root root 4096 2011-02-26 20:24 Cabal
 drwxr-xr-x  2 root root 4096 2011-02-26 20:24 haddock
 drwx--  4 root root 4096 2011-02-26 19:31 html
 -rw-r--r--  1 root root 1557 2011-02-26 20:24 index.html
 drwxr-xr-x 66 root root 4096 2011-02-26 20:24 libraries
 drwxr-xr-x  2 root root 4096 2011-02-26 20:24 users_guide
 }}}

 That is, the library documentation directories and
 /usr/local/share/doc/ghc/html/html/ have not enough permissions set for
 user access.

-- 
Ticket URL: 
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] #4981: inconsistent class requirements with TypeFamilies and FlexibleContexts

2011-02-26 Thread GHC
#4981: inconsistent class requirements with TypeFamilies and FlexibleContexts
-+--
Reporter:  ganesh|   Owner:   
Type:  bug   |  Status:  new  
Priority:  normal|   Component:  Compiler 
 Version:  7.0.1 |Keywords:   
Testcase:|   Blockedby:   
  Os:  Unknown/Multiple  |Blocking:   
Architecture:  Unknown/Multiple  | Failure:  GHC rejects valid program
-+--
Changes (by dimitris):

 * cc: dimitris@… (added)


-- 
Ticket URL: 
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] #4981: inconsistent class requirements with TypeFamilies and FlexibleContexts

2011-02-26 Thread GHC
#4981: inconsistent class requirements with TypeFamilies and FlexibleContexts
-+--
Reporter:  ganesh|   Owner:   
Type:  bug   |  Status:  new  
Priority:  normal|   Component:  Compiler 
 Version:  7.0.1 |Keywords:   
Testcase:|   Blockedby:   
  Os:  Unknown/Multiple  |Blocking:   
Architecture:  Unknown/Multiple  | Failure:  GHC rejects valid program
-+--
 If I build the code below with -DVER=2, I get a complaint about
 PatchInspect (PrimOf p) being missing from the context of
 cleverNamedResolve.

 This doesn't happen with -DVER=1 or -DVER=3

 I presume that type class resolution is operating slightly differently in
 the different cases, but it's quite confusing - in the original code
 joinPatches did something useful and I was trying to inline the known
 instance definition. I would have expected it to be consistent between all
 three cases, either requiring the context or not.

 {{{
 {-# LANGUAGE CPP, TypeFamilies, FlexibleContexts #-}
 module Class ( cleverNamedResolve ) where

 data FL p = FL p

 class PatchInspect p where
 instance PatchInspect p => PatchInspect (FL p) where

 type family PrimOf p
 type instance PrimOf (FL p) = PrimOf p

 data WithName prim = WithName prim

 instance PatchInspect prim => PatchInspect (WithName prim) where

 class (PatchInspect (PrimOf p)) => Conflict p where
 resolveConflicts :: p -> PrimOf p

 instance Conflict p => Conflict (FL p) where
 resolveConflicts = undefined

 type family OnPrim p

 #if VER==1
 class FromPrims p where

 instance FromPrims (FL p) where

 joinPatches :: FromPrims p => p -> p
 #else
 #if VER==2
 joinPatches :: FL p -> FL p
 #else
 joinPatches :: p -> p
 #endif
 #endif

 joinPatches = id

 cleverNamedResolve :: (Conflict (OnPrim p)
   ,PrimOf (OnPrim p) ~ WithName (PrimOf p))
=> FL (OnPrim p) -> WithName (PrimOf p)
 cleverNamedResolve = resolveConflicts . joinPatches

 }}}

-- 
Ticket URL: 
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] #2722: < when compiling with -O option with ghc-6.10.0.20081019

2011-02-26 Thread GHC
#2722: < when compiling with -O option with ghc-6.10.0.20081019
-+--
  Reporter:  uwe |  Owner:  simonpj   
  Type:  bug | Status:  infoneeded
  Priority:  normal  |  Milestone:  7.0.3 
 Component:  libraries (other)   |Version:  7.0.1 
Resolution:  |   Keywords:  arrows
  Testcase:  tyepcheck/should_run/T2722  |  Blockedby:
Difficulty:  Unknown | Os:  Linux 
  Blocking:  |   Architecture:  x86_64 (amd64)
   Failure:  Runtime crash   |  
-+--

Comment(by litoh):

 The problem remains, here's what I did:

 Installed new darcs to avoid sleeping:
 $ darcs -v
 > 2.5.1 (release)

 I followed the GHC build guides at
 http://hackage.haskell.org/trac/ghc/wiki/Building/Hacking (with --no-cache
 option)
 $ darcs get --lazy --no-cache http://darcs.haskell.org/ghc
 $ ./darcs-all --testsuite get

 in mk/build.mk:
 BuidlFlavour = prof

 $ perl boot
 $ ./configure --with-ghc=/usr/local/bin/ghc-7.0.1.20110217
 (I had to recompile for profiling support and define an older GHC build. I
 used the current RC build)
 $ make -j2
 $ make install
 $ ghc --version
 > The Glorious Glasgow Haskell Compilation System, version 7.1.20110223

 $ cabal install yampa
 $ ghc --make Test.hs -o test -O2 -fforce-recomp
 > test: <>

 :/

-- 
Ticket URL: 
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] #4978: Continuation passing style loop doesn't compile into a loop

2011-02-26 Thread GHC
#4978: Continuation passing style loop doesn't compile into a loop
-+--
Reporter:  tibbe |Owner:  
Type:  bug   |   Status:  new 
Priority:  normal|Milestone:  
   Component:  Compiler  |  Version:  7.0.1   
Keywords:| Testcase:  
   Blockedby:|   Difficulty:  
  Os:  Unknown/Multiple  | Blocking:  
Architecture:  Unknown/Multiple  |  Failure:  None/Unknown
-+--
Changes (by dleuschner):

 * cc: leuschner@… (added)


-- 
Ticket URL: 
GHC 
The Glasgow Haskell Compiler

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