Re: suggestion: add a .ehs file type

2007-11-28 Thread Wolfgang Jeltsch
Am Dienstag, 27. November 2007 19:21 schrieb Alex Jacobson:
 Simon, I think we've been trying to be too clever...

 The simple question is: for a given extension, what is the risk of
 leaving it turned on by default?

The risk is that one thinks that one’s program is Haskell-98-compliant while 
it isn’t.  Or that it is compatible with another compiler while it isn’t.

 […]

Best wishes,
Wolfgang
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Top-level bindings for unlifted types

2007-11-28 Thread pepe

So what's the verdict w.r.t. unlifted things bound by the debugger?
Right now it's quite easy, for example:


Prelude :m +Data.IORef
Prelude Data.IORef p - newIORef False
Prelude Data.IORef :p p
p = GHC.IOBase.IORef (GHC.STRef.STRef (_t1::GHC.Prim.MutVar#  
GHC.Prim.RealWorld Bool))

Prelude Data.IORef :t _t1
_t1 :: GHC.Prim.MutVar# GHC.Prim.RealWorld Bool




Should we actively prevent this ?


On 13/11/2007, at 13:08, Simon Marlow wrote:


Neil Mitchell wrote:


The following program:
---
{-# OPTIONS_GHC -fglasgow-exts #-}
module Test() where
import GHC.Base
test = realWorld#
-
gives the error message:
   Top-level bindings for unlifted types aren't allowed:
   { test = realWorld# }
Changing to test _ = realWorld# works fine.
The question is why are these bindings disallowed? Reading the
Unboxed values as first class citizens paper I can't see it listed
as a restriction.


Let's consider unboxed values first.  They would have to be computed  
at compile-time, and that means the value of every top-level  
unlifted value needs to be visible in the interface file, for use in  
other modules. Cycles are disallowed, of course.  Top-level unboxed  
values would then behave just like #define constants, in fact.  This  
is certainly possible, it would just add complexity to the compiler  
in various places.


Alternatively you could compute them at load-time, but then you'd  
not only have to arrange to run the initialisers somehow, but also  
worry about ordering and cycles.  And then there's the issue that a  
top-level unboxed value would be represented by a pointer to the  
value rather than the value itself, as is the case with normal  
unboxed bindings.  This doesn't sound like a profitable direction.


Top-level unlifted/boxed values would be useful, for example

 x = case newMutVar# 0 realWorld# of (# s#, x# #) - x#

eliminating a layer of indirection compared to the usual  
unsafePerformIO.newIORef.  These would also have to be computed at  
either compile-time or load-time, but there's no difficulty with the  
representation, because unlifted/boxed values are always represented  
by pointers anyway.  This is related to static arrays, which we  
don't have in GHC right now.  Conclusion: doable, but non-trivial.


realWorld# is a special case, but really falls into the unboxed  
category.


Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: Top-level bindings for unlifted types

2007-11-28 Thread Simon Marlow

pepe wrote:

So what's the verdict w.r.t. unlifted things bound by the debugger?
Right now it's quite easy, for example:


Prelude :m +Data.IORef
Prelude Data.IORef p - newIORef False
Prelude Data.IORef :p p
p = GHC.IOBase.IORef (GHC.STRef.STRef (_t1::GHC.Prim.MutVar# 
GHC.Prim.RealWorld Bool))

Prelude Data.IORef :t _t1
_t1 :: GHC.Prim.MutVar# GHC.Prim.RealWorld Bool



Should we actively prevent this ?


My guess is probably, but I can't off-hand think of where the assumption 
that bindings are lifted is wired in.  It's certainly safer to disallow them.


Cheers,
Simon




On 13/11/2007, at 13:08, Simon Marlow wrote:


Neil Mitchell wrote:


The following program:
---
{-# OPTIONS_GHC -fglasgow-exts #-}
module Test() where
import GHC.Base
test = realWorld#
-
gives the error message:
   Top-level bindings for unlifted types aren't allowed:
   { test = realWorld# }
Changing to test _ = realWorld# works fine.
The question is why are these bindings disallowed? Reading the
Unboxed values as first class citizens paper I can't see it listed
as a restriction.


Let's consider unboxed values first.  They would have to be computed 
at compile-time, and that means the value of every top-level unlifted 
value needs to be visible in the interface file, for use in other 
modules. Cycles are disallowed, of course.  Top-level unboxed values 
would then behave just like #define constants, in fact.  This is 
certainly possible, it would just add complexity to the compiler in 
various places.


Alternatively you could compute them at load-time, but then you'd not 
only have to arrange to run the initialisers somehow, but also worry 
about ordering and cycles.  And then there's the issue that a 
top-level unboxed value would be represented by a pointer to the value 
rather than the value itself, as is the case with normal unboxed 
bindings.  This doesn't sound like a profitable direction.


Top-level unlifted/boxed values would be useful, for example

 x = case newMutVar# 0 realWorld# of (# s#, x# #) - x#

eliminating a layer of indirection compared to the usual 
unsafePerformIO.newIORef.  These would also have to be computed at 
either compile-time or load-time, but there's no difficulty with the 
representation, because unlifted/boxed values are always represented 
by pointers anyway.  This is related to static arrays, which we don't 
have in GHC right now.  Conclusion: doable, but non-trivial.


realWorld# is a special case, but really falls into the unboxed category.

Cheers,
Simon
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users





___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


GHC's CPP and Cabal's unlit

2007-11-28 Thread Alistair Bayley
I'm doing some testing with GHC 6.6.1 and Cabal 1.3, and I'm trying to
figure out what happens with CPP and Cabal's unlit.

I start with file Test.lhs:

 {-# OPTIONS -fglasgow-exts #-}
 module Test where
 main = putStrLn hello CPP

and run command:
  ghc -E -x hs -cpp Test.lhs -o Test2.lhs

which gives me Test2.lhs:

{-# LINE 1 Test.lhs #-}
# 1 Test.lhs
# 1 built-in
# 1 command line
# 1 Test.lhs
 {-# OPTIONS -fglasgow-exts #-}
 module Test where
 main = putStrLn hello CPP


So I'm wondering: where does the {-# LINE #-} comment come from, and
also the # 1 lines? AFAICT the # 1 lines are ignored by GHC; I can
compile Test2.lhs without errors. Is there anything in GHC's docs
about this?

More puzzling is that the files that Cabal runs through ghc's CPP
don't get the # n lines, so we end up with something like this:

{-# LINE 1 Test.lhs #-}
 {-# OPTIONS -fglasgow-exts #-}
 module Test where
 main = putStrLn hello CPP

which is not a valid .lhs file, because we have a code line next to a comment.

I also note in Cabal the haddock command runs CPP before unlit. GHC
does it the other way around i.e. run unlit first then CPP, and I'm
wondering if Cabal shouldn't do the same thing?

Thanks,
Alistair
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: suggestion: add a .ehs file type

2007-11-28 Thread Simon Marlow

I see, all you're saying is you'd like the default to be different.

(That's not the same as saying Extensions that change syntax are 
effectively declared by the use of that syntax, which is what you said 
earlier, BTW.)


Well, we could change the default.  I don't think it's a great idea 
personally - I think we should default to compiling whatever is the most 
recent standard, i.e. Haskell 98.  But you're arguing that the proportion 
of Haskell 98 code that would fail to compile is relatively small; that 
might well be true.  This isn't a decision we could take lightly, though.


Furthermore, it's only something we could change in 6.10, by which time it 
is likely that we'll have a clearer idea of what Haskell' is, so there 
might well be a -fhaskell-prime flag (or it might even be the default).


Cheers,
Simon

Alex Jacobson wrote:


Simon, I think we've been trying to be too clever...

The simple question is: for a given extension, what is the risk of 
leaving it turned on by default?


Clearly we don't want extensions turned on that causes code to compile 
but with a different meaning.  We may not want extensions turned on that 
cause most reasonable code not to compile.


But I would say neither risk is significant in the case of most 
extensions.  To use your examples:


* FFI doesn't not cause h98 code to compile to a different meaning.  The 
worst case is that code that uses 'foreign' as a function name doesn't 
compile.  That seems okay in that more code probably uses FFI than uses 
foreign as a function name and the user can apply a language pragma to 
turn it off if really desired.


* Existential types won't cause h98 code to compile with a different 
meaning.  The worst case is that code that uses 'forall' as a type 
variable won't compile.  That seems ok


* TemplateHaskell also not compatible with h98.  The worst case is the 
loss [d| in list comprehensions.


* MagicHash: Does not appear in the ToC or the Index of the user's guide 
so should probably be turned off.  I have no idea what it does.


Note, in all cases where the extension is turned on by default, there 
should be a language pragma to turn it off.



-Alex-

Simon Marlow wrote:

Alex Jacobson wrote:


Simon, from what I can tell, with GHC 6.8.1, use of foreign as a 
function name or forall as a type variable or leaving out a space in 
a list-comprehension doesn't parse differently when the relevant 
extensions are enabled, it causes a parse error.

 
Extensions allow the same code to parse but with different meanings 
need to be declared explicitly.  But, extensions that are obvious 
from syntax should be allowed to be declared simply from the use of 
that syntax.


So for the first example I gave,

f x y = x 3# y

the MagicHash extension is one that you'd require to be explicitly 
declared, because the expression parses both with and without the 
extension.


Now, Let's take the Template Haskell example:

f x = [d|d-xs]

So this is valid Haskell 98, but invalid H98+TH.  You would therefore 
like this example to parse unambiguously as H98, correct?  But in 
order to do that, our parser would need arbitrary lookahead: it can't 
tell whether the expression is legal H98+TH until it gets to the '-' 
in this case. Certainly it's possible to implement this using a 
backtracking parser, but Haskell is supposed to be parsable with a 
shift-reduce parser such as the one GHC uses.  Or we could try parsing 
the whole module with various combinations of extensions turned on or 
off, but I'm sure you can see the problems with that.


So basically the problem is that you need a parser that parses a 
strict superset of Haskell98 - and that's hard to achieve.


Cheers,
Simon


I am not taking a position here on the merits of any extensions.

-Alex-


Simon Marlow wrote:

Alex Jacobson wrote:

Extensions that change syntax are effectively declared by the use 
of that syntax.  If you can parse the source, then you know which 
extensions it uses.


I thought we'd already established that this isn't possible.  Here 
are some code fragments that parse differently depending on which 
extensions are enabled:


f x y = x 3# y

f x = [d|d-xs]

foreign x = x

f :: forall - forall - forall

You could argue that these syntax extensions are therefore badly 
designed, but that's a separate discussion.


Cheers,
Simon


-Alex-


Duncan Coutts wrote:

On Fri, 2007-11-23 at 16:26 +0100, Wolfgang Jeltsch wrote:

Am Freitag, 23. November 2007 03:37 schrieben Sie:

On Fri, 2007-11-23 at 01:50 +0100, Wolfgang Jeltsch wrote:
Dont’t just think in terms of single modules.  If I have a 
Cabal package,
I can declare used extensions in the Cabal file.  A user can 
decide not

to start building at all if he/she sees that the package uses an
extension unsupported by the compiler.
Indeed. In theory Cabal checks all the extensions declared to be 
used by
the package are supported by the selected compiler. In practise 
I'm not

sure how well it does 

ghc vs ghci: why can't ghci do everything ghc can do?

2007-11-28 Thread Claus Reinke
1) is there a single place/wiki/ticket that collects all the 
   deficiencies of ghci, compared to ghc? things like:


   a) which platforms have ghc, but not ghci
   b) which features are available in ghc, but not in ghci
   c) does ghci encounter bugs where ghc would succeed
   d) which of these deficiencies are temporary, which
   are likely to stay

2) given that ghci is ghc --interactive, why are there
   any cases of b/c above at all? 


   wouldn't it be possible for ghci to try its stuff, but
   to fall back to ghc only for those modules which
   it can't handle from source itself (yet)?

   - we can do ghc --make; ghci, to get around issues
   - we can do ghci -fforce-recomp, to get to sources

   but those two are rather coarse-grained, and require
   too much manual tweaking to get the effect of creating
   a ghci session with as many modules from source as 
   possible, and all others from object files.


3) suggestions:

   a) could we have a :make command in ghci that does 
   a 'ghc --make' while reusing the information from 
   the current session?


   b) could we have a --prefer-source option for ghci,
   so that 'ghc --make; ghci --prefer-source' will
   try to load all modules from source, but will fall 
   back to the existing object files if necessary

   (instead of failing, as -fforce-recomp does)?

   c) allow selective switching between source and
   object files loaded into ghci (:prefer source M,N,..;
   :prefer object O,P,Q,..).

