[GHC] #7365: rem function in ghci changes result when using the Int type

2012-10-24 Thread GHC
#7365: rem function in ghci changes result when using the Int type
-+--
 Reporter:  leonardo |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  GHCi
  Version:  7.4.1|   Keywords:  
   Os:  Windows  |   Architecture:  x86 
  Failure:  Incorrect result at runtime  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 I define this function

 {{{
 congruent_modulo_n a b n = (rem a n) == (rem b n)
 }}}

 If the signature is:

 {{{
 congruent_modulo_n :: Integer-Integer-Integer-Bool
 }}}

 Then when I try this function in the ghci everything works perfect.
 If I use this signature:

 {{{
 congruent_modulo_n :: Int-Int-Int-Bool
 }}}
 Then for the following input I get False:

 {{{
 congruent_modulo_n (3^(113-1)) 1 113
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7365
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] #7365: rem function in ghci changes result when using the Int type

2012-10-24 Thread GHC
#7365: rem function in ghci changes result when using the Int type
-+--
 Reporter:  leonardo |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  GHCi
  Version:  7.4.1|   Keywords:  
   Os:  Windows  |   Architecture:  x86 
  Failure:  Incorrect result at runtime  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--

Comment(by michalt):

 I might be missing something but, I don't really see a bug here.
 ```3^112``` is way too big to fit into an ```Int```, so it will overflow.
 On the other hand ```Integer``` is an arbitrary-precision integer and
 should be able to represent this number correctly...

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7365#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] #1246: = operators get compiled worse than ==

2012-10-24 Thread GHC
#1246: = operators get compiled worse than ==
-+--
Reporter:  duncan|   Owner:  
Type:  bug   |  Status:  new 
Priority:  low   |   Milestone:  7.8.1   
   Component:  Compiler  | Version:  6.6 
Keywords:|  Os:  Unknown/Multiple
Architecture:  x86   | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonmar):

  * blockedby:  4258 =
  * milestone:  7.6.2 = 7.8.1


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1246#comment:12
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] #1246: = operators get compiled worse than ==

2012-10-24 Thread GHC
#1246: = operators get compiled worse than ==
---+
  Reporter:  duncan|  Owner: 
  Type:  bug   | Status:  closed 
  Priority:  low   |  Milestone:  7.8.1  
 Component:  Compiler  |Version:  6.6
Resolution:  fixed |   Keywords: 
Os:  Unknown/Multiple  |   Architecture:  x86
   Failure:  None/Unknown  | Difficulty:  Unknown
  Testcase:|  Blockedby: 
  Blocking:|Related: 
---+
Changes (by simonmar):

  * status:  new = closed
  * resolution:  = fixed


Comment:

 We now get equal performance for both of these functions, the only
 difference in the generated code is the conditional (= vs. ==).

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1246#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] #7365: rem function in ghci changes result when using the Int type

2012-10-24 Thread GHC
#7365: rem function in ghci changes result when using the Int type
--+-
  Reporter:  leonardo |  Owner: 
  Type:  bug  | Status:  closed 
  Priority:  normal   |  Milestone: 
 Component:  GHCi |Version:  7.4.1  
Resolution:  invalid  |   Keywords: 
Os:  Windows  |   Architecture:  x86
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown
  Testcase:   |  Blockedby: 
  Blocking:   |Related: 
--+-
Changes (by igloo):

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


Comment:

 Agreed: Thanks for the report, but, this is just a case of Int overflow,
 not a bug in GHC.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7365#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] #7351: showRichTokenStream has an off-by one error on starting col

2012-10-24 Thread GHC
#7351: showRichTokenStream has an off-by one error on starting col
-+--
Reporter:  alanz |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  GHC API   | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonmar):

  * difficulty:  = Unknown


