Re: [GHC] #2097: bug in regEnumKeys (System.Win32.Registry)

2008-04-07 Thread GHC
#2097: bug in regEnumKeys (System.Win32.Registry)
---+
 Reporter:  MagnusTherning |  Owner:  igloo  
 Type:  merge  | Status:  new
 Priority:  normal |  Milestone:  6.8.3  
Component:  libraries (other)  |Version:  6.8.2  
 Severity:  normal | Resolution: 
 Keywords: | Difficulty:  Unknown
 Testcase: |   Architecture:  Unknown
   Os:  Windows|  
---+
Comment (by MagnusTherning):

 Replying to [comment:5 igloo]:
  Fixed:
  {{{
  Sun Apr  6 21:50:51 BST 2008  Ian Lynagh [EMAIL PROTECTED]
* malloc a big enough buffer for the registry functions. Fixes trac
 #2097.
We were mallocing a byte per tchar, but tchars are normally 2 bytes
 big...
I think they are at most 4 bytes, so we now malloc 4 * #tchars. Not
 sure
if there is a proper function I should be using for this?
  }}}

 One way to be sure is to switch to using wide characters explicitly, i.e.
 to use RegOpenKeyExW rather than RegOpenKeyEx.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2097#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] #2191: A way to programmatically cause GHC to report the cost center stack associated with a value

2008-04-07 Thread GHC
#2191: A way to programmatically cause GHC to report the cost center stack
associated with a value
+---
Reporter:  SamB |Owner: 
Type:  feature request  |   Status:  new
Priority:  normal   |Milestone: 
   Component:  Profiling|  Version:  6.8.2  
Severity:  normal   |   Resolution: 
Keywords:  patch| Testcase: 
Architecture:  Unknown  |   Os:  Unknown
+---
Comment (by SamB):

 And now I have no clue what in the world this is doing, because when I try
 to use it to trace the cause of errors in JHC, the trace appears, but the
 fail or error call passed as the second argument to traceCcs# doesn't
 seem to happen :-(. Please assist! Did I do something really stupid? Is
 something missing from the documentation?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2191#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] #2177: Can Data.Unique safely derive Typeable?

2008-04-07 Thread GHC
#2177: Can Data.Unique safely derive Typeable?
-+--
 Reporter:  japple   |  Owner: 
 Type:  feature request  | Status:  new
 Priority:  normal   |  Milestone:  6.10 branch
Component:  libraries/base   |Version:  6.8.2  
 Severity:  normal   | Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  Unknown
   Os:  Unknown  |  
-+--
Comment (by japple):

 I was asking for the first. The second seems unreasonable. The third would
 be lovely.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2177#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] #2195: yi: internal error: R_X86_64_PC32 relocation out of range: (noname) = 0x7c436730a

2008-04-07 Thread GHC
#2195: yi: internal error: R_X86_64_PC32 relocation out of range: (noname) =
0x7c436730a
--+-
 Reporter:  guest |  Owner:
 Type:  bug   | Status:  closed
 Priority:  normal|  Milestone:
Component:  Compiler  |Version:  6.8.2 
 Severity:  normal| Resolution:  duplicate 
 Keywords:  linker| Difficulty:  Unknown   
 Testcase:|   Architecture:  x86_64 (amd64)
   Os:  FreeBSD   |  
--+-
Changes (by simonmar):

  * status:  new = closed
  * difficulty:  = Unknown
  * resolution:  = duplicate

Comment:

 see #2013

 upshot: we need a way to do `mmap(... MAP_32BIT ...)` on FreeBSD.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2195#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] #2013: ghci crash on startup: R_X86_64_32S relocation out of range.

2008-04-07 Thread GHC
#2013: ghci crash on startup: R_X86_64_32S relocation out of range.
-+--
 Reporter:  mboes|  Owner:
 Type:  bug  | Status:  new   
 Priority:  normal   |  Milestone:  6.8.3 
Component:  GHCi |Version:  6.9   
 Severity:  normal   | Resolution:
 Keywords:   | Difficulty:  Unknown   
 Testcase:   |   Architecture:  x86_64 (amd64)
   Os:  FreeBSD  |  
-+--
Comment (by simonmar):

 See also #2195

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2013#comment:13
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] #2191: A way to programmatically cause GHC to report the cost center stack associated with a value

2008-04-07 Thread GHC
#2191: A way to programmatically cause GHC to report the cost center stack
associated with a value
+---
Reporter:  SamB |Owner:  SamB   
Type:  feature request  |   Status:  new
Priority:  normal   |Milestone: 
   Component:  Profiling|  Version:  6.8.2  
Severity:  normal   |   Resolution: 
Keywords:  patch| Testcase: 
Architecture:  Unknown  |   Os:  Unknown
+---
Changes (by SamB):

  * owner:  = SamB

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2191#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] #2197: GHCi doesn't work when built with way=p

2008-04-07 Thread GHC
#2197: GHCi doesn't work when built with way=p
+---
 Reporter:  SamB|  Owner:  simonmar   
 Type:  bug | Status:  new
 Priority:  low |  Milestone:  6.10 branch
Component:  GHCi|Version:  6.9
 Severity:  normal  | Resolution: 
 Keywords:  | Difficulty:  Unknown
 Testcase:  |   Architecture:  Unknown
   Os:  Linux   |  
