Re: [GHC] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2009-10-18 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
+---
Reporter:  igloo|Owner:  
Type:  bug  |   Status:  closed  
Priority:  normal   |Milestone:  _|_ 
   Component:  Compiler (Type checker)  |  Version:  6.6 
Severity:  minor|   Resolution:  fixed   
Keywords:   |   Difficulty:  Unknown 
Testcase:  tcfail188|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple |  
+---
Comment (by benl):

 Looks ok to me.

-- 
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] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2009-10-15 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
+---
Reporter:  igloo|Owner:  
Type:  bug  |   Status:  closed  
Priority:  normal   |Milestone:  _|_ 
   Component:  Compiler (Type checker)  |  Version:  6.6 
Severity:  minor|   Resolution:  fixed   
Keywords:   |   Difficulty:  Unknown 
Testcase:  tcfail188|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple |  
+---
Changes (by guest):

 * cc: kfr...@gmail.com (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] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2009-10-15 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
+---
Reporter:  igloo|Owner:  
Type:  bug  |   Status:  closed  
Priority:  normal   |Milestone:  _|_ 
   Component:  Compiler (Type checker)  |  Version:  6.6 
Severity:  minor|   Resolution:  fixed   
Keywords:   |   Difficulty:  Unknown 
Testcase:  tcfail188|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple |  
+---
Changes (by simonpj):

  * status:  new => closed
 * cc: ben.lippme...@anu.edu.au (added)
  * resolution:  => fixed

Comment:

 I finally got around to fixing this
 {{{
 Thu Oct 15 13:28:10 BST 2009  simo...@microsoft.com
   * Fix Trac #959: a long-standing bug in instantiating
 otherwise-unbound type variables

  DO NOT MERGE TO GHC 6.12 branch
  (Reason: interface file format change.)

   The typechecker needs to instantiate otherwise-unconstraint type
 variables to
   an appropriately-kinded constant type, but we didn't have a supply of
   arbitrarily-kinded tycons for this purpose.  Now we do.

   The details are described in Note [Any types] in TysPrim.  The
   fundamental change is that there is a new sort of TyCon, namely
   AnyTyCon, defined in TyCon.

   There's a small change to interface-file binary format, because the new
   AnyTyCons have to be serialised.

   I tided up the handling of uniques a bit too, so that mkUnique is not
   exported, so that we can see all the different name spaces in one
 module.


 M ./compiler/basicTypes/OccName.lhs -10 +11
 M ./compiler/basicTypes/Unique.lhs -4 +20
 M ./compiler/deSugar/DsBinds.lhs -25 +23
 M ./compiler/iface/BinIface.hs -1 +5
 M ./compiler/iface/IfaceType.lhs -11 +22
 M ./compiler/iface/TcIface.lhs +3
 M ./compiler/nativeGen/Reg.hs -2 +2
 M ./compiler/nativeGen/RegAlloc/Graph/ArchBase.hs -2 +2
 M ./compiler/nativeGen/RegAlloc/Graph/SpillClean.hs -3 +3
 M ./compiler/nativeGen/RegClass.hs -3 +3
 M ./compiler/prelude/PrelNames.lhs -5 +3
 M ./compiler/prelude/TysPrim.lhs -56 +120
 M ./compiler/prelude/TysWiredIn.lhs -4 +2
 M ./compiler/stgSyn/CoreToStg.lhs -1 +1
 M ./compiler/typecheck/TcHsSyn.lhs -75 +1
 M ./compiler/types/TyCon.lhs -16 +44
 M ./compiler/types/TypeRep.lhs -8 +5
 M ./compiler/vectorise/VectUtils.hs -1 +1
 }}}
 '''IAN''': Don't merge to the 6.12 branch, because it changes interface
 file formats slightly.

 tcfail188 now compiles ok.

 '''BEN''': as part of the `mkUnique` tidy-up I moved a few lines from
 `nativeGen` to `Unique`.  Can you just review the patch (the bits
 affecting nativeGen are only a few lines) to check it's ok.  It seems to
 validate.

 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


Re: [GHC] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2009-09-02 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
+---
Reporter:  igloo|Owner:  
Type:  bug  |   Status:  new 
Priority:  normal   |Milestone:  _|_ 
   Component:  Compiler (Type checker)  |  Version:  6.6 
