Re: [GHC] #4900: DEPENDS pragma

2012-07-17 Thread GHC
#4900: DEPENDS pragma
---+
  Reporter:  cdsmith   |  Owner:  
  Type:  feature request   | Status:  new 
  Priority:  normal|  Milestone:  7.6.1   
 Component:  Compiler  |Version:  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:  TH_Depends|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by parcs):

 I have attached a patch that implements this functionality in such a way
 that the `HPT` is not touched at all during the summarise stage. Instead,
 the required information that would have been read from the `HPT` during
 the summarise stage is now pulled out of the generated `ModIface` and into
 a field in the `ModSummary` during the upsweep stage. After the upsweep,
 the module graph is reset with the  updated `ModSummary`s containing the
 necessary, fresh data for use in the next load cycle. Overall, I think
 this implementation is nicer and easier to reason about than the previous
 one.

 (As a bonus, the `hsc_mod_graph` is now kept sorted in bottom..top order
 and so the "Ok, modules loaded: ..." message will list the modules in a
 logical order instead of the seemingly-random order they're currently
 listed. This change makes one of the tests in the ghci testsuite trivially
 fail, though.)

 I think the patch is incomplete, still, at least until the uses of
 `linkableTime` are looked over to make sure they don't operate under the
 assumption that `linkableTime` is simply the timestamp of the source file
 anymore.

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


[GHC] #7082: Default type family instances

2012-07-17 Thread GHC
#7082: Default type family instances
---+
 Reporter:  guest  |  Owner:
 
 Type:  bug| Status:  new   
 
 Priority:  normal |  Component:  Compiler (Type 
checker)
  Version:  7.4.1  |   Keywords:
 
   Os:  Unknown/Multiple   |   Architecture:  Unknown/Multiple  
 
  Failure:  GHC rejects valid program  |   Testcase:
 
Blockedby: |   Blocking:
 
  Related: |  
---+
 The following code does not compile in GHC 7.4, unless line (2) is
 uncommented. I thought line (1) would remove need for (2). If it does not,
 probably declaration (1) should cause an error.

 {{{
 {-# LANGUAGE TypeFamilies #-}
 class R m where
   type D m a :: *
   type D m a = ()-- (1)
   f :: m a -> D m a -> ()

 instance R Maybe where
   -- type D Maybe a = () -- (2)
   f = undefined

 x = f (Nothing :: Maybe Int) ()
 }}}

-- 
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] #5254: usb library fails on Windows

2012-07-17 Thread GHC
#5254: usb library fails on Windows
-+--
Reporter:  basvandijk|   Owner:   
Type:  bug   |  Status:  new  
Priority:  low   |   Milestone:  7.6.1
   Component:  Compiler (FFI)| Version:  7.0.3
Keywords:|  Os:  Windows  
Architecture:  Unknown/Multiple  | Failure:  Runtime crash
  Difficulty:|Testcase:   
   Blockedby:|Blocking:   
 Related:|  
-+--

Comment(by basvandijk):

 Summarizing: executing the following isolated program with the argument
 "fp" (for !ForeignPtr) gives an error and without it I get no error:

 {{{
 {-# LANGUAGE ForeignFunctionInterface #-}

 module Main where

 import Foreign
 import Foreign.C.Types
 import Control.Concurrent
 import System.Environment

 main :: IO ()
 main = do
   ctxPtr <- alloca $ \ctxPtrPtr -> do
   _ <- c'libusb_init ctxPtrPtr
   peek ctxPtrPtr

   args <- getArgs
   case args of
 ["fp"] -> do
   fp <- newForeignPtr p'libusb_exit ctxPtr
   threadDelay 100
   print $ fp == fp

 _ -> c'libusb_exit ctxPtr

 data C'libusb_context = C'libusb_context

 foreign import stdcall "libusb_init" c'libusb_init
   :: Ptr (Ptr C'libusb_context) -> IO CInt

 foreign import stdcall "&libusb_exit" p'libusb_exit
   :: FunPtr (Ptr C'libusb_context -> IO ())

 foreign import stdcall "libusb_exit" c'libusb_exit
   :: Ptr C'libusb_context -> IO ()
 }}}

 Note that building the program with the new `win64_alpha1` GHC doesn't
 produce the error. I only get warnings that the `stdcall` calling
 convention is not supported. So I guess it then falls back to the `ccall`
 calling convention which does work.

 Make sure to give these flags to cabal when building the program:

  * `--extra-include-dirs="...\libusb\include\libusb-1.0"`
  * `--extra-lib-dirs="...\libusb\MinGW32\dll"` or: `--extra-lib-
 dirs="...\libusb\MinGW64\dll"` when building with the new `win64_alpha1`
 GHC.

 and make sure the `libusb-1.0.dll` is in your working directory when
 running the program.

-- 
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] #7081: arrow analogs of lambda case and multi-way if

2012-07-17 Thread GHC
#7081: arrow analogs of lambda case and multi-way if
-+--
Reporter:  jeltsch   |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.5 
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * difficulty:  => Unknown


Comment:

 To me this all looks plausible. Do work with Dan on #7071.

-- 
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] #4429: Ability to specify the namespace in mkName

2012-07-17 Thread GHC
#4429: Ability to specify the namespace in mkName
-+--
Reporter:  reinerp   |   Owner:  reinerp 
Type:  feature request   |  Status:  new 
Priority:  low   |   Milestone:  7.6.1   
   Component:  Template Haskell  | Version:  6.12.3  
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by simonpj):

  * difficulty:  => Unknown


