Re: [GHC] #1311: newtypes of unboxed types disallowed - documentation bug and/or feature request

2007-04-29 Thread GHC
#1311: newtypes of unboxed types disallowed - documentation bug and/or feature
request
-+--
Reporter:  Isaac Dupree  |Owner: 
Type:  bug   |   Status:  new
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.6.1  
Severity:  normal|   Resolution: 
Keywords:|   Difficulty:  Unknown
  Os:  Unknown   | Testcase: 
Architecture:  Unknown   |  
-+--
Comment (by [EMAIL PROTECTED]):

 I think `newtype FastBool = FastBool Int#` could potentially work. There
 are a bunch of places where the compiler assumes newtypes are lifted but
 that could be fixed. The newtype would have all the limitations of
 unlifted types though. You still couldn't use it in polymorphic functions
 or anything (which might be somewhat surprising to users of your code).
 Probably a better use of time would be to make SpecConstr turn enumeration
 types into `Int#`s, thus eliminating the need for FastBool altogether.

 As a side note, isn't FastBool kind of broken by design? You can't really
 do anything useful with it other than turning it back into a plain old
 Bool. `and#`/`or#` don't make sense as they must be strict in both of
 their arguments (which probably isn't what you want).

 The GADT example can't really work as you can't forall over unboxed
 tyvars. You can't write:

 `unBoo :: forall (a::#) . Boo a -> a`

 as `a` could have a completely different representation depending on how
 it was instantiated. You could probably make it so

 `unBoo :: Boo Int# -> Int#`

 would work but why not just write `BooInt = BooInt Int#` at that point.

 -Brian

-- 
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] #1311: newtypes of unboxed types disallowed - documentation bug and/or feature request

2007-04-29 Thread GHC
#1311: newtypes of unboxed types disallowed - documentation bug and/or feature
request
---+
  Reporter:  Isaac Dupree  |  Owner: 
  Type:  bug   | Status:  new
  Priority:  normal|  Milestone: 
 Component:  Compiler  |Version:  6.6.1  
  Severity:  normal|   Keywords: 
Difficulty:  Unknown   | Os:  Unknown
  Testcase:|   Architecture:  Unknown
---+
Tested in 6.6.1 and today's 6.7 (which claims to be version 6.7.20070418),

 {{{newtype FastBool = FastBool Int#}}}

 doesn't work. However this is not documented in the unboxed-types
 documentation in the User's Guide that lists similar restrictions
 http://www.haskell.org/ghc/docs/latest/html/users_guide/primitives.html

 Similarly (maybe), in phantom type arguments, even in GADTs where kind
 inference could be at work

 {{{data Boo a where Boo :: Int# -> Boo Int#}}}

 doesn't work.

 I tried {{{newtype ( FastBool :: # ) = ...}}} , and {{{data Boo ( a :: # )
 where...}}} , which just confused GHC.

 Is there a reason that coercions of unlifted types shouldn't work, or is
 it just unimplemented?  (inspired by looking at GHC's
 compiler/utils/FastTypes.lhs and thinking that using newtypes instead of
 type synonyms in places like that would improve type-safety)

-- 
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] #1310: confusing error message when trying to give a type-signature to an imported symbol

2007-04-29 Thread GHC
#1310: confusing error message when trying to give a type-signature to an 
imported
symbol
---+
  Reporter:  Isaac Dupree  |  Owner: 
  Type:  bug   | Status:  new
  Priority:  normal|  Milestone: 
 Component:  Compiler  |Version:  6.6.1  
  Severity:  normal|   Keywords: 
Difficulty:  Unknown   | Os:  Unknown
  Testcase:|   Architecture:  Unknown
---+
{{{
 import Prelude(putStrLn,String,IO)
 main = putStrLn "ha" --works fine; putStrLn _is_ in (this) scope
 }}}
 {{{
 putStrLn :: String -> IO () --produces ghc error: Not in scope: `putStrLn'
 }}}
 {{{
 Prelude.putStrLn :: String -> IO () --produces ghc error: Invalid type
 signature
 }}}

 I think an error message more like "type signatures can't be given to
 functions(or non-function data) not defined in the same module" in both
 cases would be clearer.  Not sure what the right phrase is for
 "functions(or non-function data)", "symbols",?

 {{{
 main = putStrLn "ha"
 where p :: String -> IO ()
 p x = putStrLn x
 --produces ghc error: Misplaced type signature: p :: String -> IO ()
 }}}
 which shows a little more understanding in that case... If someone didn't
 understand how that style of type-signature could only appear parallel to
 a definition, I'm not sure how helpful it is.

 {{{
 main = putStrLn "ha"
 where putStrLn :: String -> IO ()
 --produces ghc error for the second line: Not in scope: `putStrLn'
 }}}

-- 
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] #1292: -fwarn-monomorphism-restriction should be -Wmonomorphism-restriction

2007-04-29 Thread GHC
#1292: -fwarn-monomorphism-restriction should be -Wmonomorphism-restriction
-+--
Reporter:  guest |Owner: 
Type:  bug   |   Status:  closed 
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.7
Severity:  normal|   Resolution:  invalid
Keywords:|   Difficulty:  Unknown
  Os:  Unknown   | Testcase: 
Architecture:  Unknown   |  
-+--
Comment (by igloo):

 (Can you please not close bugs without comment or anonymously? Thanks)

 On the name of the flag, `-fwarn` rather than `-W` seems to be the naming
 convention.

 However, on having the warning on by default:

 We've seen a number of failures in the HEAD+extralibs build because of
 this warning,
 e.g. a warning about `index` in the below snippet from regex-compat:
 {{{
 else let index = (read (head bgroups)) - 1
  in
  if index == -1
 then match
 else groups !! index
 }}}
 Here, and I imagine everywhere (non-contrived) that compilation succeeds,
 monomorphism is exactly what we want. As I believe it is a good policy to
 keep code `-Wall` clean, I personally would not like this warning to be
 enabled even by `-Wall`. Debatably it would be good style to add a type
 signature for `index`, though.

 The warning may be useful for people investigating removing or replacing
 the MR, but they can enable it themselves.

 It may also be useful to show any such warnings when compilation fails,
 but that feels like a bit of a hack and may result in a flood of unrelated
 warnings when a single error occurs.

 I've turned the warning off for now, so at least it won't break the
 nightly builds.

-- 
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] #1302: Unwanted output when installing

2007-04-29 Thread GHC
#1302: Unwanted output when installing
-+--
Reporter:  guest |Owner: 
Type:  bug   |   Status:  closed 
Priority:  normal|Milestone: 
   Component:  Compiler  |  Version:  6.7
Severity:  normal|   Resolution:  fixed  
Keywords:|   Difficulty:  Unknown
  Os:  Windows   | Testcase: 
Architecture:  Unknown   |  
-+--
Changes (by igloo):

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

Comment:

 Thanks for the report! Now fixed:
 {{{
 Fri Apr 27 05:26:17 PDT 2007  Simon Marlow <[EMAIL PROTECTED]>
   * add missing @ (see bug #1302)
 }}}

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