Re: [GHC] #5002: 7.0.2 ignores a context which 7.0.1 picks up

2011-05-19 Thread GHC
#5002: 7.0.2 ignores a context which 7.0.1 picks up
+---
  Reporter:  patrick_premont|  Owner:  simonpj
  Type:  bug| Status:  closed 
  Priority:  highest|  Milestone:  7.2.1  
 Component:  Compiler   |Version:  7.0.2  
Resolution:  fixed  |   Keywords: 
  Testcase: |  Blockedby: 
Difficulty: | Os:  Windows
  Blocking: |   Architecture:  x86
   Failure:  GHC rejects valid program  |  
+---
Changes (by dimitris):

  * status:  new = closed
  * resolution:  = fixed


Comment:

 This is indeed fixed but (1) prioritizing equalities and (2) more delaying
 of the
 application of instances if there is a possibility of a given matching.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5002#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] #5002: 7.0.2 ignores a context which 7.0.1 picks up

2011-05-19 Thread GHC
#5002: 7.0.2 ignores a context which 7.0.1 picks up
+---
  Reporter:  patrick_premont|  Owner:  simonpj
  Type:  bug| Status:  closed 
  Priority:  highest|  Milestone:  7.2.1  
 Component:  Compiler   |Version:  7.0.2  
Resolution:  fixed  |   Keywords: 
  Testcase:  indexed-types/should_compile/T5002.hs  |  Blockedby: 
Difficulty: | Os:  Windows
  Blocking: |   Architecture:  x86
   Failure:  GHC rejects valid program  |  
+---
Changes (by dimitris):

  * testcase:  = indexed-types/should_compile/T5002.hs


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5002#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: [GHC] #5002: 7.0.2 ignores a context which 7.0.1 picks up

2011-05-10 Thread GHC
#5002: 7.0.2 ignores a context which 7.0.1 picks up
+---
Reporter:  patrick_premont  |Owner:  simonpj  
Type:  bug  |   Status:  new  
Priority:  highest  |Milestone:  7.2.1
   Component:  Compiler |  Version:  7.0.2
Keywords:   | Testcase:   
   Blockedby:   |   Difficulty:   
  Os:  Windows  | Blocking:   
Architecture:  x86  |  Failure:  GHC rejects valid program
+---

Comment(by dimitris):

 OK yes this is indeed related to #4981 and is fixed because of saturation
 of equalities, but there's more work to be done -- see the commentary on
 #4981. I will
 add both these to the testsuite.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5002#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] #5002: 7.0.2 ignores a context which 7.0.1 picks up

2011-05-09 Thread GHC
#5002: 7.0.2 ignores a context which 7.0.1 picks up
+---
Reporter:  patrick_premont  |Owner:  simonpj  
Type:  bug  |   Status:  new  
Priority:  highest  |Milestone:  7.2.1
   Component:  Compiler |  Version:  7.0.2
Keywords:   | Testcase:   
   Blockedby:   |   Difficulty:   
  Os:  Windows  | Blocking:   
Architecture:  x86  |  Failure:  GHC rejects valid program
+---
Changes (by simonpj):

  * owner:  = simonpj


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5002#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] #5002: 7.0.2 ignores a context which 7.0.1 picks up

2011-03-11 Thread GHC
#5002: 7.0.2 ignores a context which 7.0.1 picks up
+---
Reporter:  patrick_premont  |Owner:   
Type:  bug  |   Status:  new  
Priority:  highest  |Milestone:  7.2.1
   Component:  Compiler |  Version:  7.0.2
Keywords:   | Testcase:   
   Blockedby:   |   Difficulty:   
  Os:  Windows  | Blocking:   
Architecture:  x86  |  Failure:  GHC rejects valid program
+---