the application i have in mind is trying to use ghci on
non-trivial projects, such as darcs, or even ghc itself:

- it isn't possible to load all sources into ghci
- loading all object files is possible, but prevents
   use of ghci features such as ':m *Module',
   ':browse *Module', breakpoints, tags, ..
- ghci -fforce-recomp fails because it applies to all 
   modules

- there is substantial setup to do before one can
   call ghc or ghci, so dropping out of a session 
   and trying to figure out dependencies and flags

   for compiling individual modules by hand isn't
   practical
- there is often a configurable makefile, so that 
   one can use the same setup for calling either

   'ghc --make' or 'ghc --interactive'; but, within
   the latter, one cannot simply switch to full 
   :make or to selective --prefer-source, without 
   losing the setup


ideally, ghci would simply work whereever ghc
works, and would provide its additional features
for as many modules as it can. but in the interim, 
having 3a and especially 3b would help me a lot. 
3c would also be nice, too, but not as urgent as 3b.


i find it sad that, currently, there is this gap that 
doesn't allow me to make full use of ghci's features 
for larger projects such as darcs or ghc.


is hoping for 3b realistic?

claus



___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users


Re: suggestion: add a .ehs file type

2007-11-28 Thread Alex Jacobson
My original point (refined) was that I'd like a file extension (.ehs) 
that defaults to including all extensions that don't change the meaning 
of a .hs program but that may cause a small subset of them not to 
compile (e.g. ones that use forall as a type variable, foreign as a 
function, or 'd' as the result value of a list comprehension)