Comment:

 Reiner, I'm not sure what the status is on this ticket.  Now that we've
 done #5469, do you want to revisit this?

 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] #5469: Reorganisation of exports in template-haskell library

2012-07-17 Thread GHC
#5469: Reorganisation of exports in template-haskell library
---+
  Reporter:  reinerp   |  Owner:  simonpj 
  Type:  task  | Status:  closed  
  Priority:  normal|  Milestone:  7.6.1   
 Component:  Template Haskell  |Version:  7.2.1   
Resolution:  fixed |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonpj):

  * status:  patch => closed
  * resolution:  => fixed


Comment:

 Great, thanks Reiner.  I've committed them all.  (For tiresome reasons I
 had to apply them as patches, so they mention you in the comment rather
 than the author field.)

 Much obliged.

 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] #7074: Way too long, and unhelpful, error message

2012-07-17 Thread GHC
#7074: Way too long, and unhelpful, error message
---+
  Reporter:  ksf   |  Owner:  
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  
 Component:  Compiler  |Version:  7.4.2   
Resolution:  fixed |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by simonpj@…):

 commit a9a775ab5a484ca6a7530c776b1917b98789bef4
 {{{
 Author: Simon Peyton Jones 
 Date:   Mon Jul 16 17:02:07 2012 +0100

 Improve pretty printing for 'rec' Stmts, using pprDeeper

 Fixes Trac #7074

  compiler/hsSyn/HsExpr.lhs |4 ++--
  1 files changed, 2 insertions(+), 2 deletions(-)
 }}}

-- 
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] #6082: Program compiled with 7.4.1 runs many times slower than compiled with 7.2.2

2012-07-17 Thread GHC
#6082: Program compiled with 7.4.1 runs many times slower than compiled with 
7.2.2
--+-
Reporter:  gchrupala  |   Owner:  pcapriotti 
Type:  bug|  Status:  new
Priority:  high   |   Milestone:  7.4.3  
   Component:  libraries (other)  | Version:  7.4.1  
Keywords: |  Os:  Unknown/Multiple   
Architecture:  Unknown/Multiple   | Failure:  Runtime performance bug
  Difficulty:  Unknown|Testcase: 
   Blockedby: |Blocking: 
 Related: |  
--+-
Changes (by milan):

 * cc: fox@… (added)


Comment:

 Hi,

 I also came across this bug.

 The problem is that with array-0.4.0.0, the RULEs for unsafeFreeze and
 unsafeThaw do not fire. The problem can be reproduced by copying the
 attached `Test` module to either array-0.3.0.3 or array-0.4.0.0 package
 and adding it to array.cabal. The `Test` module contains the following
 method:
 {{{
 test bounds = m
   where m = runSTUArray $ do
   a <- newArray bounds 0

   a' <- unsafeFreeze a
   a'' <- unsafeThaw a'
   let _ = a' :: UArray Int Int
   _ = a'' `asTypeOf` a

   return a
 }}}
 Here are the results of compilation with GHC-7.4.1:
 {{{
 array-0.3.0.3
 Rule fired: Class op newArray
 Rule fired: unsafeFreeze/STUArray
 Rule fired: unsafeThaw/STUArray
 Rule fired: Class op return
 Rule fired: Class op >>=
 Rule fired: Class op >>=
 Rule fired: Class op >>=
 Rule fired: Class op rangeSize
 Rule fired: Class op rangeSize
 Rule fired: unpack-list
 }}}
 {{{
 array-0.4.0.0
 Rule fired: Class op newArray
 Rule fired: Class op return
 Rule fired: Class op >>=
 Rule fired: Class op >>=
 Rule fired: Class op >>=
 Rule fired: freeze/STUArray
 Rule fired: thaw/STUArray
 Rule fired: Class op rangeSize
 Rule fired: Class op rangeSize
 Rule fired: unpack-list
 }}}

-- 
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] #4900: DEPENDS pragma