Severity:  minor|   Resolution:  
Keywords:   |   Difficulty:  Unknown 
Testcase:  tcfail188|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple |  
+---
Comment (by ganesh):

 I have encountered this in darcs when trying to make our phantom types be
 of some complicated (and arbitrarily chosen) kind to minimise the risk of
 them being instantiated with a real type (which would then lead to a risk
 of unsafeCoerce happening on those real types due to other aspects of the
 way we use phantom types).

-- 
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] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2008-06-03 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
-+--
 Reporter:  igloo|  Owner: 
 Type:  bug  | Status:  new
 Priority:  normal   |  Milestone:  _|_
Component:  Compiler (Type checker)  |Version:  6.6
 Severity:  minor| Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:  tcfail188|   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Comment (by magnushiie):

 A real-world example of the same error:

 {{{
 -- Specifying -fno-monomorphism-restriction removes the error
 --{-# OPTIONS_GHC -fno-monomorphism-restriction #-}

 module ParsecWrap where

 import Control.Monad.Trans
 import qualified Text.ParserCombinators.Parsec as P

 -- these work without type signature
 many1 f = lift $ P.many1 f
 oneOf cs = lift $ P.oneOf cs
 {-
 :t many1
 many1 :: (MonadTrans t) =>
 P.GenParser tok st a -> t (P.GenParser tok st) [a]
 :t oneOf
 oneOf :: (MonadTrans t) => [Char] -> t (P.GenParser Char st) Char
 -}
 --anyChar :: MonadTrans t => t (P.GenParser Char st) Char
 anyChar = lift $ P.anyChar
 {-
 Without type signature on anyChar, gives:
 Urk! Inventing strangely-kinded void TyCon:
 :t{tc a1vc}
 (* -> *) -> * -> *

 D:\Dev\Test\ParseCpp\src\ParsecWrap.hs:30:10:
 Ambiguous type variable `t' in the constraint:
   `MonadTrans t'
 arising from use of `lift'
 at D:\Dev\Test\ParseCpp\src\ParsecWrap.hs:30:10-13
 Possible cause: the monomorphism restriction applied to the following:
   anyChar :: forall st. t (P.GenParser Char st) Char
 (bound at D:\Dev\Test\ParseCpp\src\ParsecWrap.hs:30:0)
 Probable fix: give these definition(s) an explicit type signature
   or use -fno-monomorphism-restriction
 Failed, modules loaded: none.
 -}
 }}}

-- 
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] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2007-11-22 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
-+--
 Reporter:  igloo|  Owner: 
 Type:  bug  | Status:  new
 Priority:  normal   |  Milestone:  _|_
Component:  Compiler (Type checker)  |Version:  6.6
 Severity:  minor| Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:  tcfail188|   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Changes (by igloo):

  * owner:  igloo =>
  * type:  merge => bug
  * milestone:  6.8.2 => _|_

Comment:

 Merged

-- 
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] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2007-11-19 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
-+--
 Reporter:  igloo|  Owner:  igloo  
 Type:  merge| Status:  new
 Priority:  normal   |  Milestone:  6.8.2  
Component:  Compiler (Type checker)  |Version:  6.6
 Severity:  minor| Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:  tcfail188|   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Changes (by simonpj):

  * testcase:  => tcfail188
  * owner:  simonpj => igloo
  * type:  bug => merge

Comment:

 OK, I have
  * turned the "trace" into a civilised warning
  * added a tiny bit of advice about how to suppress the warning (add a
 type signature)
  * given a reference to this page
  * added a test case

 None of this is the Real Fix, which is to provide a way to robustly export
 strangely-kinded Any !TyCons across interface files.  But that's a bigger
 job, and I'm still unconvinced it's worth doing.

 '''If you trip over the new warning in a real program, and have thereby
 found your way to this page, please add a comment to say so.  Better
 still, please upload a small example, so we can gather evidence about how
 important this is.'''

 Ian: merge to the 6.8 branch; then change milestone to _|_, and type to
 'Bug'
 {{{
 Mon Nov 19 12:29:38 GMT 2007  [EMAIL PROTECTED]
   * Improve the situation for Trac #959: civilised warning
   instead of a trace msg
 }}}

-- 
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] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2007-11-12 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
-+--
 Reporter:  igloo|  Owner:  simonpj
 Type:  bug  | Status:  new
 Priority:  normal   |  Milestone:  6.8.2  
Component:  Compiler (Type checker)  |Version:  6.6
 Severity:  minor| Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Changes (by simonmar):

  * owner:  => simonpj
  * milestone:  6.8 branch => 6.8.2

Comment:

 confirmed in 6.8.1.

-- 
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] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2007-09-20 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
+---
Reporter:  igloo|Owner:
Type:  bug  |   Status:  new   
Priority:  normal   |Milestone:  6.8 branch
   Component:  Compiler (Type checker)  |  Version:  6.6   
Severity:  minor|   Resolution:
Keywords:   |   Difficulty:  Unknown   
  Os:  Unknown  | Testcase:
Architecture:  Unknown  |  
+---
Changes (by igloo):

  * milestone:  _|_ => 6.8 branch
  * priority:  lowest => normal

Comment:

 Andres ran into this in a real program, so I'm reclassifying 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] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2007-09-12 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
+---
Reporter:  igloo|Owner: 
Type:  bug  |   Status:  new
Priority:  lowest   |Milestone:  _|_
   Component:  Compiler (Type checker)  |  Version:  6.6
Severity:  minor|   Resolution: 
Keywords:   |   Difficulty:  Unknown
  Os:  Unknown  | Testcase: 
Architecture:  Unknown  |  
+---
Comment (by guest):

 Here's a program that provokes the message (in 6.6.1), but otherwise
 passes the typechecker:

 {{{
 {-# OPTIONS_GHC -fglasgow-exts #-}

 data D (f :: (* -> *) -> * -> *) (af :: * -> *) (ax :: *) =
   D (af (f af ax))

 data CList (f :: (* -> *) -> * -> *) (a :: *) =
   RCons a (CList (D f) a)

 type CycleList a = forall f. CList f a

 chead :: CycleList a -> a
 chead ys = case ys of (RCons x xs) -> x
 }}}

 Andres

-- 
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] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2007-04-02 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
-+--
 Reporter:  igloo|  Owner: 
 Type:  bug  | Status:  new
 Priority:  lowest   |  Milestone:  _|_
Component:  Compiler (Type checker)  |Version:  6.6
 Severity:  minor| Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Comment (by seekgzl):

 [http://www.makegamegold.com World Of Warcraftwow
 gold][http://www.makegamegold.com/default.asp?cateid=6 wow
 gold][http://www.makegamegold.com/default.asp?cateid=6 gold wow
 ][http://www.makegamegold.com/default.asp?cateID=11
 aids][http://www.makegamegold.com/default.html wow gold
 sale][http://www.makegamegold.com/default.asp?cateID=5 cheap
 hotel][http://www.makegamegold.com/default.asp?cateID=13 health
 services][http://www.makegamegold.com/article.asp?id=547 coins and
 edals][http://www.makegamegold.com/article.asp?id=512 bar code
 ccd][http://www.makegamegold.com/article.asp?id=511 skannerz bar codes]
 [http://www.makegamegold.com/article.asp?id=510 wireless bar code
 reader][http://www.makegamegold.com/article.asp?id=509 buy bar
 code][http://www.makegamegold.com/article.asp?id=508 bar code scanning
 system][http://www.makegamegold.com/article.asp?id=507 sap bar
 code][http://www.makegamegold.com/article.asp?id=506 which barcode scanner
 should i buy?] [http://www.makegamegold.com/article.asp?id=262 Aristo
 Halifax][http://www.makegamegold.com/article.asp?id=108 god of war
 unlockable videos A Secret
 Revealed][http://www.makegamegold.com/article.asp?id=262 discounts
 furniture][http://www.makegamegold.com/default.asp?id=318 walleye worm
 harness][http://www.makegamegold.com/article.asp?id=108 gold of war
 cheats][http://www.makegamegold.com/article.asp?id=99 world warcraft power
 leveling][http://www.makegamegold.com/article.asp?id=122 wrought iron
 stair railings][http://www.makegamegold.com/default.asp?page=20 Valerie
 confections][http://www.makegamegold.com/article.asp?id=249 more than
 words lyrics][http://www.makegamegold.com/default.asp?cateid=12 study
 abroad][http://www.makegamegold.com/article.asp?id=376 superman
 tattoo][http://www.makegamegold.com/article.asp?id=100 wow power
 leveling][http://www.makegamegold.com/article.asp?id=120 rod iron wall
 decor][http://www.makegamegold.com/article.asp?id=90 buy wow gold
 ][http://www.makegamegold.com/article.asp?id=122 staircase
 iron][http://www.makegamegold.com/article.asp?id=375 Star
 Tattoos][http://www.makegamegold.com/article.asp?id=376 superman tribal
 tattoo][http://www.makegamegold.com/article.asp?id=264 Huge Bedding & Bath
 Discounts ][http://www.makegamegold.com/article.asp?id=135 wow gold
 contrast][http://www.makegamegold.com/article.asp?id=116 iron gate in
 california for sale][http://www.makegamegold.com/article.asp?id=118 iron
 gate in california for
 sale][http://www.makegamegold.com/default.asp?CateID=6&page=8 really cheap
 wow gold][http://www.makegamegold.com/article.asp?id=122 atlanta wrought
 iron doors][http://www.makegamegold.com/Powerleveling/Powerleveling.html
 wow europe Powerleveling][http://www.makegamegold.com/article.asp?id=329
 computer desks][http://www.makegamegold.com/article.asp?id=90 cheap wow
 gold word listed][http://www.makegamegold.com/article.asp?id=122 wrought
 iron stair railings][http://www.makegamegold.com/article.asp?id=669
 ileus][http://www.makegamegold.com/article.asp?id=116 automatic
 gates][http://www.makegamegold.com/article.asp?id=82 europe wow
 gold][http://www.makegamegold.com/article.asp?id=92
 powerleveling][http://www.makegamegold.com/article.asp?id=12 cheap gold
 for wow][http://www.makegamegold.com/article.asp?id=81 cheap american gold
 coins][http://www.makegamegold.com/article.asp?id=322 california gold rush
 stories hangings][http://www.makegamegold.com/article.asp?id=383 Foreign
 stuff][http://www.makegamegold.com/article.asp?id=262 discounts furniture
 ][http://www.makegamegold.com/default.asp?id=175 Study Abroad in Japan
 ][http://www.makegamegold.com/article.asp?id=269 Call
 Center][http://www.makegamegold.com/article.asp?id=671 constipation
 ][http://www.makegamegold.com/article.asp?id=546
 treadmill][http://www.makegamegold.com/article.asp?id=855
 superman][http://www.makegamegold.com/article.asp?id=856
 spiderman?3][http://www.makegamegold.com/article.asp?id=148 cheap car
 insurance company][http://www.makegamegold.com/article.asp?id=149 cheap
 female car insurance][http://www.makegamegold.com/article.asp?id=150
 airline tickets for cheap][http://www.makegamegold.com/article.asp?id=151
 cheap air tickets to
 london][http://www.makegamegold.

Re: [GHC] #959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"

2006-10-30 Thread GHC
#959: Debugging info(?) leaks out: "Urk! Inventing strangely-kinded void TyCon"
-+--
 Reporter:  igloo|  Owner: 
 Type:  bug  | Status:  new
 Priority:  lowest   |  Milestone:  _|_
Component:  Compiler (Type checker)  |Version:  6.6
 Severity:  minor| Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Changes (by simonpj):

  * milestone:  6.6.1 => _|_
  * priority:  normal => lowest
  * severity:  normal => minor

Comment:

 The leakage is actually deliberate.

 In this program there is nothing to fix 'm' in the call to 'foo', so GHC
 makes up a fake type constructor, of kind (*->*)->*, and uses that at the
 call to foo.

 Now the trouble is that if this fake type constructor should show up in an
 interface file, GHC would not recognise the type constructor when reading
 the interface.  So I left the warning in, so that people would yell if it
 actually happened.

 This is really a bug, and I'm sure there's a way round it, but it has not
 occurred in a real program so far, so I've been postponing fixing it, and
 propose to continue to postpone.

 The relevant code is in `TcHsSyn.mkArbitraryType`

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