On 26 July 2011 00:12, Simon Peyton-Jones <[email protected]> wrote:
> [Widening to cvs-ghc because others may have opinions]
>
> | > Generally, if you want to put a language extension in a pragma then the
> | > compiler needs to support that extension, or compilation will fail.
> | > There may be some odd exceptions (the main one that comes to mind is
> | > {-# LANGUAGE NoSomeExtensionYouDoNotHave #-}; most of the Safe and
> | > Trustworthy functionality is similar to that, really) but I'm not
> | > convinced that LANGUAGE_MAYBE is the right solution.
> |
> | I understand the concern here but would like to hear from the Simon's
> | before weighing in. Simon's if you could offer you opinions that would
> | be great as I'd like to carry on with the work on making the libraries
> | included with GHC safe.
>
> Simon M is on holiday this week, and I have not been following the discussion
> properly. I believe the question at issue is this.
>
> * "LANGUAGE Foo" means that the module uses language extension Foo, and won't
> compile unless the compiler supports Foo
>
> * But Safe Haskell for the first time is a language *restriction*. You are
> questioning {-# LANGUAGE SafeHaskell #-} (or trustworthy or something)
> because it *reduces* the set of programs accepted, but does not *increase*
> them.
> So an old compiler that knows nothing of SafeHaskell would compile the module
> just fine.
>
> * So you don't want to add lots of {-# LANGUAGE SafeHaskell #-} pragmas that
> would mean
> you couldn't compile the module with an older compiler.
>
> * Ian responded that if you use "import safe" then you are *increasing* the
> language accepted. You didn't respond, except to say that you "don't have
> to use
> import safe". But that is a problem isn't it?
Sometimes. We tried to design Safe Haskell in a way that is
noninvasive as possible. So we believe there should be a lot of cases
where users can simply add the correct pragma to the top of their
source file and require no further modifications. I'm going through
some libraries now and both Cabal and Bytestring for example fit this
model.
In the case where the module author decides they need to use the
'import safe' feature then the advice would be, don't use {-#
LANGUAGE_MAYBE Trustworthy #-} but use {-# LANGUAGE Trustworthy #-}.
Perhaps some would disagree with a language extension being allowed in
both pragmas though.
>
> It occurs to me that restricting the language is a bit like
> "-fwarn-unused-bindings -Werror". That also restricts the language, this
> time to programs that don't have any unused bindings. So another alternative
> would be
>
> {-# OPTIONS_GHC -safe #-}
>
> But again, older GHCs will simply reject such programs with "unknown flag".
> But perhaps un-recognised flags should only be warned about, rather than
> errored about? After all, we could imagine adding lots of cunning flags that
> do extra checks, but older compilers should still compile the module.
>
> So your proposal is
> {-# LANGUAGE_MAYBE SafeHaskell #-}
> where LANGUAGE_MAYBE flags are ignored (albeit with a warning) if
> unrecognised. I kind of like that. Maybe LANGUAGE_RESTRICTION?
>
> I'm a bit reluctant to commit to something before Simon M gets back (in a
> week's time).
>
> Simon
>
_______________________________________________
Cvs-ghc mailing list
[email protected]
http://www.haskell.org/mailman/listinfo/cvs-ghc