[GHC] #3049: STM with data invariants crashes GHC

2009-02-25 Thread GHC
#3049: STM with data invariants crashes GHC
---+
  Reporter:  simonpj   |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  6.10.1  
  Severity:  normal|   Keywords:  
Difficulty:  Unknown   |   Testcase:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
---+
 Ben Franksen writes: my ghc(i) crashes when using STM data invariants.
 This little piece of code demonstrates the problem:
 {{{
 module Bug where

 import Control.Concurrent.STM

 test = do
   x - atomically $ do
 v - newTVar 0
 always $ return True -- remove this line and all is fine
 return v
   atomically (readTVar x) = print
 }}}
 This is what ghci makes of it:
 {{{
 b...@sarun ghci Bug.hs
 GHCi, version 6.10.1: http://www.haskell.org/ghc/  :? for help
 Loading package ghc-prim ... linking ... done.
 Loading package integer ... linking ... done.
 Loading package base ... linking ... done.
 [1 of 1] Compiling Bug  ( Bug.hs, interpreted )
 Ok, modules loaded: Bug.
 *Bug test
 Loading package syb ... linking ... done.
 Loading package array-0.2.0.0 ... linking ... done.
 Loading package stm-2.1.1.2 ... linking ... done.
 zsh: segmentation fault  ghci Bug.hs
 }}}
 I am using ghc-6.10.1 freshly installed from source with just a 'cabal
 install stm' thrown after it.

 BTW, the documentation for `Control.Concurrent.STM.TVar` lists... nothing.
 Similar with `Control.Monad.STM`. Well, at least the source link works, so
 one isn't completely lost... :-)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3049
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] #1884: Win64 Port

2009-02-25 Thread GHC
#1884: Win64 Port
---+
Reporter:  simonmar|Owner: 
Type:  task|   Status:  new
Priority:  normal  |Milestone:  6.10 branch
   Component:  Compiler|  Version:  6.8.1  
Severity:  normal  |   Resolution: 
Keywords:  |   Difficulty:  Unknown
Testcase:  |   Os:  Windows
Architecture:  x86_64 (amd64)  |  
---+
Changes (by guest):

 * cc: bulat.zigans...@gmail.com (added)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1884#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] #2189: hSetBuffering stdin NoBuffering doesn't work on Windows

2009-02-25 Thread GHC
#2189: hSetBuffering stdin NoBuffering doesn't work on Windows
---+
Reporter:  FalconNL|Owner: 
Type:  bug |   Status:  new
Priority:  normal  |Milestone:  6.10.2 
   Component:  libraries/base  |  Version:  6.8.2  
Severity:  normal  |   Resolution: 
Keywords:  hsetbuffering buffering buffer  |   Difficulty:  Unknown
Testcase:  |   Os:  Windows
Architecture:  x86 |  
---+
Comment (by simonmar):

 Replying to [comment:17 sof]:
  I believe I have a trivial fix for this, and can forward for testing 
 commit, if still of interest.

 Yes please!

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189#comment:19
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] #2189: hSetBuffering stdin NoBuffering doesn't work on Windows

2009-02-25 Thread GHC
#2189: hSetBuffering stdin NoBuffering doesn't work on Windows
---+
Reporter:  FalconNL|Owner: 
Type:  bug |   Status:  new
Priority:  normal  |Milestone:  6.10.2 
   Component:  libraries/base  |  Version:  6.8.2  