+---
Changes (by simonmar):

  * priority:  normal = low
  * difficulty:  = Unknown
  * owner:  = simonmar
  * milestone:  = 6.10 branch

Comment:

 GHCi + profiling doesn't work for deeper reasons than this: it would
 require a lot of work in the byte-code compiler and interpreter.

 If you try 'ghci -prof' you get an error message, but in this case you
 built GHCi itself with -prof and tried to use it.  I'll make it so that
 GHCi fails with a helpful error message earlier.

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


[GHC] #2203: TFs in class instances heads

2008-04-07 Thread GHC
#2203: TFs in class instances heads
-+--
Reporter:  chak  |   Owner:  chak   
Type:  bug   |  Status:  new
Priority:  normal|   Component:  Compiler (Type checker)
 Version:  6.9   |Severity:  normal 
Keywords:|Testcase: 
Architecture:  Multiple  |  Os:  Multiple   
-+--
 Ganesh posted the following example on haskell-cafe:
 {{{
 {-# LANGUAGE ScopedTypeVariables, TypeFamilies, FlexibleInstances #-}

 module Test1a where

 class Foo a where
type TheFoo a
foo :: TheFoo a - a
foo' :: a - Int

 class Bar b where
bar :: b - Int

 instance Foo a = Bar (Either a (TheFoo a)) where
bar (Left a) = foo' a
bar (Right b) = foo' (foo b :: a)

 instance Foo Int where
type TheFoo Int = Int
foo = id
foo' = id

 val :: Either Int Int
 val = Left 5

 res :: Int
 res = bar val
 }}}
 It fails to type check as the type of `bar` cannot be inferred.  However,
 GHC should reject the instance due to the TF in the head despite
 `FlexibleInstances`.

 Moreover, the corrected code
 {{{
 {-# LANGUAGE ScopedTypeVariables, TypeFamilies, UndecidableInstances #-}

 module Test1a where

 class Foo a where
type TheFoo a
foo :: TheFoo a - a
foo' :: a - Int

 class Bar b where
bar :: b - Int

 instance (b ~ TheFoo a, Foo a) = Bar (Either a b) where
bar (Left a) = foo' a
bar (Right b) = foo' (foo b :: a)

 instance Foo Int where
type TheFoo Int = Int
foo = id
foo' = id

 val :: Either Int Int
 val = Left 5

 res :: Int
 res = bar val
 }}}
 requires `UndecidableInstances`, although it shouldn't.

 We should be able to allow equalities of the form `tv ~ F tv1 .. tvn` with
 tv and tvi being distinct type variables without requiring
 `UndecidableInstances`.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2203
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] #1673: Template Haskell support for type families

2008-04-07 Thread GHC
#1673: Template Haskell support for type families
+---
 Reporter:  [EMAIL PROTECTED]  |  Owner: 
 Type:  feature request | Status:  new
 Priority:  low |  Milestone:  6.10 branch
Component:  Template Haskell|Version:  6.7
 Severity:  normal  | Resolution: 
 Keywords:  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Linux   |  
+---
Changes (by hpacheco):

 * cc: [EMAIL PROTECTED] (removed)
 * cc: [EMAIL PROTECTED] (added)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1673#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] #1673: Template Haskell support for type families

2008-04-07 Thread GHC
#1673: Template Haskell support for type families
+---
 Reporter:  [EMAIL PROTECTED]  |  Owner: 
 Type:  feature request | Status:  new
 Priority:  low |  Milestone:  6.10 branch
Component:  Template Haskell|Version:  6.7
 Severity:  normal  | Resolution: 
 Keywords:  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Linux   |  
+---
Changes (by hpacheco):

 * cc: [EMAIL PROTECTED] (added)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1673#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] #2151: GADTs in function Patterns

2008-04-07 Thread GHC
#2151: GADTs in function Patterns
--+-
 Reporter:  hpacheco  |  Owner:  chak   
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone:  6.10 branch
Component:  Compiler  |Version:  6.9
 Severity:  blocker   | Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Multiple   
   Os:  Multiple  |  
--+-
Changes (by hpacheco):

 * cc: [EMAIL PROTECTED] (added)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2151#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] #2157: Equality Constraints with Type Families

2008-04-07 Thread GHC
#2157: Equality Constraints with Type Families
-+--
 Reporter:  hpacheco |  Owner:  chak   
 Type:  feature request  | Status:  new
 Priority:  normal   |  Milestone:  6.10 branch
Component:  Compiler (Type checker)  |Version:  6.9
 Severity:  normal   | Resolution: 
 Keywords:   | Difficulty:  Unknown
 Testcase:   |   Architecture:  Multiple   
   Os:  Multiple |  
-+--
Changes (by hpacheco):

 * cc: [EMAIL PROTECTED] (added)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2157#comment:14
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] #1673: Template Haskell support for type families

2008-04-07 Thread GHC
#1673: Template Haskell support for type families
+---
 Reporter:  [EMAIL PROTECTED]  |  Owner: 
 Type:  feature request | Status:  new
 Priority:  low |  Milestone:  6.10 branch
Component:  Template Haskell|Version:  6.7
 Severity:  normal  | Resolution: 
 Keywords:  | Difficulty:  Unknown
 Testcase:  |   Architecture:  x86
   Os:  Linux   |  
+---
Comment (by hpacheco):

 Myself, I would simply like to be able to write TH code to automatically
 generate type family instances. However, I understand it is not a very
 important feature.

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