This does not seem like a major change, does not break any existing 
code, and has the advantage of making it really obvious when people are 
going beyond haskell98.


-Alex-

Simon Marlow wrote:

I see, all you're saying is you'd like the default to be different.

(That's not the same as saying Extensions that change syntax are 
effectively declared by the use of that syntax, which is what you said 
earlier, BTW.)


Well, we could change the default.  I don't think it's a great idea 
personally - I think we should default to compiling whatever is the most 
recent standard, i.e. Haskell 98.  But you're arguing that the 
proportion of Haskell 98 code that would fail to compile is relatively 
small; that might well be true.  This isn't a decision we could take 
lightly, though.


Furthermore, it's only something we could change in 6.10, by which time 
it is likely that we'll have a clearer idea of what Haskell' is, so 
there might well be a -fhaskell-prime flag (or it might even be the 
default).


Cheers,
Simon

Alex Jacobson wrote:


Simon, I think we've been trying to be too clever...

The simple question is: for a given extension, what is the risk of 
leaving it turned on by default?


Clearly we don't want extensions turned on that causes code to compile 
but with a different meaning.  We may not want extensions turned on 
that cause most reasonable code not to compile.


But I would say neither risk is significant in the case of most 
extensions.  To use your examples:


* FFI doesn't not cause h98 code to compile to a different meaning.  
The worst case is that code that uses 'foreign' as a function name 
doesn't compile.  That seems okay in that more code probably uses FFI 
than uses foreign as a function name and the user can apply a language 
pragma to turn it off if really desired.


