Re: [GHC] #1642: Space leak Control.Monad.Strict

2007-08-29 Thread GHC
#1642: Space leak Control.Monad.Strict
--+-
Reporter:  [EMAIL PROTECTED]  |Owner: 
Type:  support request|   Status:  closed 
Priority:  normal |Milestone: 
   Component:  Compiler   |  Version:  6.7
Severity:  critical   |   Resolution:  invalid
Keywords: |   Difficulty:  Unknown
  Os:  Unknown| Testcase: 
Architecture:  Unknown|  
--+-
Comment (by simonpj):

 However, if the result of that discussion is that something is wrong with
 what GHC is doing, then do by all means re-open the bug with more specific
 details of what is wrong.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1642
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] #1643: Unnecessary dictionaries

2007-08-29 Thread GHC
#1643: Unnecessary dictionaries
-+--
Reporter:  guest |Owner:  simonpj
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.7
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  MacOS X   | Testcase: 
Architecture:  x86   |  
-+--
Changes (by simonpj):

  * owner:  = simonpj

Comment:

 Ah I see -- it's to do with (the new) implication constraints.  I'm snowed
 this week, but I'll look at it after that.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1643
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] #1614: Type checker does not use fundep to avoid ambiguity

2007-08-29 Thread GHC
#1614: Type checker does not use fundep to avoid ambiguity
+---
Reporter:  guest|Owner: 
Type:  bug  |   Status:  new
Priority:  normal   |Milestone:  6.8
   Component:  Compiler (Type checker)  |  Version:  6.7
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Unknown
  Os:  MacOS X  | Testcase: 
Architecture:  x86  |  
+---
Comment (by chak):

 This works with the latest head:
 {{{
 {-# OPTIONS_GHC -fglasgow-exts #-}

 module E where

 data E v a = E a
 data RValue

 instance (v ~ RValue, Eq a) = Eq (E v a) where
 E x == E y  =  x == y

 a :: E v Int
 a = undefined

 foo = a == a
 }}}
 So, I agree with SimonPJ, death to functional dependencies.  This solution
 was btw SimonPJ's idea (he just couldn't test it as his latest build
 wasn't complete yet.)

 `t1 ~ t2` is an equality constraint and part of the type families patch
 that landed in the head yesterday.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1614
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] #915: Implement list fusion using streams instead of foldr/build

2007-08-29 Thread GHC
#915: Implement list fusion using streams instead of foldr/build
---+
Reporter:  simonpj |Owner:  simonpj   
Type:  task|   Status:  new   
Priority:  normal  |Milestone:  6.8   
   Component:  libraries/base  |  Version:  6.6   
Severity:  normal  |   Resolution:
Keywords:  fusion  |   Difficulty:  Project ( 1 week)
  Os:  Unknown | Testcase:  N/A   
Architecture:  Multiple|  
---+
Changes (by guest):

  * cc:  [EMAIL PROTECTED] = [EMAIL PROTECTED],
 [EMAIL PROTECTED]

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


runghc printing result of main when main is not IO ()

2007-08-29 Thread Tomasz Zielonka
Hello!

Consider:

$ cat R.hs 
main = return [()]
$ runghc R.hs 
[()]

This was a bit surprising for me, because I thought that runghc
mimics the way a compiled program behaves.

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


Re: [GHC] #1375: ByteString’s “line s” eats empty lines

2007-08-29 Thread GHC
#1375: ByteString’s “lines” eats empty lines
---+
Reporter:  guest   |Owner:  [EMAIL PROTECTED], [EMAIL 
PROTECTED]
Type:  bug |   Status:  closed  
 
Priority:  high|Milestone:  6.8 
 
   Component:  libraries/base  |  Version:  6.6.1   
 
Severity:  normal  |   Resolution:  fixed   
 
Keywords:  |   Difficulty:  Unknown 
 
  Os:  Unknown | Testcase:  bytestring006   
 
Architecture:  Unknown |  
---+
Changes (by igloo):

  * resolution:  = fixed
  * testcase:  = bytestring006
  * status:  new = closed

Comment:

 Fixed by Duncan:
 {{{
 Mon Aug 27 16:23:45 BST 2007  Duncan Coutts [EMAIL PROTECTED]
   * Fix Lazy.lines foo\n\nbar
 }}}
 and now tested by bytestring006.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1375
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: Data.HashTable.hashInt seems somewhat sub-optimal

2007-08-29 Thread Ian Lynagh

Hi,

