Re: [GHC] #7354: Panic with recursion-schemes package and unit

2012-10-28 Thread GHC
#7354: Panic with recursion-schemes package and unit
---+
Reporter:  amplitwist  |   Owner:  
Type:  bug |  Status:  new 
Priority:  normal  |   Milestone:  
   Component:  GHCi| Version:  7.6.1   
Keywords:  |  Os:  Linux   
Architecture:  x86_64 (amd64)  | Failure:  GHCi crash  
  Difficulty:  Unknown |Testcase:  indexed_types/T7354a, T7354b
   Blockedby:  |Blocking:  
 Related:  |  
---+

Comment(by amplitwist):

 OK, that'll do.  Good to see it's fixed in HEAD.

-- 
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] #7374: rule not firing

2012-10-28 Thread GHC
#7374: rule not firing
-+--
Reporter:  igloo |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by carter):

 * cc: carter.schonwald@… (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


Re: [GHC] #7374: rule not firing

2012-10-28 Thread GHC
#7374: rule not firing
-+--
Reporter:  igloo |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by kazu-yamamoto):

 * cc: kazu@… (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


Re: [GHC] #7356: Building HEAD on Mac OS X 10.5 reports Undefined "_pthread_threadid_np" ref'd from _kernelThreadId in libHSrts_thr.a(OSThreads.thr_o)

2012-10-28 Thread GHC
#7356: Building HEAD on Mac OS X 10.5 reports Undefined "_pthread_threadid_np"
ref'd from _kernelThreadId in libHSrts_thr.a(OSThreads.thr_o)
-+--
 Reporter:  thorkilnaur  |  Owner:
 Type:  bug  | Status:  patch 
 Priority:  normal   |  Component:  Runtime System
  Version:  7.7  |   Keywords:
   Os:  MacOS X  |   Architecture:  x86   
  Failure:  Building GHC failed  |   Testcase:
Blockedby:   |   Blocking:
  Related:   |  
-+--

Comment(by spl):

 The patch compiles for me on 10.5.

-- 
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] #7374: rule not firing