* Existential types won't cause h98 code to compile with a different 
meaning.  The worst case is that code that uses 'forall' as a type 
variable won't compile.  That seems ok


* TemplateHaskell also not compatible with h98.  The worst case is the 
loss [d| in list comprehensions.


* MagicHash: Does not appear in the ToC or the Index of the user's 
guide so should probably be turned off.  I have no idea what it does.


Note, in all cases where the extension is turned on by default, there 
should be a language pragma to turn it off.



-Alex-

Simon Marlow wrote:

Alex Jacobson wrote:


Simon, from what I can tell, with GHC 6.8.1, use of foreign as a 
function name or forall as a type variable or leaving out a space in 
a list-comprehension doesn't parse differently when the relevant 
extensions are enabled, it causes a parse error.

 
Extensions allow the same code to parse but with different meanings 
need to be declared explicitly.  But, extensions that are obvious 
from syntax should be allowed to be declared simply from the use of 
that syntax.


So for the first example I gave,

f x y = x 3# y

the MagicHash extension is one that you'd require to be explicitly 
declared, because the expression parses both with and without the 
extension.


Now, Let's take the Template Haskell example:

f x = [d|d-xs]

So this is valid Haskell 98, but invalid H98+TH.  You would therefore 
like this example to parse unambiguously as H98, correct?  But in 
order to do that, our parser would need arbitrary lookahead: it can't 
tell whether the expression is legal H98+TH until it gets to the '-' 
in this case. Certainly it's possible to implement this using a 
backtracking parser, but Haskell is supposed to be parsable with a 
shift-reduce parser such as the one GHC uses.  Or we could try 
parsing the whole module with various combinations of extensions 
turned on or off, but I'm sure you can see the problems with that.


So basically the problem is that you need a parser that parses a 
strict superset of Haskell98 - and that's hard to achieve.


Cheers,
Simon


I am not taking a position here on the merits of any extensions.

-Alex-


Simon Marlow wrote:

Alex Jacobson wrote:

Extensions that change syntax are effectively declared by the use 
of that syntax.  If you can parse the source, then you know which 
extensions it uses.


I thought we'd already established that this isn't possible.  Here 
are some code fragments that parse differently depending on which 
extensions are enabled:


f x y = x 3# y

f x = [d|d-xs]

foreign x = x

f :: forall - forall - forall

You could argue that these syntax extensions are therefore badly 
designed, but that's a separate discussion.


Cheers,
Simon


-Alex-


Duncan Coutts wrote:

On Fri, 2007-11-23 at 16:26 +0100, Wolfgang Jeltsch 

Re: suggestion: add a .ehs file type

2007-11-28 Thread Alex Young

Alex Jacobson wrote:
My original point (refined) was that I'd like a file extension (.ehs) 
that defaults to including all extensions that don't change the meaning 
of a .hs program but that may cause a small subset of them not to 
compile (e.g. ones that use forall as a type variable, foreign as a 
function, or 'd' as the result value of a list comprehension)


This does not seem like a major change, does not break any existing 
code, and has the advantage of making it really obvious when people are 
going beyond haskell98.




It'll break all sorts of things when .ehs has to get merged into .hs the
next time this conversation comes around, unless it's guaranteed that
all .hs processors will eventually be upgraded to cope with .ehs
semantics.  I don't think anyone's arguing for that...

--
Alex


-Alex-

Simon Marlow wrote:

I see, all you're saying is you'd like the default to be different.

(That's not the same as saying Extensions that change syntax are 
effectively declared by the use of that syntax, which is what you 
said earlier, BTW.)


Well, we could change the default.  I don't think it's a great idea 
personally - I think we should default to compiling whatever is the 
most recent standard, i.e. Haskell 98.  But you're arguing that the 
proportion of Haskell 98 code that would fail to compile is relatively 
small; that might well be true.  This isn't a decision we could take 
lightly, though.


Furthermore, it's only something we could change in 6.10, by which 
time it is likely that we'll have a clearer idea of what Haskell' is, 
so there might well be a -fhaskell-prime flag (or it might even be the 
default).


Cheers,
Simon

Alex Jacobson wrote:


Simon, I think we've been trying to be too clever...

The simple question is: for a given extension, what is the risk of 
leaving it turned on by default?


Clearly we don't want extensions turned on that causes code to 
compile but with a different meaning.  We may not want extensions 
turned on that cause most reasonable code not to compile.


But I would say neither risk is significant in the case of most 
extensions.  To use your examples:


* FFI doesn't not cause h98 code to compile to a different meaning.  
The worst case is that code that uses 'foreign' as a function name 
doesn't compile.  That seems okay in that more code probably uses FFI 
than uses foreign as a function name and the user can apply a 
language pragma to turn it off if really desired.


* Existential types won't cause h98 code to compile with a different 
meaning.  The worst case is that code that uses 'forall' as a type 
variable won't compile.  That seems ok


* TemplateHaskell also not compatible with h98.  The worst case is 
the loss [d| in list comprehensions.


* MagicHash: Does not appear in the ToC or the Index of the user's 
guide so should probably be turned off.  I have no idea what it does.


Note, in all cases where the extension is turned on by default, there 
should be a language pragma to turn it off.



-Alex-

Simon Marlow wrote:

Alex Jacobson wrote:


Simon, from what I can tell, with GHC 6.8.1, use of foreign as a 
function name or forall as a type variable or leaving out a space 
in a list-comprehension doesn't parse differently when the 
relevant extensions are enabled, it causes a parse error.

 
Extensions allow the same code to parse but with different meanings 
need to be declared explicitly.  But, extensions that are obvious 
from syntax should be allowed to be declared simply from the use of 
that syntax.


So for the first example I gave,

f x y = x 3# y

the MagicHash extension is one that you'd require to be explicitly 
declared, because the expression parses both with and without the 
extension.


Now, Let's take the Template Haskell example:

f x = [d|d-xs]

So this is valid Haskell 98, but invalid H98+TH.  You would 
therefore like this example to parse unambiguously as H98, correct?  
But in order to do that, our parser would need arbitrary lookahead: 
it can't tell whether the expression is legal H98+TH until it gets 
to the '-' in this case. Certainly it's possible to implement this 
using a backtracking parser, but Haskell is supposed to be parsable 
with a shift-reduce parser such as the one GHC uses.  Or we could 
try parsing the whole module with various combinations of extensions 
turned on or off, but I'm sure you can see the problems with that.


So basically the problem is that you need a parser that parses a 
strict superset of Haskell98 - and that's hard to achieve.


Cheers,
Simon


I am not taking a position here on the merits of any extensions.

-Alex-


Simon Marlow wrote:

Alex Jacobson wrote:

Extensions that change syntax are effectively declared by the use 
of that syntax.  If you can parse the source, then you know which 
extensions it uses.


I thought we'd already established that this isn't possible.  Here 
are some code fragments that parse differently depending on which 
extensions are enabled:



Re: GHC's CPP and Cabal's unlit

2007-11-28 Thread Alistair Bayley
 More puzzling is that the files that Cabal runs through ghc's CPP
 don't get the # n lines, so we end up with something like this:

(Answering my own message)

Having done some more testing with ghc-6.8.1 and ghc-6.6.1 and cabal's
1.1.6.2 and 1.3, I've realised that the cpp optP-P option in Cabal-1.3
is suppressing the # n lines, so that means the {-# LINE 1 Test.lhs
#-} comment does indeed end up immediately preceding the first real
line of the program (thus causing unlit to spit the dummy).

I've also noticed that the options passed from cabal-1.1.6.2 to the
ghc cpp phase do NOT include -x hs, so ghc unlits the file before
cabal then tries to unlit it. Surely this cannot work, and indeed it
does not, because the resulting .hs file contains no code.

I'm of a mind to fix two things in cabal:
 - the haddock command runs unlit first, THEN cpp
 - the unlit module preserves comments, for the benefit of haddock

I already have these done in my local Cabal-1.3, so creating patches
ought to be straightforward. I've only tested with ghc on Windows
though.

Comments?

Thanks,
Alistair
___
Glasgow-haskell-users mailing list
Glasgow-haskell-users@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users