Old description:

 When using showRichTokenStream to re-create a source file, all lines
 after the first one start one column from the left.

 The code for advancing to a new line has an off-by one bug where it
 assumes zero based columns.

 I have marked what I assume to be a fix in the pasted code below.

 ---
 showRichTokenStream ts = go startLoc ts 
 where sourceFile = getFile $ map (getLoc . fst) ts
   getFile [] = panic showRichTokenStream: No source file found
   getFile (UnhelpfulSpan _ : xs) = getFile xs
   getFile (RealSrcSpan s : _) = srcSpanFile s
   startLoc = mkRealSrcLoc sourceFile 1 1
   go _ [] = id
   go loc ((L span _, str):ts)
   = case span of
 UnhelpfulSpan _ - go loc ts
 RealSrcSpan s
  | locLine == tokLine - ((replicate (tokCol - locCol) '
 ') ++)
. (str ++)
. go tokEnd ts
  | otherwise - ((replicate (tokLine - locLine) '\n') ++)
   . ((replicate (tokCol - 1) ' ') ++) -- AZ:
 updated line
   . (str ++)
   . go tokEnd ts
   where (locLine, locCol) = (srcLocLine loc, srcLocCol
 loc)
 (tokLine, tokCol) = (srcSpanStartLine s,
 srcSpanStartCol s)
 tokEnd = realSrcSpanEnd s
 --

New description:

 When using showRichTokenStream to re-create a source file, all lines after
 the first one start one column from the left.

 The code for advancing to a new line has an off-by one bug where it
 assumes zero based columns.

 I have marked what I assume to be a fix in the pasted code below.

 {{{
 showRichTokenStream ts = go startLoc ts 
 where sourceFile = getFile $ map (getLoc . fst) ts
   getFile [] = panic showRichTokenStream: No source file found
   getFile (UnhelpfulSpan _ : xs) = getFile xs
   getFile (RealSrcSpan s : _) = srcSpanFile s
   startLoc = mkRealSrcLoc sourceFile 1 1
   go _ [] = id
   go loc ((L span _, str):ts)
   = case span of
 UnhelpfulSpan _ - go loc ts
 RealSrcSpan s
  | locLine == tokLine - ((replicate (tokCol - locCol) '
 ') ++)
. (str ++)
. go tokEnd ts
  | otherwise - ((replicate (tokLine - locLine) '\n') ++)
   . ((replicate (tokCol - 1) ' ') ++) -- AZ:
 updated line
   . (str ++)
   . go tokEnd ts
   where (locLine, locCol) = (srcLocLine loc, srcLocCol
 loc)
 (tokLine, tokCol) = (srcSpanStartLine s,
 srcSpanStartCol s)
 tokEnd = realSrcSpanEnd s
 }}}

--

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7351#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] #7351: showRichTokenStream has an off-by one error on starting col

2012-10-24 Thread GHC
#7351: showRichTokenStream has an off-by one error on starting col
-+--
Reporter:  alanz |   Owner:  simonmar
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  7.6.2   
   Component:  GHC API   | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonmar):

  * owner:  = simonmar
  * milestone:  = 7.6.2


Comment:

 Thanks, I'll commit.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7351#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] #7353: Make system IO interruptible on Windows

2012-10-24 Thread GHC
#7353: Make system IO interruptible on Windows
-+--
Reporter:  joeyadams |   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone:  7.8.1  
   Component:  libraries/base| Version:  7.6.1  
Keywords:|  Os:  Windows
Architecture:  Unknown/Multiple  | Failure:  Incorrect result at runtime
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by simonmar):

  * difficulty:  = Unknown
  * component:  Runtime System = libraries/base
  * milestone:  = 7.8.1


Comment:

 There are a few options:

  * maybe `foreign import ccall interruptible` will work for the FFI calls
 in the network package.  It causes `CancelSynchronousIo()` to be called
 when the thread is the target of an exception, but I have no idea whether
 this will actually work to interrupt the operation or not.

  * make a version of `threadWaitRead` that works for sockets.  This is
 easy; see #5797.  However, this won't necessarily cancel the operation
 when an exception is raised, you'll need to arrange that separately
 somehow.

  * Implement an IO manager for Windows.  This is of course the best
 solution, but it's a lot of work.  You'd need to bind all the appropriate
 APIs in the base package, maybe copying or moving bits of the Win32
 package into base.  Ideally instead of FDs in the IO library we would use
 Win32 `HANDLE`s, so there would need to be Win32 replacements for
 `GHC.IO.FD` and `GHC.IO.Handle.FD`.  This would have the nice effect of
 eliminating both the mingw and msvcrt layers from the IO library on Win32.
 Then the IO manager can use Win32 overlapped I/O.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7353#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] #7366: Strange data corruption with HEAD

2012-10-24 Thread GHC
#7366: Strange data corruption with HEAD
-+--
 Reporter:  bgamari  |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:   |   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Building GHC failed  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
 Since at least 5f37e0c ghc has failed to build for me. The failure occurs
 early in the final stage build, showing up as,

 {{{
 inplace/bin/ghc-stage2 -fPIC -dynamic  -H32m -O-hide-all-packages -i
 -iutils/haddock/src -iutils/haddock/dist/build
 -iutils/haddock/dist/build/autogen -Iutils/haddock/dist/build
 -Iutils/haddock/dist/build/autogen-optP-DIN_GHC_TREE -optP-include
 -optPutils/haddock/dist/build/autogen/cabal_macros.h -package Cabal-1.17.0
 -package array-0.4.0.1 -package base-4.6.0.0 -package containers-0.5.0.0
 -package directory-1.2.0.0 -package filepath-1.3.0.1 -package
 ghc-7.7.20121024 -package pretty-1.1.1.0 -package xhtml-3000.2.1 -package
 deepseq-1.3.0.1  -funbox-strict-fields -O2 -Wall -fwarn-tabs -XHaskell2010
 -XCPP -XDeriveDataTypeable -XScopedTypeVariables -XMagicHash  -no-user-
 package-db -rtsopts  -odir utils/haddock/dist/build -hidir
 utils/haddock/dist/build -stubdir utils/haddock/dist/build -hisuf dyn_hi
 -osuf  dyn_o -hcsuf dyn_hc -c utils/haddock/src/Haddock/GhcUtils.hs -o
 utils/haddock/dist/build/Haddock/GhcUtils.dyn_o
 /m/vinci7/data1/dietz/ghc/ghc/inplace/lib/settings: openFile: does not
 exist (No such file or directory)
 }}}
 Investigation with strace shows that the path passed to open() has been
 corrupted,
 {{{
 
open(/m/vinci7/data1/dietz/ghc/ghc/inplace/lib/settin@\270\215\240\347\277\212,
 O_RDONLY|O_NOCTTY|O_NONBLOCK) = -1 ENOENT (No such file or directory)
 }}}

 Furthermore, the stage 1 testsuite fails immediately,
 {{{
 $ make
 ../mk/boilerplate.mk:149: ../mk
 /ghcconfig_m_vinci7_data1_dietz_ghc_ghc_inplace_bin_ghc-stage2.mk: No such
 file or directory
 ../mk/ghc-config /m/vinci7/data1/dietz/ghc/ghc/inplace/bin/ghc-stage2
 ../mk/ghcconfig_m_vinci7_data1_dietz_ghc_ghc_inplace_bin_ghc-stage2.mk;
 if [ $? != 0 ]; then rm -f ../mk
 /ghcconfig_m_vinci7_data1_dietz_ghc_ghc_inplace_bin_ghc-stage2.mk; exit
 1; fi
 ghc-config: b���羌
 make: *** [../mk/ghcconfig_m_vinci7_data1_dietz_ghc_ghc_inplace_bin_ghc-
 stage2.mk] Error 1
 }}}

 I am using gcc 4.4.6 and have tried both self-built ghc 7.4.2 and ghc
 7.6.1 for stage 0.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7366
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] #7366: Strange data corruption with HEAD

2012-10-24 Thread GHC
#7366: Strange data corruption with HEAD
-+--
 Reporter:  bgamari  |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:   |   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Building GHC failed  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--

Comment(by bgamari):

 To be clear, this is the output of make stage=1 (which was omitted from
 the run cited previously),
 {{{
 $ make stage=1
 ../mk/boilerplate.mk:149: ../mk
 /ghcconfig_m_vinci7_data1_dietz_ghc_ghc_inplace_bin_ghc-stage1.mk: No such
 file or directory
 ../mk/ghc-config /m/vinci7/data1/dietz/ghc/ghc/inplace/bin/ghc-stage1
 ../mk/ghcconfig_m_vinci7_data1_dietz_ghc_ghc_inplace_bin_ghc-stage1.mk;
 if [ $? != 0 ]; then rm -f ../mk
 /ghcconfig_m_vinci7_data1_dietz_ghc_ghc_inplace_bin_ghc-stage1.mk; exit
 1; fi
 ghc-config: ���美
 make: *** [../mk/ghcconfig_m_vinci7_data1_dietz_ghc_ghc_inplace_bin_ghc-
 stage1.mk] Error 1
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7366#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] #7366: Strange data corruption with HEAD

2012-10-24 Thread GHC
#7366: Strange data corruption with HEAD
-+--
 Reporter:  bgamari  |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:   |   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Building GHC failed  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
Changes (by bgamari):

 * cc: bgamari@… (added)


Comment:

 I have now reproduced this on two machines. I believe the regression
 occurred sometime between 176a360 and 0b3811c.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7366#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] #7353: Make system IO interruptible on Windows

2012-10-24 Thread GHC
#7353: Make system IO interruptible on Windows
-+--
Reporter:  joeyadams |   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Milestone:  7.8.1  
   Component:  libraries/base| Version:  7.6.1  
Keywords:|  Os:  Windows
Architecture:  Unknown/Multiple  | Failure:  Incorrect result at runtime
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--

Comment(by joeyadams):

 ''maybe foreign import ccall interruptible will work for the FFI calls in
 the network package.''

 Unfortunately, this is only available on Windows Vista and up.  My program
 has to run on Windows XP.

 I looked into some potential approaches to wait for IO on Windows.  Please
 do point out any errors in this assessment.

 == Completion ports ==

 This would involve a manager thread that repeatedly calls
 [http://msdn.microsoft.com/en-
 us/library/windows/desktop/aa364986(v=vs.85).aspx
 GetQueuedCompletionStatus].  To perform sends and receives, we would use
 calls like [http://msdn.microsoft.com/en-
 us/library/windows/desktop/ms737606(v=vs.85).aspx ConnectEx] and
 [http://msdn.microsoft.com/en-
 us/library/windows/desktop/ms741688(v=vs.85).aspx WSARecv].  Caveats:

  * IOCP doesn't provide a way to wait for socket readiness, as far as I
 can tell.  This means threadWaitRead and IODevice.ready will have to be
 emulated by some other means.

  On the other hand, it might be possible using zero-size reads/writes.

  * IO operations are sensitive to the calling thread.  From the
 documentation of [http://msdn.microsoft.com/en-
 us/library/windows/desktop/ms741688(v=vs.85).aspx WSARecv]:

 '''Note'''  All I/O initiated by a given thread is canceled when that
 thread exits. For overlapped sockets, pending asynchronous operations can
 fail if the thread is closed before the operations complete. See
 !ExitThread for more information.

  Thus, we'll probably need a manager that assigns I/O jobs to threads such
 that no thread has multiple pending jobs involving the same HANDLE.

 == select ==

 We could have a thread call [http://msdn.microsoft.com/en-
 us/library/windows/desktop/ms740141(v=vs.85).aspx select] to wait on
 sockets in bulk.  Caveats:

  * select() is limited to 64 sockets, so we'd have to manage a pool of
 threads to wait for more sockets.

  * As far as I can tell, there is no way to interrupt select() except by
 giving it a short timeout, or by writing to a control socket to prod the
 IO manager (the GHC event manager does this).  We can't create such a
 socket on Windows without making the program host on a system port.

  I suppose we could repeat the select() every 0.1 seconds or so, but this
 would cause a lot of latency; each read and write would spend up to this
 long waiting for the IO manager.

  A faster approach would be to have the caller do a blocking select for a
 short period of time.  If that times out, then we use the IO manager.
 This keeps quick waits quick, and has little effect on longer waits.

 == WSAEventSelect ==

 We could instead use [http://msdn.microsoft.com/en-
 us/library/windows/desktop/ms741576(v=vs.85).aspx WSAEventSelect] and
 [http://msdn.microsoft.com/en-
 us/library/windows/desktop/ms687025(v=vs.85).aspx WaitForMultipleObjects],
 which provides more flexibility than select(), and lets us create our own
 event handle which we can use to interrupt the IO manager.  Caveats:

  * WSAEventSelect sets the socket to non-blocking mode, and cancels any
 previous WSAEventSelect and WSAAsyncSelect calls on the same socket.  This
 might clash with libraries.

  * !WaitForMultipleObjects is also limited to 64 handles, so we'd have to
 manage a thread pool.

 == A plan ==

 Here's a plan: implement an IO manager for Windows using
 !WaitForMultipleObjects, which allows callers to wait on their own HANDLEs
 using a function like this:

 {{{
 registerHandle :: EventManager - (HandleKey - IO ()) - HANDLE - IO
 HandleKey
 }}}

 Using WSAEventSelect, we can implement the following on top:

 {{{
 evtRead, evtWrite, evtOOB, evtAccept, evtConnect, ... :: Event

 registerSocket :: EventManager - (SocketKey - Event - IO ()) - Fd -
 Event - IO FdKey
 }}}

 This API is modeled off of
 [http://hackage.haskell.org/packages/archive/base/latest/doc/html/GHC-
 Event.html GHC.Event].

 Now we can implement an alternative to threadWaitRead and threadWaitWrite
 for Windows sockets:

 {{{
 waitSocket :: Event - Fd - IO ()
 }}}

 With this, it should be possible to update Network.Socket and GHC.IO.FD so
 blocking operations can 

Re: [GHC] #7349: -fth is deprecated without warning

2012-10-24 Thread GHC
#7349: -fth is deprecated without warning
--+-
 Reporter:  guest |  Owner:  
 Type:  bug   | Status:  patch   
 Priority:  normal|  Component:  Compiler
  Version:  7.6.1 |   Keywords:  
   Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
  Failure:  None/Unknown  |   Testcase:  
Blockedby:|   Blocking:  
  Related:|  
--+-
Changes (by guest):

  * status:  new = patch


Comment:

 Fix is a one-liner. Bug: The operator () was used for the (-) r monad,
 instead of DynP, and it ignored its left argument.

 {{{
 diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
 index 121c85f..138cb99 100644
 --- a/compiler/main/DynFlags.hs
 +++ b/compiler/main/DynFlags.hs
 @@ -2372,7 +2372,7 @@ fFlags = [
  fLangFlags :: [FlagSpec ExtensionFlag]
  fLangFlags = [
( th,   Opt_TemplateHaskell,
 -deprecatedForExtension TemplateHaskell  checkTemplateHaskellOk ),
 +\x - deprecatedForExtension TemplateHaskell x 
 checkTemplateHaskellOk x ),
( fi,   Opt_ForeignFunctionInterface,
  deprecatedForExtension ForeignFunctionInterface ),
( ffi,  Opt_ForeignFunctionInterface,
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7349#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] #7366: Strange data corruption with HEAD

2012-10-24 Thread GHC
#7366: Strange data corruption with HEAD
-+--
 Reporter:  bgamari  |  Owner:  
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:   |   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Building GHC failed  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--

Comment(by bgamari):

 Here is my bisection log.
 {{{
 git bisect start
 # good: [176a360031e1e7ef4d49ff18f1dd3e32ce4f56d9] Fix typo
 git bisect good 176a360031e1e7ef4d49ff18f1dd3e32ce4f56d9
 # bad: [0b3811c093736950c1d2757fb12dba60f9bf97ca] typo
 git bisect bad 0b3811c093736950c1d2757fb12dba60f9bf97ca
 # good: [2c2be637206cb1d58f4fc8a4a2e717e419c9fa5d] comments only
 git bisect good 2c2be637206cb1d58f4fc8a4a2e717e419c9fa5d
 # bad: [88a6f863d9f127fc1b03a1e2f068fd20ecbe096c] Small optimisation:
 always sink/inline reg1 = reg2 assignments
 git bisect bad 88a6f863d9f127fc1b03a1e2f068fd20ecbe096c
 # good: [2471a6bacccdf4d187aa4b31c382d5a5094b6fa5] Use canned heap checks
 to save a few bytes of code
 git bisect good 2471a6bacccdf4d187aa4b31c382d5a5094b6fa5
 # good: [2324b40f65b5cb7e427c5ec0185d635422b4a265] removeWay should also
 unset the wayGeneralFlags
 git bisect good 2324b40f65b5cb7e427c5ec0185d635422b4a265
 # good: [a7e0d4484189d08125083638582a6f8e4ae44801] a small -fPIC
 optimisation
 git bisect good a7e0d4484189d08125083638582a6f8e4ae44801
 }}}

 It seems that the first bad commit is,
 {{{
 commit 88a6f863d9f127fc1b03a1e2f068fd20ecbe096c
 Author: Simon Marlow marlo...@gmail.com
 Date:   Tue Oct 23 13:06:17 2012 +0100

 Small optimisation: always sink/inline reg1 = reg2 assignments

 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7366#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] #7366: Strange data corruption with HEAD

2012-10-24 Thread GHC
#7366: Strange data corruption with HEAD
-+--
 Reporter:  bgamari  |  Owner:  smarlow 
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:   |   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Building GHC failed  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
Changes (by bgamari):

  * owner:  = smarlow


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7366#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] #7366: Strange data corruption with HEAD

2012-10-24 Thread GHC
#7366: Strange data corruption with HEAD
-+--
 Reporter:  bgamari  |  Owner:  simonmar
 Type:  bug  | Status:  new 
 Priority:  normal   |  Component:  Compiler
  Version:   |   Keywords:  
   Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
  Failure:  Building GHC failed  |   Testcase:  
Blockedby:   |   Blocking:  
  Related:   |  
-+--
Changes (by bgamari):

  * owner:  smarlow = simonmar


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