On Tue, Aug 28, 2007 at 11:41:22AM -0400, Jan-Willem Maessen wrote:
 
 golden :: Int32
 golden = 1013904242 -- = round ((sqrt 5 - 1) * 2^32) :: Int32
 -- was -1640531527 = round ((sqrt 5 - 1) * 2^31) :: Int32
 -- but that has bad mulHi properties (even adding 2^32 to get its  
 inverse)
 -- Whereas the above works well and contains no hash duplications for
 -- [-32767..65536]
 
 hashInt32 :: Int32 - Int32
 hashInt32 x = mulHi x golden + x

This gives

 map hashInt [0..16]
[0,1,2,3,4,6,7,8,9,11,12,13,14,16,17,18,19]

 --  (length $ group $ sort $ map hashInt [-32767..65536]) == 65536 +  
 32768

This test also passes for the

golden :: Int32
golden = -1640531527

hashInt :: Int - Int32
hashInt x = fromIntegral x * golden

implementation, which has a very pretty distribution; graph at the
bottom of
http://www.brpreiss.com/books/opus4/html/page214.html

 hashString :: String - Int32
 hashString = foldl' f golden
   where f m c = fromIntegral (fromEnum c) * magic + hashInt32 m
 magic = 0xdeadbeef

Why use magic rather than golden? This makes sense to me:

hashString :: String - Int32
hashString = foldl' f golden
  where f m c = (fromIntegral (ord c) `xor` m) * golden 

Is anything obviously wrong with it?


Thanks
Ian

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


Re: [GHC] #1614: Type checker does not use fundep to avoid ambiguity

2007-08-29 Thread GHC
#1614: Type checker does not use fundep to avoid ambiguity
+---
Reporter:  guest|Owner: 
Type:  bug  |   Status:  new
Priority:  normal   |Milestone:  6.8
   Component:  Compiler (Type checker)  |  Version:  6.7
Severity:  normal   |   Resolution: 
Keywords:   |   Difficulty:  Unknown
  Os:  MacOS X  | Testcase: 
Architecture:  x86  |  
+---
Comment (by guest):

 Using v ~ RValue works like a charm!

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1614
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] #1648: ghci linker does not know about rts_getWord64

2007-08-29 Thread GHC
#1648: ghci linker does not know about rts_getWord64
-+--
  Reporter:  duncan  |  Owner:
  Type:  bug | Status:  new   
  Priority:  normal  |  Milestone:  6.8   
 Component:  Runtime System  |Version:  6.6.1 
  Severity:  major   |   Keywords:
Difficulty:  Easy (1 hr) | Os:  Linux 
  Testcase:  |   Architecture:  x86_64 (amd64)
-+--
I stumbled into this with this code:

 {{{
 foreign export ccall gtk2hs_store_get_column_type_impl
   customTreeModelGetColumnType_static :: StablePtr
 (CustomTreeModelImplementation row) - CInt - IO GType
 }}}

 {{{GType}}} turns out to be a {{{CULong}}} and I'm on a 64bit arch.

 So the _stub.c file end up using {{{rts_getWord64}}}

 However when we try and load {{{ghci -package gtk}}} we get a linker error
 from the ghci linker because it doesn't know {{{rts_getWord64}}}.

 Indeed, inspecting {{{rts/Linker.c we}}} have {{{rts_getWord}}} and
 {{{rts_getWord32}}} but not {{{rts_getWord64}}}.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1648
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] #1649: running GHCi screws up console display by changing code page

2007-08-29 Thread GHC
#1649: running GHCi screws up console display by changing code page
--+-
  Reporter:  guest|  Owner:
  Type:  bug  | Status:  new   
  Priority:  normal   |  Milestone:
 Component:  GHCi |Version:  6.6.1 
  Severity:  normal   |   Keywords:  codepage code page
Difficulty:  Unknown  | Os:  Windows   
  Testcase:   |   Architecture:  x86   
--+-
[Note:  tested on two computers, both running the US English version of
 Windows XP Professional.]

 Running GHCi screws up the display of non-ASCII characters like the line-
 drawing characters used in most interactive text-mode programs.

 Apparently, GHCi changes the code page of the console session to 28591 for
 some reason and then fails to change it back when it exits.

 To reproduce:

 1) Open up a new Command Prompt window.

 2) Run the CHCP command to see what the current code page is set to
 (probably 437) and run a text mode program such as EDIT that makes use of
 non-ASCII characters to confirm that it displays correctly.

 3) Navigate to the GHC bin directory, run ghci.exe, then immediately exit
 via :q .

 4) Run CHCP again to confirm that the code page has changed.  Likewise,
 run EDIT (or whatever) again to confirm that it no longer displays
 correctly.


 Workaround:  issuing a CHCP 437 command after running GHCi fixes the
 problem.

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