Comment(by patrick_premont):

 I am sorry. I sent the wrong code version. There should be no [a] in
 there. This was the attempt mentionned at the end of the comment.

 When testing again, I also surprised to see that okInBoth' in fact
 compiles in 7.0.2 only. I don't know what happened here. So I am renaming
 it to okIn702, and pasting an updated description below :

 GHC 7.0.2 rejects programs which 7.0.1 accepts, and vice-versa

 A passed context is not used, and the compiler (expectedly) fails to
 deduce an instance.  Patching the code so that it works again is not
 difficult. Some type annotations can do the trick. So this is not a
 critical issue but it is a bit surprising.

 I have simplified my code as much as possible so that it still shows
 the error in 7.0.2 (okIn701). I have included two further
 simplifications. One produces no error in both versions (okInBoth) and
 the other produces an error in 7.0.1 (okIn702).

 The code also compiles if we remove the instance
 declaration for class B. In that case the type of a in okIn701 can be
 infered, and the context for that type is provided.

 I have seen the following comment by dimitris in ticket #4981, which
 seems related.  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. Ticket #4981 seems to be an issue
 with 7.0.1. In the initial ticket text I though this was a regression with
 7.0.2,
 but in some cases 7.0.2 is better than 7.0.1 (okIn702).

 The diagnosis of ticket #3018 may be applicable to the code here: we
 may be asking too much of the compiler. As an additional
 simplification attempt, I have added function fromTicket3018, but it
 compiles fine with 7.0.1 and 7.0.2.

 Also if the instance for 'B' is restricted to '[a]' (we can then
 remove the UndecidableInstances extension), and the type 'a' is
 replaced by '[a]' in 'okIn701', then it compiles fine. Are instances
 that match everything applied more eagerly ? If so then this
 compilatin problem should be quite rare.

 {{{

  {-# LANGUAGE TypeFamilies, FlexibleInstances, UndecidableInstances,
 FlexibleContexts #-}

  class A a
  class B a where b :: a - ()
  instance A a = B a where b = undefined

  newtype Y a = Y (a - ())

  okIn701 :: B a = Y a
  okIn701 = wrap $ const () . b

  okIn702 :: B a = Y a
  okIn702 = wrap $ b

  okInBoth :: B a = Y a
  okInBoth = Y $ const () . b

  class Wrapper a where
  type Wrapped a
  wrap :: Wrapped a - a
  instance Wrapper (Y a) where
type Wrapped (Y a) = a - ()
wrap = Y

  fromTicket3018 :: Eq [a] = a - ()
  fromTicket3018 x = let {g :: Int - Int; g = [x]==[x] `seq` id} in ()

  main = undefined

 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5002#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] #5002: 7.0.2 ignores a context which 7.0.1 picks up

2011-03-10 Thread GHC
#5002: 7.0.2 ignores a context which 7.0.1 picks up
+---
Reporter:  patrick_premont  |Owner:   
Type:  bug  |   Status:  new  
Priority:  highest  |Milestone:  7.2.1
   Component:  Compiler |  Version:  7.0.2
Keywords:   | Testcase:   
   Blockedby:   |   Difficulty:   
  Os:  Windows  | Blocking:   
Architecture:  x86  |  Failure:  GHC rejects valid program
+---
Changes (by igloo):

  * priority:  normal = highest
  * milestone:  = 7.2.1


Comment:

 Thanks for the report. Let's look into whether or not this is a bug before
 the 7.2.1 release.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/5002#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] #5002: 7.0.2 ignores a context which 7.0.1 picks up

2011-03-07 Thread GHC
#5002: 7.0.2 ignores a context which 7.0.1 picks up
+---
Reporter:  patrick_premont  |   Owner:   
Type:  bug  |  Status:  new  
Priority:  normal   |   Component:  Compiler 
 Version:  7.0.2|Keywords:   
Testcase:   |   Blockedby:   
  Os:  Windows  |Blocking:   
Architecture:  x86  | Failure:  GHC rejects valid program
+---
 GHC 7.0.2 rejects programs which 7.0.1 accepts.

 A passed context is not used, and the compiler (expectedly) fails to
 deduce an instance.  Patching the code so that it works again is not
 difficult. Some type annotations can do the trick. So this is not a
 critical issue but it is a bit surprising.

 I have simplified my code as much as possible so that it still shows
 the error in 7.0.2 (okIn701). I have included two further
 simplifications which produce no error : okInBoth and okInBoth'. I see
 why okInBoth is more simple (it side steps a type function), but I do
 not see why okInBoth' would avoid the problem.

 The code also compiles if we remove the instance
 declaration for class B. In that case the type of a in okIn701 can be
 infered, and the context for that type is provided.

 I have seen the following comment by dimitris in ticket #4981, which
 seems related.  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. Ticket #4981 seems to be an issue
 with 7.0.1. Here we see an apparent regression with 7.0.2, so I
 thought I would bring it up in case it is an unexpected change in
 behavior.

 The diagnosis of ticket #3018 may be applicable to the code here: we
 may be asking too much of the compiler. As an additional
 simplification attempt, I have added function fromTicket3018, but it
 compiles fine with 7.0.1 and 7.0.2.

 Also if the instance for 'B' is restricted to '[a]' (we can then
 remove the UndecidableInstances extension), and the type 'a' is
 replaced by '[a]' in 'okIn701', then it compiles fine. Are instances
 that match everything applied more eagerly ? If so then this
 compilatin problem should be quite rare.

 {{{

  {-# LANGUAGE TypeFamilies, FlexibleInstances, UndecidableInstances,
 FlexibleContexts #-}

  class A a
  class B a where b :: a - ()
  instance A a = B [a] where b = undefined

  newtype Y a = Y (a - ())

  okIn701 :: B [a] = Y [a]
  okIn701 = wrap $ const () . b

  okInBoth' :: B a = Y a
  okInBoth' = wrap $ b

  okInBoth :: B a = Y a
  okInBoth = Y $ const () . b

  class Wrapper a where
  type Wrapped a
  wrap :: Wrapped a - a
  instance Wrapper (Y a) where
type Wrapped (Y a) = a - ()
wrap = Y

  fromTicket3018 :: Eq [a] = a - ()
  fromTicket3018 x = let {g :: Int - Int; g = [x]==[x] `seq` id} in ()

  main = undefined

 }}}

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