Re: [GHC] #7420: mis-attributed kind in the explict type/kind signature

2012-11-16 Thread GHC
#7420: mis-attributed kind in the explict type/kind signature
---+
Reporter:  guest   |   Owner:   
Type:  bug |  Status:  new  
Priority:  normal  |   Milestone:   
   Component:  Compiler| Version:  7.4.2
Keywords:  |  Os:  FreeBSD  
Architecture:  x86_64 (amd64)  | Failure:  GHC rejects valid program
  Difficulty:  Unknown |Testcase:   
   Blockedby:  |Blocking:   
 Related:  |  
---+
Changes (by simonpj):

  * difficulty:  = Unknown


Old description:

 The following simple code

 {-# LANGUAGE DataKinds #-}[[BR]]
 {-# LANGUAGE KindSignatures #-}[[BR]]
 {-# LANGUAGE PolyKinds #-}[[BR]]
 {-# LANGUAGE ScopedTypeVariables #-}[[BR]]

 data Proxy tp

 hUpdateAtLabel :: forall l (n::Bool) v. v - () - ()

 hUpdateAtLabel _ () = undefined (undefined::Proxy (n::Bool))

 fails to type-check. The error message betrays a deep confusion in the
 kind checker:

 /tmp/s3.hs:9:52:
 Kind mis-match

 An enclosing kind signature specified kind `Bool',

 but `n' has kind `l'

 In an expression type signature: Proxy (n :: Bool)

 In the first argument of `undefined', namely
   `(undefined :: Proxy (n :: Bool))'

 In the expression: undefined (undefined :: Proxy (n :: Bool))

 If I write

 hUpdateAtLabel :: forall (l :: *) (n::Bool) v. v - () - ()

 hUpdateAtLabel _ () = undefined (undefined::Proxy (n::Bool))

 the code type-checks. However,

 hUpdateAtLabel :: forall l1 (l :: *) (n::Bool) v. v - () - ()

 hUpdateAtLabel _ () = undefined (undefined::Proxy (n::Bool))

 reports an error

 Kind mis-match

 An enclosing kind signature specified kind `Bool',

 but `n' has kind `*'

 It looks like an off-by-one error, at least in the error message.

New description:

 The following simple code
 {{{
 {-# LANGUAGE DataKinds #-}[[BR]]
 {-# LANGUAGE KindSignatures #-}[[BR]]
 {-# LANGUAGE PolyKinds #-}[[BR]]
 {-# LANGUAGE ScopedTypeVariables #-}[[BR]]

 data Proxy tp

 hUpdateAtLabel :: forall l (n::Bool) v. v - () - ()

 hUpdateAtLabel _ () = undefined (undefined::Proxy (n::Bool))
 }}}
 fails to type-check. The error message betrays a deep confusion in the
 kind checker:
 {{{
 /tmp/s3.hs:9:52:
 Kind mis-match
 An enclosing kind signature specified kind `Bool',
 but `n' has kind `l'
 In an expression type signature: Proxy (n :: Bool)
 In the first argument of `undefined', namely
   `(undefined :: Proxy (n :: Bool))'
 In the expression: undefined (undefined :: Proxy (n :: Bool))
 }}}
 If I write
 {{{
 hUpdateAtLabel :: forall (l :: *) (n::Bool) v. v - () - ()
 hUpdateAtLabel _ () = undefined (undefined::Proxy (n::Bool))
 }}}
 the code type-checks. However,
 {{{
 hUpdateAtLabel :: forall l1 (l :: *) (n::Bool) v. v - () - ()
 hUpdateAtLabel _ () = undefined (undefined::Proxy (n::Bool))
 }}}
 reports an error
 {{{
 Kind mis-match
 An enclosing kind signature specified kind `Bool',
 but `n' has kind `*'
 }}}
 It looks like an off-by-one error, at least in the error message.

--

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7420#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] #7420: mis-attributed kind in the explict type/kind signature

2012-11-16 Thread GHC
#7420: mis-attributed kind in the explict type/kind signature
+---
  Reporter:  guest  |  Owner:
  Type:  bug| Status:  closed
  Priority:  normal |  Milestone:
 Component:  Compiler   |Version:  7.4.2 
Resolution:  fixed  |   Keywords:
Os:  FreeBSD|   Architecture:  x86_64 (amd64)
   Failure:  GHC rejects valid program  | Difficulty:  Unknown   
  Testcase: |  Blockedby:
  Blocking: |Related:
+---
Changes (by simonpj):

  * status:  new = closed
  * resolution:  = fixed


Comment:

 Thanks.  Polymorphic kinds were not an advertised feature of GH 7.4; the
 flags existed but they didn't work properly.  Kind polymorphism does work
 in 7.6, and indeed happily this program works fine in 7.6 and HEAD.

 Simon

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7420#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] #7062: Spurious undefined reference to `openpty'

2012-11-16 Thread GHC
#7062: Spurious undefined reference to `openpty'
---+
  Reporter:  simonmar  |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  high  |  Milestone:  7.6.2   
 Component:  Compiler  |Version:  7.4.2   
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+

Comment(by trommler):

 Replying to [comment:23 markwright]:
  Replying to [comment:21 trommler]:
 
  I added this patch to #3072 to add an rpath to the ghc core libs
 I built HEAD and the patch fixes the issue.

 The test, however, still fails with the same error. To fix that error we
 need to do the same thing in testsuite for Linux that we do for OS X and
 for Windows already: Set an environment variable to point ld.so to the
 freshly built libraries. Otherwise the system libraries will be used (if
 present) and this is not what we want in testsuite.

 For builds that link with --enable-new-dtags (.so contains both RUNPATH
 and RPATH) setting LD_LIBRARY_PATH would be sufficient. If only RPATH is
 set (--disable-new-dtags), however, LD_PRELOAD must be used to override
 RPATH. LD_PRELOAD works in both cases, so LD_PRELOAD should be set.

 I could create a patch for testsuite to implement that.

 Are there plans to merge markwright's patch into 7.6?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7062#comment:24
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] #7417: replace Control.Concurrent.QSem (was: Undeprecate Control.Concurrent.QSem)

2012-11-16 Thread GHC
#7417: replace Control.Concurrent.QSem
---+
  Reporter:  tibbe |  Owner:  
  Type:  bug   | Status:  new 
  Priority:  normal|  Milestone:  
 Component:  libraries/base|Version:  7.6.1   
Resolution:|   Keywords:  
Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
   Failure:  None/Unknown  | Difficulty:  Unknown 
  Testcase:|  Blockedby:  
  Blocking:|Related:  
---+
Changes (by simonmar):

  * status:  closed = new
  * resolution:  wontfix =


Comment:

 Ian is right, there's no good reason to have these in base, except that we
 inconvenience users by removing them without making alternative provisions
 (Duncan's point).  So I propose that we

  * make sure there's a clear replacement
  * arrange that it will be in the platform when the platform adopts 7.8

 and if we can't do these, then we should put the original modules back. (I
 think we could do without `mergeIO`, but at least `QSem` is important).

 I've been experimenting with semaphore implementations:
 [https://github.com/simonmar/sem]

 The one in [https://github.com/simonmar/sem/blob/master/Sem2.hs] is
 reasonably simple, safe from async exceptions, and has good performance
 (better than the ones in SafeSemaphore).  We could make a new package,
 with this as a starting point perhaps?  It's only a tiny bit of code
 though.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7417#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] #7270: Incorrect optimization with Data.ByteString.append

2012-11-16 Thread GHC
#7270: Incorrect optimization with Data.ByteString.append
--+-
  Reporter:  ocheron  |  Owner:  duncan  
  Type:  bug  | Status:  merge   
  Priority:  highest  |  Milestone:  7.6.2   
 Component:  libraries (other)|Version:  7.6.1   
Resolution:   |   Keywords:  
Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
   Failure:  Incorrect result at runtime  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by duncan):

  * status:  new = merge


Comment:

 Oops, dunno how that happened. Fixed.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7270#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] #7407: error: expected ';' before 'else'

2012-11-16 Thread GHC
#7407: error: expected ';' before 'else'
-+--
Reporter:  erikd |   Owner:  simonmar   
Type:  bug   |  Status:  new
Priority:  highest   |   Milestone:  7.8.1  
   Component:  Compiler  | Version:  7.7
Keywords:|  Os:  Linux  
Architecture:  Unknown/Multiple  | Failure:  Building GHC failed
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--
Changes (by simonmar):

  * owner:  = simonmar
  * difficulty:  = Unknown
  * priority:  normal = highest
  * milestone:  = 7.8.1


Comment:

 I'm fixing this.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7407#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] #1409: Allow recursively dependent modules transparently (without .hs-boot or anything)

2012-11-16 Thread GHC
#1409: Allow recursively dependent modules transparently (without .hs-boot or
anything)
-+--
Reporter:  Isaac Dupree  |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  _|_ 
   Component:  Compiler  | Version:  6.10.2  
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--
Changes (by hvr):

 * cc: hvr@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1409#comment:57
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] #4385: Type-level natural numbers

2012-11-16 Thread GHC
#4385: Type-level natural numbers
+---
Reporter:  diatchki |   Owner:  diatchki
Type:  feature request  |  Status:  new 
Priority:  normal   |   Milestone:  7.6.2   
   Component:  Compiler (Type checker)  | Version:  
Keywords:   |  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple | Failure:  None/Unknown
  Difficulty:   |Testcase:  
   Blockedby:   |Blocking:  
 Related:   |  
+---
Changes (by hvr):

 * cc: hvr@… (added)


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/4385#comment:56
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] #7407: error: expected ';' before 'else'

2012-11-16 Thread GHC
#7407: error: expected ';' before 'else'
-+--
Reporter:  erikd |   Owner:  simonmar   
Type:  bug   |  Status:  new
Priority:  highest   |   Milestone:  7.8.1  
   Component:  Compiler  | Version:  7.7
Keywords:|  Os:  Linux  
Architecture:  Unknown/Multiple  | Failure:  Building GHC failed
  Difficulty:  Unknown   |Testcase: 
   Blockedby:|Blocking: 
 Related:|  
-+--

Comment(by marlowsd@…):

 commit 80269ef4899252e22319e9223b6c50df5600ccd3
 {{{
 Author: Simon Marlow marlo...@gmail.com
 Date:   Fri Nov 16 13:54:52 2012 +

 fix syntax error in generated C (#7407)

  compiler/cmm/PprC.hs |4 ++--
  1 files changed, 2 insertions(+), 2 deletions(-)
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7407#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] #7407: error: expected ';' before 'else'

2012-11-16 Thread GHC
#7407: error: expected ';' before 'else'
--+-
  Reporter:  erikd|  Owner:  simonmar
  Type:  bug  | Status:  closed  
  Priority:  highest  |  Milestone:  7.8.1   
 Component:  Compiler |Version:  7.7 
Resolution:  fixed|   Keywords:  
Os:  Linux|   Architecture:  Unknown/Multiple
   Failure:  Building GHC failed  | Difficulty:  Unknown 
  Testcase:   |  Blockedby:  
  Blocking:   |Related:  
--+-
Changes (by simonmar):

  * status:  new = closed
  * resolution:  = fixed


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7407#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] #1409: Allow recursively dependent modules transparently (without .hs-boot or anything)

2012-11-16 Thread GHC
#1409: Allow recursively dependent modules transparently (without .hs-boot or
anything)
-+--
Reporter:  Isaac Dupree  |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  _|_ 
   Component:  Compiler  | Version:  6.10.2  
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by diatchki):

 I also think that having more direct support for mutually recursive
 modules would be nice.   Here is one corner case we encountered when we
 implemented this in Programatica (just documenting it here in case someone
 starts implementing this feature)

 The problem is the specification of defaulting, which talks about a single
 module.  If (i) there is a recursive binding group which happens to be
 spread across modules, and (ii) defaulting needs to happen, then it is not
 clear which module's defaulting rules should be used.

 A simple solution would be to simply report and error in that situation,
 if the modules have different defaulting rules.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1409#comment:58
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] #7158: GHCi commands case insensitive

2012-11-16 Thread GHC
#7158: GHCi commands case insensitive
-+--
Reporter:  Oblosys   |   Owner:  
Type:  feature request   |  Status:  new 
Priority:  normal|   Milestone:  7.8.1   
   Component:  GHCi  | Version:  7.6.1-rc1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by simonmar):

 I vote against, mainly because I have a Unix upbringing and I am allergic
 to case insensitivity.  But if everyone else wants this I don't feel that
 strongly.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7158#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] #7347: Existential data constructors should not be promoted

2012-11-16 Thread GHC
#7347: Existential data constructors should not be promoted
-+--
Reporter:  simonpj   |   Owner:  
Type:  bug   |  Status:  merge   
Priority:  normal|   Milestone:  
   Component:  Compiler  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  polykinds/T7347 
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by goldfire):

 Stephanie and I thought about this issue this morning, and we believe that
 promoting existentials is sound.

 Consider this:
 {{{
 {-# LANGUAGE ExistentialQuantification, PolyKinds, DataKinds #-}
 data Ex = forall a. MkEx a

 type family UnEx (ex :: Ex) :: k
 type instance UnEx (MkEx x) = x
 }}}

 This compiles in GHC 7.6.1, and it should.

 First off, let's look at the type of {{{'MkEx}}}, which is {{{forall
 (k::BOX). k - Ex}}}. Now, let's look at the elaboration of {{{UnEx}}} in
 FC:

 {{{
 UnEx :: forall (k::BOX). Ex - k
 axUnEx :: forall k. forall (x::k). (UnEx k (MkEx k x) ~ x)
 }}}

 So, the elaboration of {{{UnEx}}} simply contains a non-linear pattern in
 {{{k}}}. But, because {{{k}}} is a parameter to {{{UnEx}}}, the kind of
 {{{x}}} is not really escaping. As proof, here is an excerpt of the output
 from {{{-ddump-tc}}}:

 {{{
 TYPE CONSTRUCTORS
   Ex :: *
   data Ex
   No C type associated
   RecFlag NonRecursive
   = MkEx :: forall a. a - Ex Stricts: _
   FamilyInstance: none
   UnEx :: forall (k :: BOX). Ex - k
   type family UnEx (k::BOX) (ex::Ex) :: k
 COERCION AXIOMS
   axiom Scratch.TFCo:R:UnExkMkEx (k :: BOX) (x :: k)
 :: UnEx k ('MkEx k x) ~# x
 }}}

 One comment above says that {{{UnEx}}} would default to a result kind of
 {{{*}}}. This would only happen in the absence of an explicit kind
 signature for the return kind; all un-annotated types involved in a type
 family default to {{{*}}}.

 What's different about the type level is that there is no phase separation
 between kinds and types. Unpacking a type-level existential happens at
 compile time, so the type checker can incorporate what it learns in
 simplifying the call to {{{UnEx}}}.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7347#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] #7379: rangeTest test fails on Windows

2012-11-16 Thread GHC
#7379: rangeTest test fails on Windows
-+--
Reporter:  igloo |   Owner:  
Type:  bug   |  Status:  new 
Priority:  normal|   Milestone:  
   Component:  libraries/random  | Version:  7.6.1   
Keywords:|  Os:  Unknown/Multiple
Architecture:  Unknown/Multiple  | Failure:  None/Unknown
  Difficulty:  Unknown   |Testcase:  
   Blockedby:|Blocking:  
 Related:|  
-+--

Comment(by joeyadams):

 Here are the problematic lines:

 {{{
 checkBounds CWchar (intRange 32)  (approxBounds random trials
 (undefined:: CWchar))
 checkBounds CSigAtomic (intRange 32)  (approxBounds random trials
 (undefined:: CWchar))
 ...
 checkBounds CWchar R (False,-100,100)  (approxBounds (randomR
 (-100,100)) trials (undefined:: CWchar))
 checkBounds CSigAtomic R (False,-100,100)  (approxBounds (randomR
 (-100,100)) trials (undefined:: CWchar))
 }}}

 Also, it says `undefined:: CWchar` for both `CWchar` and `CSigAtomic`.  Is
 this a typo?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7379#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] #7419: hpc markup should accept multiple .mix file search paths

2012-11-16 Thread GHC
#7419: hpc markup should accept multiple .mix file search paths
-+--
Reporter:  ttuegel   |  Owner:  
Type:  feature request   | Status:  patch   
Priority:  normal|  Component:  Compiler
 Version:  7.6.1 |   Keywords:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown  |  Blockedby:  
Blocking:|Related:  
-+--

Comment(by ttuegel):

 The .mix file must not be found in multiple locations: the hpc library
 considers it an error for multiple .mix files to match. This sounds more
 constraining than it actually is, because matching is based on module name
 and a hash; one should only get multiple matches if the same file is
 checked twice.

 (If you do {{{ hpc --hpc-dir=A --hpc-dir=B }}}, hpc will search in the
 order you specified the directories, but it always searches all the
 paths.)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7419#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] #7419: hpc markup should accept multiple .mix file search paths

2012-11-16 Thread GHC
#7419: hpc markup should accept multiple .mix file search paths
-+--
Reporter:  ttuegel   |  Owner:  
Type:  feature request   | Status:  patch   
Priority:  normal|  Component:  Code Coverage   
 Version:  7.6.1 |   Keywords:  
  Os:  Unknown/Multiple  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown  |  Blockedby:  
Blocking:|Related:  
-+--
Changes (by tibbe):

  * component:  Compiler = Code Coverage


Comment:

 Thanks for clarifying. The code looks good to me. Please merge.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7419#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] #7299: threadDelay broken in ghci, Mac OS X

2012-11-16 Thread GHC
#7299: threadDelay broken in ghci, Mac OS X
-+--
Reporter:  tmcdonell |   Owner:  igloo 
Type:  bug   |  Status:  new   
Priority:  highest   |   Milestone:  7.6.2 
   Component:  GHCi  | Version:  7.6.1 
Keywords:|  Os:  MacOS X   
Architecture:  Unknown/Multiple  | Failure:  GHCi crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--
Changes (by igloo):

  * owner:  = igloo


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


[GHC] #7421: Data.List.insert / insertBy do not match the documentation

2012-11-16 Thread GHC
#7421: Data.List.insert / insertBy do not match the documentation
+---
Reporter:  Bart Massey  |  Owner:  
Type:  bug  | Status:  new 
Priority:  normal   |  Component:  libraries/base  
 Version:  7.6.1|   Keywords:  
  Os:  Unknown/Multiple |   Architecture:  Unknown/Multiple
 Failure:  Incorrect result at runtime  |  Blockedby:  
Blocking:   |Related:  
+---
 In Data.List from base 4.6.0.0 (as in every previous version), the
 documentation for insert says The insert function takes an element and a
 list and inserts the element into the list at the last position where it
 is still less than or equal to the next element. However:

  insert 1 [2,3,4,2,3,4]
 [1,2,3,4,2,3,4]

 One could correct the code to match the documentation. However, any
 maximally productive version is likely quite a bit less efficient than the
 current code, and the documented behavior doesn't seem terribly useful.

 Instead, I suggest patching the documentation in the obvious way: The
 insert function takes an element and a list and inserts the element into
 the list at the first position where it is less than or equal to the next
 element.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7421
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] #7415: Add more error code support to GHC.Windows (patch)

2012-11-16 Thread GHC
#7415: Add more error code support to GHC.Windows (patch)
+---
Reporter:  joeyadams|  Owner:  joeyadams   
Type:  feature request  | Status:  new 
Priority:  normal   |  Component:  libraries/base  
 Version:  7.6.1|   Keywords:  
  Os:  Windows  |   Architecture:  Unknown/Multiple
 Failure:  None/Unknown |  Blockedby:  
Blocking:  7353 |Related:  
+---
Changes (by joeyadams):

  * owner:  = joeyadams


-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7415#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] #7299: threadDelay broken in ghci, Mac OS X

2012-11-16 Thread GHC
#7299: threadDelay broken in ghci, Mac OS X
-+--
Reporter:  tmcdonell |   Owner:  igloo 
Type:  bug   |  Status:  new   
Priority:  highest   |   Milestone:  7.6.2 
   Component:  GHCi  | Version:  7.6.1 
Keywords:|  Os:  MacOS X   
Architecture:  Unknown/Multiple  | Failure:  GHCi crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:|Blocking:
 Related:|  
-+--

Comment(by tmcdonell):

 Replying to [comment:3 joeyadams]:
  What happens if you compile with `-threaded` ?  ghci uses the threaded
 RTS.  Compiling with `ghc`, by default, does not use the threaded RTS.
 `threadDelay` follows a much different code path with `-threaded` than
 without.

 Works fine compiled with ghc -threaded, both i386 and x86_64 on 7.6.1.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/7299#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] #7299: threadDelay broken in ghci, Mac OS X

2012-11-16 Thread GHC
#7299: threadDelay broken in ghci, Mac OS X
-+--
Reporter:  tmcdonell |   Owner:  igloo 
Type:  bug   |  Status:  new   
Priority:  highest   |   Milestone:  7.6.2 
   Component:  GHCi  | Version:  7.6.1 
Keywords:|  Os:  MacOS X   
Architecture:  Unknown/Multiple  | Failure:  GHCi crash
  Difficulty:  Unknown   |Testcase:
   Blockedby:  3658  |Blocking:
 Related:|  
-+--
Changes (by igloo):

  * blockedby:  = 3658


Comment:

 I can reproduce this.

 However, it doesn't happen with a dynamic-by-default build.

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


[GHC] #7422: GHC panics while trying to derive Generic for GADT with kind-lifted phantom parameter

2012-11-16 Thread GHC
#7422: GHC panics while trying to derive Generic for GADT with kind-lifted 
phantom
parameter
---+
Reporter:  rpglover64  |  Owner:  
Type:  bug | Status:  new 
Priority:  normal  |  Component:  Compiler
 Version:  7.4.1   |   Keywords:  
  Os:  MacOS X |   Architecture:  x86 
 Failure:  Compile-time crash  |  Blockedby:  
Blocking:  |Related:  
---+
 This may be a duplicate of #5884

 Compiling the attached file gives the following crash:

 {{{
 ghc: panic! (the 'impossible' happened)
   (GHC version 7.4.1 for i386-apple-darwin):
 tcTyVarDetails ( tag{tv ae8} [tv] :: main:Main.ExprTag{tc rdD} )
 }}}

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