2012-07-17 Thread GHC
#4900: DEPENDS pragma
---+
  Reporter:  cdsmith   |  Owner:  
  Type:  feature request   | Status:  new 
  Priority:  normal|  Milestone:  7.6.1   
 Component:  Compiler  |Version:  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:  TH_Depends|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by parcs):

 Replying to [comment:53 simonmar]:
 > I looked at the new patch, and maybe I'm being stupid here, but it looks
 like my previous concerns still apply.  Looking at the HPT during the
 summarise stage rings alarm bells - the `hsc_env` should only be used for
 its `DynFlags` and the finder cache.  So I'm still not sure how to reason
 that this patch works correctly.

 Regarding your previous concerns, the important part of this new patch is
 that `ms_uf_date` is not read at all during the summarize stage; it is
 only used to propagate the latest usage file date computed during the
 summarize stage to the stability check. Instead of comparing the previous
 `ms_uf_date` to the latest `ms_uf_date`, as the last patch did, the
 `usg_mtime`s are compared and calculated piecewise from the module's
 `HMI`. This is better because these mtimes get calculated during the
 `upsweep`, meaning that they will be as accurate as they can be for the
 next `load` cycle. (Compare the current `isOkUsageFileDate` with the
 previous patch's `getUsageFileDate`).

 I _believe_ that reading the `HPT` in the way that is done in the patch is
 safe -- it is only read if an old summary is available. Is it guaranteed
 that if an old summary is available, then a corresponding `HMI` exists
 within the `HPT`? It seems so, but I am not sure.

 Also, I should mention that it is necessary to compute and check the usage
 file dates before or during the summarise stage, because that's when a
 file is ran through the preprocessor, and a usage file may be a CPP
 include. Without the `HPT`, the only real information you have at that
 point is an old `ModSummary`. Therefore, if the `HPT` should not be read
 during the summarise stage, then it seems that the only alternative would
 be to stuff the `UsageFile` data from the `HMI` to a field of the
 corresponding `ModSummary`. An `HMI` is created during the `upsweep`
 stage, so the `hsc_mod_graph` would have to be updated after the `upsweep`
 occurs, which is currently not done and doing so would probably introduce
 its own subtleties. (Currently, the mod graph is only updated right after
 the summarise stage). Does this seem more reasonable to you?

-- 
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] #6166: Performance regression in mwc-random since 7.0.x

2012-07-17 Thread GHC
#6166: Performance regression in mwc-random since 7.0.x
---+
Reporter:  bos |   Owner: 
Type:  bug |  Status:  new
Priority:  high|   Milestone:  7.6.1  
   Component:  Compiler| Version:  7.4.2  
Keywords:  |  Os:  Unknown/Multiple   
Architecture:  x86_64 (amd64)  | Failure:  Runtime performance bug
  Difficulty:  Unknown |Testcase: 
   Blockedby:  |Blocking: 
 Related:  |  
---+
Changes (by bgamari):

 * cc: bgamari@… (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] #5006: Write locale character encoding to hpc html report

2012-07-17 Thread GHC
#5006: Write locale character encoding to hpc html report
---+
  Reporter:  basvandijk|  Owner:  simonmar
  Type:  bug   | Status:  closed  
  Priority:  normal|  Milestone:  7.6.1   
 Component:  Code Coverage |Version:  7.0.2   
Resolution:  fixed |   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonmar):

  * status:  patch => closed
  * resolution:  => fixed


Comment:

 Applied, thanks!

-- 
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] #4900: DEPENDS pragma

2012-07-17 Thread GHC
#4900: DEPENDS pragma
---+
  Reporter:  cdsmith   |  Owner:  
  Type:  feature request   | Status:  new 
  Priority:  normal|  Milestone:  7.6.1   
 Component:  Compiler  |Version:  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:  TH_Depends|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonmar):

  * owner:  simonmar =>
  * status:  patch => new


-- 
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] #4900: DEPENDS pragma

2012-07-17 Thread GHC
#4900: DEPENDS pragma
---+
  Reporter:  cdsmith   |  Owner:  simonmar
  Type:  feature request   | Status:  patch   
  Priority:  normal|  Milestone:  7.6.1   
 Component:  Compiler  |Version:  
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:  TH_Depends|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by simonmar):

 I looked at the new patch, and maybe I'm being stupid here, but it looks
 like my previous concerns still apply.  Looking at the HPT during the
 summarise stage rings alarm bells - the `hsc_env` should only be used for
 its `DynFlags` and the finder cache.  So I'm still not sure how to reason
 that this patch works correctly.

-- 
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] #7064: TH: Pragmas refactoring (also adds RULES and 'SPECIALIZE instance' support) [patch]

2012-07-17 Thread GHC
#7064: TH: Pragmas refactoring (also adds RULES and 'SPECIALIZE instance' 
support)
[patch]
+---
 Reporter:  mikhail.vorozhtsov  |  Owner:  
 Type:  bug | Status:  patch   
 Priority:  normal  |  Component:  Template Haskell
  Version:  7.5 |   Keywords:  
   Os:  Unknown/Multiple|   Architecture:  Unknown/Multiple
  Failure:  None/Unknown|   Testcase:  
Blockedby:  |   Blocking:  
  Related:  |  
+---
Changes (by mikhail.vorozhtsov):

  * status:  new => patch


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