[GHC] #2219: GADT match fails to refine type variable

2008-04-14 Thread GHC
#2219: GADT match fails to refine type variable
-+--
Reporter:  dolio |   Owner: 
Type:  bug   |  Status:  new
Priority:  normal|   Component:  Compiler (Type checker)
 Version:  6.9   |Severity:  normal 
Keywords:  gadt type family  |Testcase: 
Architecture:  x86   |  Os:  Linux  
-+--
 The following code is accepted by the type checker in 6.8.2, but is
 rejected by a HEAD build, 6.9.20080411:

 {{{
 {-# LANGUAGE TypeFamilies, GADTs, EmptyDataDecls, TypeOperators #-}

 data Zero
 data Succ a

 data FZ
 data FS fn

 data Fin n fn where
   FZ :: Fin (Succ n) FZ
   FS :: Fin n fn - Fin (Succ n) (FS fn)

 data Nil
 data a ::: b

 type family Lookup ts fn :: *
 type instance Lookup (t ::: ts) FZ = t
 type instance Lookup (t ::: ts) (FS fn) = Lookup ts fn

 data Tuple n ts where
   Nil   :: Tuple Zero Nil
   (:::) :: t - Tuple n ts - Tuple (Succ n) (t ::: ts)

 proj :: Fin n fn - Tuple n ts - Lookup ts fn
 proj FZ  (v ::: _)  = v
 proj (FS fn) (_ ::: vs) = proj fn vs
 }}}

 The error in question is:

 {{{
 Bug.hs:25:16:
 Occurs check: cannot construct the infinite type:
   t = Lookup (t ::: ts) fn
 In the pattern: v ::: _
 In the definition of `proj': proj FZ (v ::: _) = v
 }}}

 Which seems to indicate that the pattern match against {{{FZ}}} in the
 first case is failing to refine the type variable {{{fn}}} to {{{FZ}}}.
 Reversing the order of the cases yields the same error, so either the
 match against FS is working correctly, or the type checker thinks that it
 can solve {{{Lookup (t ::: ts) fn ~ Lookup ts fn}}}.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2219
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] #1886: GHC API should preserve and provide access to comments

2008-04-14 Thread GHC
#1886: GHC API should preserve and provide access to comments
---+
 Reporter:  claus  |  
Owner: 
 Type:  bug| 
Status:  new
 Priority:  normal |  
Milestone:  6.10 branch
Component:  GHC API|
Version:  6.9
 Severity:  normal | 
Resolution: 
 Keywords:  GHC API, comments, program transformation, layout  | 
Difficulty:  Unknown
 Testcase: |   
Architecture:  Unknown
   Os:  Unknown|  
---+
Comment (by claus):

 see also this thread on `cvs-ghc`, messages before and after this one:

 [http://www.haskell.org/pipermail/cvs-ghc/2007-November/039526.html should
 haddock.ghc be a sub-repo of ghc?]

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1886#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] #1886: GHC API should preserve and provide access to comments

2008-04-14 Thread GHC
#1886: GHC API should preserve and provide access to comments
---+
 Reporter:  claus  |  
Owner: 
 Type:  bug| 
Status:  new
 Priority:  normal |  
Milestone:  6.10 branch
Component:  GHC API|
Version:  6.9
 Severity:  normal | 
Resolution: 
 Keywords:  GHC API, comments, program transformation, layout  | 
Difficulty:  Unknown
 Testcase: |   
Architecture:  Unknown
   Os:  Unknown|  
---+
Changes (by j.waldmann):

 * cc: j.waldmann (added)

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1886#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] #2220: Subprocesses do not close open FDs

2008-04-14 Thread GHC
#2220: Subprocesses do not close open FDs
-+--
Reporter:  Baughn|   Owner:
Type:  bug   |  Status:  new   
Priority:  normal|   Component:  Runtime System
 Version:  6.8.2 |Severity:  normal
Keywords:|Testcase:
Architecture:  Multiple  |  Os:  Multiple  
-+--
 When creating a subprocess, for example with runInteractiveProcess, only
 pipes that are created in the process of creating the process are closed
 appropriately; any FDs created elsewhere in the program are ignored. As
 unix pipes are only considered closed once every process that could
 conceivably write to one has closed it, one consequence of this is that
 programs that rely on detecting EOF will be unable to do so. Another is
 that the system may leak FDs over the runtime of the program, conceivably
 running out.

 As an example, this makes it impossible to write a fully functional shell
 with pipes in GHC; in a shell command like main program | cat | cat,
 the second cat may acquire a reference to the pipe used for writing to the
 first one, which will prevent that pipe from ever being considered closed.

 A brute-force solution would be to attempt to close every possible FD when
 creating subprocesses. This is undesirable for several reasons - most
 obviously performance, but also because there are legitimate reasons to
 pass FDs other than stdin/out/err to a subprocess. A more elegant one
 would be for all FDs opened by any means to be marked as close-on-exec on
 creation, and provide a call to clear this bit if transferring it to a
 specific subprocess is desired.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2220
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] #2220: Subprocesses do not close open FDs

2008-04-14 Thread GHC
#2220: Subprocesses do not close open FDs
---+
Reporter:  Baughn  |Owner:  
Type:  bug |   Status:  new 
Priority:  normal  |Milestone:  
   Component:  Runtime System  |  Version:  6.8.2   
Severity:  normal  |   Resolution:  
Keywords:  | Testcase:  
Architecture:  Multiple|   Os:  Multiple
---+
Comment (by Baughn):

 If setting FD_CLOEXEC (close on exec) is picked, then.. since it has to be
 set in a separate call after opening the FD, there is a potential race
 condition if any other thread calls exec. Probably only one OS thread
 should do I/O or forks - my understanding is that this is already the
 case, but it had to be mentioned.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2220#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] #2221: Can't use quotationes ([| ... |]) insides declaration splices

2008-04-14 Thread GHC
#2221: Can't use quotationes ([| ... |]) insides declaration splices
---+
Reporter:  m4dc4p  |   Owner:  
Type:  bug |  Status:  new 
Priority:  normal  |   Component:  Template Haskell
 Version:  6.8.2   |Severity:  normal  
Keywords:  |Testcase:  
Architecture:  x86 |  Os:  Windows 
---+
 Normal Template Haskell allows many levels of splicing and quotations:

 {{{
  runQ [| (const $([|Int|])) |]
 AppE (VarE GHC.Base.const) (LitE (StringL Int))
 }}}

 And TH can parse declarations easily:
 {{{
  runQ [d| type T = Int|]
 [TySynD T [] (ConT GHC.Base.Int)]
 }}}

 But splicing inside a declaration gives a syntax error:

 {{{
  runQ [d| type T = $([t|Int|])|]
 parse error on input `$('
 }}}

 Another example. Bulat Ziganshin defines the cnst function
 (http://www.haskell.org/bz/th3.htm) as:

 {{{
 cnst 0 str = [| str |]
 cnst n str = [| \_ - $(cnst (n-1) str) |]
 }}}

 Which evaluates to a function that takes n arguments and returns the
 string given. It would make sense that a function to define a data
 constructor which takes n arguments could be written similarly:

 {{{
 dataCnst n = [d|data D = D $(dataCnst' n)|]
 dataCnst' n = [t|Int|] ++ dataCnst' (n - 1)
 }}}

 Finally, a function that makes a data type which varies the field type
 based on an argument:

 {{{
 dataVar n = [d|data D = D $(dataVar' n)|]
 dataVar' Int = ''Int
 dataVar' String = ''String
 etc.
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2221
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] #2221: Can't use quotations ([| ... |]) insides declaration splices

2008-04-14 Thread GHC
#2221: Can't use quotations ([| ... |]) insides declaration splices
-+--
Reporter:  m4dc4p|Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Template Haskell  |  Version:  6.8.2  
Severity:  normal|   Resolution: 
Keywords:| Testcase: 
Architecture:  x86   |   Os:  Windows
-+--
Changes (by m4dc4p):

  * summary:  Can't use quotationes ([| ... |]) insides declaration splices
  = Can't use quotations ([| ... |]) insides
  declaration splices

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/2221#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] #1877: Change the meaning of -fextended-default-rules

2008-04-14 Thread GHC
#1877: Change the meaning of -fextended-default-rules
--+-
 Reporter:  simonmar  |  Owner: 
 Type:  task  | Status:  new
 Priority:  normal|  Milestone:  6.10 branch
Component:  GHCi  |Version:  6.8.1  
 Severity:  normal| Resolution: 
 Keywords:| Difficulty:  Easy (1 hr)
 Testcase:|   Architecture:  Unknown
   Os:  Unknown   |  
--+-
Comment (by SamB):

 Replying to [comment:3 igloo]:
  OK, thanks for pointing that out, sorear. It sounds like we need 2 flags
 then: One to control behaviour for code typed at the GHCi prompt, and one
 for the behaviour for code from files. In which case we should leave the
 existing flag with its current meaning and add one to control the
 behaviour for code typed at the GHCi prompt.

 What about the -X flag? We could use that one for source files and
 -fextended-default-rules for GHCi.

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1877#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] #1592: Unexpected boxing in generated code

2008-04-14 Thread GHC
#1592: Unexpected boxing in generated code
--+-
 Reporter:  neil  |  Owner: 
 Type:  bug   | Status:  new
 Priority:  normal|  Milestone:  6.10 branch
Component:  Compiler  |Version:  6.6.1  
 Severity:  minor | Resolution: 
 Keywords:| Difficulty:  Unknown
 Testcase:|   Architecture:  Unknown
   Os:  Unknown   |  
--+-
Comment (by SamB):

 neil, you really need to work on your style ;-). More seriously, maybe
 your compiler should use {{{seq}}} to indicate that it wants things to be
 strict?

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/1592#comment:10
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] #2219: GADT match fails to refine type variable

2008-04-14 Thread GHC
#2219: GADT match fails to refine type variable
+---
Reporter:  dolio|Owner:  chak 
Type:  bug  |   Status:  new  
Priority:  normal   |Milestone:   
   Component:  Compiler (Type checker)  |  Version:  6.9  
Severity:  normal   |   Resolution:   
Keywords:  gadt type family | Testcase:   
Architecture:  x86  |   Os:  Linux
+---
Changes (by chak):

  * owner:  = chak

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