2012-10-28 Thread GHC
#7374: rule not firing
-+--
Reporter:  igloo |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
 In the code below, the rule appears not to fire.

 Based on the bytestring rules, reported as broken here:
 http://www.haskell.org/pipermail/glasgow-haskell-
 users/2012-August/022775.html

 {{{
 ghc -O --make h.hs -ddump-simpl -fforce-recomp -Wall
 }}}
 {{{
 module Q (f) where

 {-# NOINLINE f #-}
 f :: Bool -> String
 f c = g ((==) c)

 {-# NOINLINE g #-}
 g :: (Bool -> Bool) -> String
 g _ = "g"

 h :: Bool -> String
 h _ = "h"

 {-# RULES "MyRule" forall x . g ((==) x) = h x #-}
 }}}
 {{{
  Tidy Core 
 Result size of Tidy Core = {terms: 25, types: 21, coercions: 0}

 lvl_rkK :: GHC.Types.Char
 [GblId, Caf=NoCafRefs, Str=DmdType m]
 lvl_rkK = GHC.Types.C# 'h'

 lvl1_rkL :: [GHC.Types.Char]
 [GblId, Caf=NoCafRefs, Str=DmdType]
 lvl1_rkL =
   GHC.Types.:
 @ GHC.Types.Char lvl_rkK (GHC.Types.[] @ GHC.Types.Char)

 h_reA :: GHC.Types.Bool -> GHC.Base.String
 [GblId, Arity=1, Caf=NoCafRefs, Str=DmdType A]
 h_reA = \ _ -> lvl1_rkL

 lvl2_rkM :: GHC.Types.Char
 [GblId, Caf=NoCafRefs, Str=DmdType m]
 lvl2_rkM = GHC.Types.C# 'g'

 lvl3_rkN :: [GHC.Types.Char]
 [GblId, Caf=NoCafRefs, Str=DmdType]
 lvl3_rkN =
   GHC.Types.:
 @ GHC.Types.Char lvl2_rkM (GHC.Types.[] @ GHC.Types.Char)

 g_rez :: (GHC.Types.Bool -> GHC.Types.Bool) -> GHC.Base.String
 [GblId, Arity=1, Caf=NoCafRefs, Str=DmdType A]
 g_rez = \ _ -> lvl3_rkN

 Q.f [InlPrag=NOINLINE] :: GHC.Types.Bool -> GHC.Base.String
 [GblId, Arity=1, Caf=NoCafRefs, Str=DmdType A]
 Q.f =
   \ (c_aeC :: GHC.Types.Bool) ->
 g_rez (GHC.Classes.$fEqBool_$c== c_aeC)
 }}}

-- 
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] #7373: When building GHC: Failed to load interface for `GHC.Fingerprint'

2012-10-28 Thread GHC
#7373: When building GHC: Failed to load interface for `GHC.Fingerprint'
-+--
Reporter:  igloo |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  libraries/base| Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
 when doing a build with THREADS=1, we are getting
 things like:
 {{{
 inplace/bin/ghc-stage1 [...] -c
 libraries/time/./Data/Time/Calendar/Days.hs [...]
 /home/ian/ghc/git/ghc/libraries/base/dist-
 install/build/Data/Typeable/Internal.dyn_hi
 Declaration for mkTyConApp
 Unfolding of Data.Typeable.Internal.mkTyConApp:
   Failed to load interface for `GHC.Fingerprint'
   Perhaps you haven't installed the "dyn" libraries for package `base'?
   Use -v to see a list of the files searched for.
 /home/ian/ghc/git/ghc/libraries/base/dist-
 install/build/Data/Typeable.dyn_hi
 Declaration for mkTyCon
 Unfolding of Data.Typeable.mkTyCon:
   Can't find interface-file declaration for variable
 GHC.Fingerprint.fingerprintString
 Probable cause: bug in .hi-boot file, or inconsistent .hi file
 Use -ddump-if-trace to get an idea of which file caused the error
 }}}

 (we only have Fingerprint.dyn_hi-boot). GHC still exits successfully,
 however.

-- 
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] #7312: panic! applytTypeToArgs with non-infix function type constructor

2012-10-28 Thread GHC
#7312: panic! applytTypeToArgs with non-infix function type constructor
+---
Reporter:  jwlato   |   Owner:  simonpj 
  
Type:  bug  |  Status:  merge   
  
Priority:  normal   |   Milestone:  7.6.2   
  
   Component:  Compiler (Type checker)  | Version:  7.6.1   
  
Keywords:   |  Os:  Unknown/Multiple
  
Architecture:  Unknown/Multiple | Failure:  Compile-time crash  
  
  Difficulty:  Unknown  |Testcase:  
typecheck/should_compile/T7312
   Blockedby:   |Blocking:  
  
 Related:   |  
+---

Comment(by simonpj):

 When merging, please check whether the change fixes #7372 in the 7.6
 branch

-- 
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] #7372: Lint failure in GHC 7.6.1

2012-10-28 Thread GHC
#7372: Lint failure in GHC 7.6.1
-+--
Reporter:  simonpj   |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Old description:

> José Romildo Malaquias reports that the attached file makes GHC 7.6.1
> give a Lint error:
> {{{
> bash-3.1$ c:/fp/ghc-7.6.1/bin/ghc -c applicative-eval.hs  -dcore-lint
> -fforce-recomp
> *** Core Lint errors : in result of Desugar (after optimization) ***
> : Warning:
> In a case alternative: (Main.Cte i_ayo :: GHC.Integer.Type.Integer)
> Type of case alternatives not the same as the annotation on case:
> Main.Memory -> GHC.Integer.Type.Integer
> (->) Main.Memory GHC.Integer.Type.Integer
> Control.Applicative.pure
>   @ ((->) Main.Memory)
>   $dApplicative_a1b4
>   @ GHC.Integer.Type.Integer
>   i_ayo
> *** Offending Program ***
> 
> }}}
> However HEAD compiles it just fine.
>
> Sjoerd Visser found that you can avoid the error by replacing
> {{{
>   eval :: Exp -> (->) Memory Integer
> }}}
> with
> {{{
>   eval :: Exp -> Memory -> Integer
> }}}
> which should be the same, but apparently isn't internally in GHC.

New description:

 José Romildo Malaquias reports that the attached file (requires `parsec`
 unfortunately) makes GHC 7.6.1 give a Lint error:
 {{{
 bash-3.1$ c:/fp/ghc-7.6.1/bin/ghc -c applicative-eval.hs  -dcore-lint
 -fforce-recomp
 *** Core Lint errors : in result of Desugar (after optimization) ***
 : Warning:
 In a case alternative: (Main.Cte i_ayo :: GHC.Integer.Type.Integer)
 Type of case alternatives not the same as the annotation on case:
 Main.Memory -> GHC.Integer.Type.Integer
 (->) Main.Memory GHC.Integer.Type.Integer
 Control.Applicative.pure
   @ ((->) Main.Memory)
   $dApplicative_a1b4
   @ GHC.Integer.Type.Integer
   i_ayo
 *** Offending Program ***
 
 }}}
 However HEAD compiles it just fine.

 Sjoerd Visser found that you can avoid the error by replacing
 {{{
   eval :: Exp -> (->) Memory Integer
 }}}
 with
 {{{
   eval :: Exp -> Memory -> Integer
 }}}
 which should be the same, but apparently isn't internally in GHC.

--

Comment(by simonpj):

 I'm guessing that this is another manifestation of #7312, which is fixed
 and which should be in 7.6.2.  But it would be good if someone could
 check.

 Simon

-- 
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] #7372: Lint failure in GHC 7.6.1

2012-10-28 Thread GHC
#7372: Lint failure in GHC 7.6.1
-+--
Reporter:  simonpj   |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  7.8.1   
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
 José Romildo Malaquias reports that the attached file makes GHC 7.6.1 give
 a Lint error:
 {{{
 bash-3.1$ c:/fp/ghc-7.6.1/bin/ghc -c applicative-eval.hs  -dcore-lint
 -fforce-recomp
 *** Core Lint errors : in result of Desugar (after optimization) ***
 : Warning:
 In a case alternative: (Main.Cte i_ayo :: GHC.Integer.Type.Integer)
 Type of case alternatives not the same as the annotation on case:
 Main.Memory -> GHC.Integer.Type.Integer
 (->) Main.Memory GHC.Integer.Type.Integer
 Control.Applicative.pure
   @ ((->) Main.Memory)
   $dApplicative_a1b4
   @ GHC.Integer.Type.Integer
   i_ayo
 *** Offending Program ***
 
 }}}
 However HEAD compiles it just fine.

 Sjoerd Visser found that you can avoid the error by replacing
 {{{
   eval :: Exp -> (->) Memory Integer
 }}}
 with
 {{{
   eval :: Exp -> Memory -> Integer
 }}}
 which should be the same, but apparently isn't internally in GHC.

-- 
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] #7356: Building HEAD on Mac OS X 10.5 reports Undefined "_pthread_threadid_np" ref'd from _kernelThreadId in libHSrts_thr.a(OSThreads.thr_o)

2012-10-28 Thread GHC
#7356: Building HEAD on Mac OS X 10.5 reports Undefined "_pthread_threadid_np"
ref'd from _kernelThreadId in libHSrts_thr.a(OSThreads.thr_o)
-+--
 Reporter:  thorkilnaur  |  Owner:
 Type:  bug  | Status:  patch 
 Priority:  normal   |  Component:  Runtime System
  Version:  7.7  |   Keywords:
   Os:  MacOS X  |   Architecture:  x86   
  Failure:  Building GHC failed  |   Testcase:
Blockedby:   |   Blocking:
  Related:   |  
-+--
Changes (by thorkilnaur):

  * status:  new => patch


Comment:

 Added patch with a suggested fix for this problem.

 Best regards
 Thorkil

-- 
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