Skip to content
Snippets Groups Projects
Commit b501709e authored by Ryan Scott's avatar Ryan Scott
Browse files

Fix Show derivation in the presence of RebindableSyntax/OverloadedStrings

Summary:
To fix this issue, we simply disable `RebindableSyntax` whenever we rename
the code generated from a deriving clause.

Fixes #12688.

Test Plan: make test TEST=T12688

Reviewers: simonpj, austin, bgamari

Reviewed By: simonpj, bgamari

Subscribers: thomie

Differential Revision: https://phabricator.haskell.org/D2591

GHC Trac Issues: #12688
parent e39589e2
No related merge requests found
......@@ -288,11 +288,17 @@ renameDeriv is_boot inst_infos bagBinds
, emptyValBindsOut, usesOnly (plusFVs fvs)) }
| otherwise
= discardWarnings $ -- Discard warnings about unused bindings etc
setXOptM LangExt.EmptyCase $ -- Derived decls (for empty types) can have
-- case x of {}
setXOptM LangExt.ScopedTypeVariables $ -- Derived decls (for newtype-deriving) can
setXOptM LangExt.KindSignatures $ -- used ScopedTypeVariables & KindSignatures
= discardWarnings $
-- Discard warnings about unused bindings etc
setXOptM LangExt.EmptyCase $
-- Derived decls (for empty types) can have
-- case x of {}
setXOptM LangExt.ScopedTypeVariables $
setXOptM LangExt.KindSignatures $
-- Derived decls (for newtype-deriving) can use ScopedTypeVariables &
-- KindSignatures
unsetXOptM LangExt.RebindableSyntax $
-- See Note [Avoid RebindableSyntax when deriving]
do {
-- Bring the extra deriving stuff into scope
-- before renaming the instances themselves
......@@ -362,6 +368,31 @@ dropped patterns have.
Also, this technique carries over the kind substitution from deriveTyData
nicely.
Note [Avoid RebindableSyntax when deriving]
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
The RebindableSyntax extension interacts awkwardly with the derivation of
any stock class whose methods require the use of string literals. The Show
class is a simple example (see Trac #12688):
{-# LANGUAGE RebindableSyntax, OverloadedStrings #-}
newtype Text = Text String
fromString :: String -> Text
fromString = Text
data Foo = Foo deriving Show
This will generate code to the effect of:
instance Show Foo where
showsPrec _ Foo = showString "Foo"
But because RebindableSyntax and OverloadedStrings are enabled, the "Foo"
string literal is now of type Text, not String, which showString doesn't
accept! This causes the generated Show instance to fail to typecheck.
To avoid this kind of scenario, we simply turn off RebindableSyntax entirely
in derived code.
************************************************************************
* *
From HsSyn to DerivSpec
......
......@@ -18,7 +18,7 @@ module TcRnMonad(
setGblEnv, getLclEnv, updLclEnv, setLclEnv,
getEnvs, setEnvs,
xoptM, doptM, goptM, woptM,
setXOptM, unsetGOptM, unsetWOptM,
setXOptM, unsetXOptM, unsetGOptM, unsetWOptM,
whenDOptM, whenGOptM, whenWOptM, whenXOptM,
getGhcMode,
withDoDynamicToo,
......@@ -460,6 +460,10 @@ setXOptM :: LangExt.Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
setXOptM flag =
updTopEnv (\top -> top { hsc_dflags = xopt_set (hsc_dflags top) flag})
unsetXOptM :: LangExt.Extension -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
unsetXOptM flag =
updTopEnv (\top -> top { hsc_dflags = xopt_unset (hsc_dflags top) flag})
unsetGOptM :: GeneralFlag -> TcRnIf gbl lcl a -> TcRnIf gbl lcl a
unsetGOptM flag =
updTopEnv (\top -> top { hsc_dflags = gopt_unset (hsc_dflags top) flag})
......
......@@ -25,6 +25,10 @@ Language
- A bug has been fixed that caused standalone derived ``Ix`` instances to fail
for GADTs with exactly one constructor (:ghc-ticket:`12583`).
- A bug has been fixed that caused derived ``Show`` instances to fail in the
presence of :ghc-flag:`-XRebindableSyntax` and
:ghc-flag:`-XOverloadedStrings` (:ghc-ticket:`12688`).
Compiler
~~~~~~~~
......
......@@ -1460,6 +1460,33 @@ Be warned: this is an experimental facility, with fewer checks than
usual. Use ``-dcore-lint`` to typecheck the desugared program. If Core
Lint is happy you should be all right.
Things unaffected by :ghc-flag:`-XRebindableSyntax`
~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~
:ghc-flag:`-XRebindableSyntax` does not apply to any code generated from a
``deriving`` clause or declaration. To see why, consider the following code: ::
{-# LANGUAGE RebindableSyntax, OverloadedStrings #-}
newtype Text = Text String
fromString :: String -> Text
fromString = Text
data Foo = Foo deriving Show
This will generate code to the effect of: ::
instance Show Foo where
showsPrec _ Foo = showString "Foo"
But because :ghc-flag:`-XRebindableSyntax` and :ghc-flag:`-XOverloadedStrings`
are enabled, the ``"Foo"`` string literal would now be of type ``Text``, not
``String``, which ``showString`` doesn't accept! This causes the generated
``Show`` instance to fail to typecheck. It's hard to imagine any scenario where
it would be desirable have :ghc-flag:`-XRebindableSyntax` behavior within
derived code, so GHC simply ignores :ghc-flag:`-XRebindableSyntax` entirely
when checking derived code.
.. _postfix-operators:
Postfix operators
......
{-# LANGUAGE RebindableSyntax, OverloadedStrings #-}
module T12688 where
import Prelude (String,Show(..))
newtype Text = Text String
fromString :: String -> Text
fromString = Text
x :: Text
x = "x"
newtype Foo = Foo ()
deriving (Show)
......@@ -76,3 +76,4 @@ test('T12245', normal, compile, [''])
test('T12399', normal, compile, [''])
test('T12583', normal, compile, [''])
test('T12616', normal, compile, [''])
test('T12688', normal, compile, [''])
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment