[GHC] #7528: Non terminating thunk resolution blocks world, even in the case of forkOS

2012-12-25 Thread GHC
#7528: Non terminating thunk resolution blocks world, even in the case of forkOS
+---
Reporter:  timthelion   |  Owner:   
  
Type:  bug  | Status:  new  
  
Priority:  normal   |  Component:  Runtime System   
  
 Version:  7.4.2|   Keywords:  forkOS Concurrent 
thunk
  Os:  Unknown/Multiple |   Architecture:  x86_64 (amd64)   
  
 Failure:  Incorrect result at runtime  |  Blockedby:   
  
Blocking:   |Related:   
  
+---
 Please see:
 http://comments.gmane.org/gmane.comp.lang.haskell.cafe/102479

 {-# LANGUAGE ScopedTypeVariables #-}
 import Control.Concurrent

 main = do
  putStrLn Hello
  forkOS neverEnds
  putStrLn Bye bye --We never get here(or at least I don't).

 neverEnds = do
  let (a::String) = a
  putStrLn a

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7528
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] #7529: Crash when using (-) instead of (=) in a typeclass instance

2012-12-25 Thread GHC
#7529: Crash when using (-) instead of (=) in a typeclass instance
---+
Reporter:  Helkafen|  Owner:   
Type:  bug | Status:  new  
Priority:  normal  |  Component:  Compiler (Parser)
 Version:  7.4.1   |   Keywords:   
  Os:  Linux   |   Architecture:  x86  
 Failure:  Compile-time crash  |  Blockedby:   
Blocking:  |Related:   
---+
 import qualified Data.Vector as V
 import Test.QuickCheck
 import Control.Monad (liftM)

 instance (Arbitrary a) - Arbitrary (V.Vector a) where
 arbitrary = fmap V.fromList arbitrary

 main = do
 print bla

 The arrow is obviously incorrect.

 runghc thisfile tells me:
 *** Exception: compiler/rename/RnSource.lhs:429:14-81: Irrefutable pattern
 failed for pattern Data.Maybe.Just (inst_tyvars,
 _,
 SrcLoc.L _ cls,
 _)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7529
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] #7530: Proposal: Add isLeft/isRight to Data.Either

2012-12-25 Thread GHC
#7530: Proposal: Add isLeft/isRight to Data.Either
-+--
Reporter:  SimonHengel   |  Owner:  
Type:  bug   | Status:  new 
Priority:  normal|  Component:  Compiler
 Version:  7.6.1 |   Keywords:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown  |  Blockedby:  
Blocking:|Related:  
-+--
 I propose to add {{{isLeft}}}/{{{isRight}}} to {{{Data.Either}}}.  The
 corresponding thread on {{{haskell-liraries}}} is here:
 http://www.haskell.org/pipermail/libraries/2012-November/018976.html

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7530
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] #7530: Proposal: Add isLeft/isRight to Data.Either

2012-12-25 Thread GHC
#7530: Proposal: Add isLeft/isRight to Data.Either
-+--
Reporter:  SimonHengel   |  Owner:  
Type:  feature request   | Status:  new 
Priority:  normal|  Component:  libraries/base  
 Version:  7.6.1 |   Keywords:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown  |  Blockedby:  
Blocking:|Related:  
-+--
Changes (by SimonHengel):

  * type:  bug = feature request
  * component:  Compiler = libraries/base


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7530#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] #7529: Crash when using (-) instead of (=) in a typeclass instance

2012-12-25 Thread GHC
#7529: Crash when using (-) instead of (=) in a typeclass instance
-+--
Reporter:  Helkafen  |Owner:
Type:  bug   |   Status:  closed
Priority:  normal|Component:  Compiler (Parser) 
 Version:  7.4.1 |   Resolution:  duplicate 
Keywords:|   Os:  Linux 
Architecture:  x86   |  Failure:  Compile-time crash
   Blockedby:| Blocking:
 Related:|  
-+--
Changes (by monoidal):

  * status:  new = closed
  * resolution:  = duplicate


Comment:

 Thanks for the report, the bug is already fixed in GHC 7.6.1, see #5951.
 Now you get

 {{{
 T.hs:5:10:
 Malformed instance: (Arbitrary a) - Arbitrary (V.Vector a)
 }}}

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


[GHC] #7531: after manualy installing array-0.4.0.1

2012-12-25 Thread GHC
#7531: after manualy installing array-0.4.0.1
-+--
Reporter:  guest |  Owner:
Type:  bug   | Status:  new   
Priority:  normal|  Component:  Package system
 Version:  7.6.1 |   Keywords:
  Os:  Windows   |   Architecture:  x86_64 (amd64)
 Failure:  None/Unknown  |  Blockedby:
Blocking:|Related:
-+--
 After manually installing array-0.4.0.1 installation manually of Cabal
 -1.16.0.3 print:
 c:\download\archive\Cabal\1.16.0.3\Cabal-1.16.0.3runghc Setup.hs install
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.4.2 for i386-unknown-mingw32):
 interactiveUI:setBuffering2

 Please report this as a GHC bug:  http://www.haskell.org/ghc/reportabug

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7531
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] #7528: Non terminating thunk resolution blocks world, even in the case of forkOS

2012-12-25 Thread GHC
#7528: Non terminating thunk resolution blocks world, even in the case of forkOS
+---
Reporter:  timthelion   |  Owner:   
  
Type:  bug  | Status:  new  
  
Priority:  normal   |  Component:  Runtime System   
  
 Version:  7.4.2|   Keywords:  forkOS Concurrent 
thunk
  Os:  Unknown/Multiple |   Architecture:  x86_64 (amd64)   
  
 Failure:  Incorrect result at runtime  |  Blockedby:   
  
Blocking:   |Related:   
  
+---

Comment(by cdupont):

 I reproduced the bug in 7.4.1 compiled with ghc -threaded.
 However, runnning main in ghci doesn't show the bug (it finishes
 correctly).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7528#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] #7528: Non terminating thunk resolution blocks world, even in the case of forkOS

2012-12-25 Thread GHC
#7528: Non terminating thunk resolution blocks world, even in the case of forkOS
+---
Reporter:  timthelion   |  Owner:   
  
Type:  bug  | Status:  new  
  
Priority:  normal   |  Component:  Runtime System   
  
 Version:  7.4.2|   Keywords:  forkOS Concurrent 
thunk
  Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple 
  
 Failure:  Incorrect result at runtime  |  Blockedby:   
  
Blocking:   |Related:   
  
+---
Changes (by Yuras):

 * cc: shumovichy@… (added)
  * architecture:  x86_64 (amd64) = Unknown/Multiple


Comment:

 Seems to be a duplicate of #367: you have a loop without allocations and
 the scheduler doesn't have chance to reschedule the thread.

 I can reproduce it with the HEAD with -O0. With -O1 it works ok for
 me.
 It works with -O0 -fno-omit-yields too.

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


Fundeps and type equality

2012-12-25 Thread Conal Elliott
I ran into a simple falure with functional dependencies (in GHC 7.4.1):

 class Foo a ta | a - ta

 foo :: (Foo a ta, Foo a tb, Eq ta) = ta - tb - Bool
 foo = (==)

I expected that the `a - ta` functional dependency would suffice to prove
that `ta ~ tb`, but

Pixie/Bug1.hs:9:7:
Could not deduce (ta ~ tb)
from the context (Foo a ta, Foo a tb, Eq ta)
  bound by the type signature for
 foo :: (Foo a ta, Foo a tb, Eq ta) = ta - tb - Bool
  at Pixie/Bug1.hs:9:1-10
  `ta' is a rigid type variable bound by
   the type signature for
 foo :: (Foo a ta, Foo a tb, Eq ta) = ta - tb - Bool
   at Pixie/Bug1.hs:9:1
  `tb' is a rigid type variable bound by
   the type signature for
 foo :: (Foo a ta, Foo a tb, Eq ta) = ta - tb - Bool
   at Pixie/Bug1.hs:9:1
Expected type: ta - tb - Bool
  Actual type: ta - ta - Bool
In the expression: (==)
In an equation for `foo': foo = (==)
Failed, modules loaded: none.

Any insights about what's going wrong here?

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


Re: Fundeps and type equality

2012-12-25 Thread Iavor Diatchki
Hello Conal,

GHC implementation of functional dependencies is incomplete: it will use
functional dependencies during type inference (i.e., to determine the
values of free type variables), but it will not use them in proofs, which
is what is needed in examples like the one you posted.  The reason some
proving is needed is that the compiler needs to figure out that for each
instantiation of the type `ta` and `tb` will be the same (which, of course,
follows directly from the FD on the class).

As far as I understand, the reason that GHC does not construct such proofs
is that it can't express them in its internal proof language (System FC).
 It seems to me that it should be fairly straight-forward to extend FC to
support this sort of proof, but I have not been able to convince folks that
this is the case.  I could elaborate, if there's interest.

In the mean time, the way forward would probably be to express the
dependency using type families, which I find tends to be more verbose but,
at present, is better supported in GHC.

Cheers,
-Iavor
PS: cc-ing the GHC users' list, as there was some talk of closing the
ghc-bugs list, but I am not sure if the transition happened yet.





On Tue, Dec 25, 2012 at 6:15 PM, Conal Elliott co...@conal.net wrote:

 I ran into a simple falure with functional dependencies (in GHC 7.4.1):

  class Foo a ta | a - ta
 
  foo :: (Foo a ta, Foo a tb, Eq ta) = ta - tb - Bool
  foo = (==)

 I expected that the `a - ta` functional dependency would suffice to prove
 that `ta ~ tb`, but

 Pixie/Bug1.hs:9:7:
 Could not deduce (ta ~ tb)
 from the context (Foo a ta, Foo a tb, Eq ta)
   bound by the type signature for
  foo :: (Foo a ta, Foo a tb, Eq ta) = ta - tb - Bool
   at Pixie/Bug1.hs:9:1-10
   `ta' is a rigid type variable bound by
the type signature for
  foo :: (Foo a ta, Foo a tb, Eq ta) = ta - tb - Bool
at Pixie/Bug1.hs:9:1
   `tb' is a rigid type variable bound by
the type signature for
  foo :: (Foo a ta, Foo a tb, Eq ta) = ta - tb - Bool
at Pixie/Bug1.hs:9:1
 Expected type: ta - tb - Bool
   Actual type: ta - ta - Bool
 In the expression: (==)
 In an equation for `foo': foo = (==)
 Failed, modules loaded: none.

 Any insights about what's going wrong here?

 -- Conal

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


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


Re: [GHC] #4363: openFile sharing permissions are inconsistent across platforms

2012-12-25 Thread GHC
#4363: openFile sharing permissions are inconsistent across platforms
--+-
  Reporter:  jystic   |  Owner:  
  Type:  bug  | Status:  closed  
  Priority:  high |  Milestone:  7.6.1   
 Component:  libraries/base   |Version:  6.12.3  
Resolution:  fixed|   Keywords:  
Os:  Windows  |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by PHO):

 * cc: pho@… (added)


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