Severity:  normal  |   Resolution: 
Keywords:  hsetbuffering buffering buffer  |   Difficulty:  Unknown
Testcase:  |   Os:  Windows
Architecture:  x86 |  
---+
Comment (by sof):

 ok, not futzing with making this a proper patch:

 {{{
 --- old-base/cbits/consUtils.c  2009-02-25 10:06:10.631125000 -0800
 +++ new-base/cbits/consUtils.c  2009-02-25 10:06:10.64675 -0800
 @@ -25,10 +25,13 @@
  DWORD flgs = ENABLE_LINE_INPUT | ENABLE_ECHO_INPUT;

  if ( (h = (HANDLE)_get_osfhandle(fd)) != INVALID_HANDLE_VALUE ) {
 +  /* Only for console-connected Handles */
 +  if ( GetFileType(h) == FILE_TYPE_CHAR ) {
 if ( GetConsoleMode(h,st) 
 -SetConsoleMode(h, cooked ? (st | ENABLE_LINE_INPUT) : st 
 ~flgs) ) {
 +SetConsoleMode(h, cooked ? (st | flgs) : st  ~flgs)  ) {
 return 0;
 }
 +  }
  }
  return -1;
  }

 --- old-base/GHC/Handle.hs  2009-02-25 10:06:10.631125000 -0800
 +++ new-base/GHC/Handle.hs  2009-02-25 10:06:10.64675 -0800
 @@ -1374,13 +1374,10 @@
is_tty - fdIsTTY (haFD handle_)
when (is_tty  isReadableHandleType (haType handle_)) $
  case mode of
 -#ifndef mingw32_HOST_OS
 --- 'raw' mode under win32 is a bit too specialised (and
 troublesome
 --- for most common uses), so simply disable its use here.
 +   -- Note: we used to disable 'cooked' mode setting
 +   -- for mingw / win32 here, but it is now back on (and
 well
 +   -- behaved for Console-connected Handles.)
NoBuffering - setCooked (haFD handle_) False
 -#else
 -  NoBuffering - return ()
 -#endif
_   - setCooked (haFD handle_) True

-- throw away spare buffers, they might be the wrong size
 }}}

 i.e., reliably (un)setting the line buffering flags of the underlying
 Console handle (if there's one) takes care of this.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2189#comment:20
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] #3050: parsec: bug in caret escape parsing

2009-02-25 Thread GHC
#3050: parsec: bug in caret escape parsing
-+--
Reporter:  sof   |  Owner:   
Type:  bug   | Status:  new  
Priority:  normal|  Component:  libraries (other)
 Version:  6.10.1|   Severity:  normal   
Keywords:|   Testcase:   
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple 
-+--
 The parsing of escape carets in character literals isn't quite right:
  * off-by-one (i.e., \^A == \NUL; ought to be \^A=\001)
  * only A-Z carets are supported.

 The following minor mod takes care of the problem:

 {{{
 --- Text/ParserCombinators/Parsec/Token.hs  2009-02-20
 10:49:32.11550 -0800
 +++ Text/ParserCombinators/Parsec/Token.hs.~1~  2009-02-20
 10:02:45.89675 -0800
 @@ -193,8 +193,8 @@

  -- charControl :: CharParser st Char
  charControl = do{ char '^'
 -; code - (oneOf ['@'..'_']) | char '?'
 -; return (if code == '?' then '\DEL' else toEnum
 (fromEnum code - fromEnum '@'))
 +; code - upper
 +; return (toEnum (fromEnum code - fromEnum 'A'))
  }
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/3050
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] #2739: GHC API crashes on template haskell splices

2009-02-25 Thread GHC
#2739: GHC API crashes on template haskell splices
-+--
Reporter:  waern |Owner:  nominolo
Type:  bug   |   Status:  closed  
Priority:  normal|Milestone:  6.10.2  
   Component:  Compiler  |  Version:  6.10.1  
Severity:  major |   Resolution:  fixed   
Keywords:|   Difficulty:  Unknown 
Testcase:|   Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  |  
-+--
Changes (by nominolo):

  * status:  assigned = closed
  * resolution:  = fixed

Comment:

 The above patched has been back-ported and appears to work.  Re-open this
 bug if you encounter any problems.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2739#comment:11
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] #3041: Arch independent binary representations

2009-02-25 Thread GHC
#3041: Arch independent binary representations
-+--
 Reporter:  nomeata  |  Owner:  
 Type:  feature request  | Status:  new 
 Priority:  normal   |  Milestone:  
Component:  Compiler |Version:  6.10.1  
 Severity:  normal   | Resolution:  
 Keywords:   |   Testcase:  
   Os:  Linux|   Architecture:  Unknown/Multiple
-+--
Comment (by kaol):

 Here's another thought regarding this. Let's remove the whole {{{instance
 Binary Int}}}. That'd make anyone using Binary to have to choose between
 using Int32 and Int64. Having an Int instance is just asking for errors
 when moving data between 32 and 64 bit architectures, at some point. It
 may be inconvenient for people using Binary, but I assume that it's meant
 to be a low level interface, anyway.

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