[commit: ghc] master: Modify IsString String instance (fixes #10814) (b225b23)

git at git.haskell.org git at git.haskell.org
Mon Dec 21 11:59:35 UTC 2015


Repository : ssh://git@git.haskell.org/ghc

On branch  : master
Link       : http://ghc.haskell.org/trac/ghc/changeset/b225b234a6b11e42fef433dcd5d2a38bb4b466bf/ghc

>---------------------------------------------------------------

commit b225b234a6b11e42fef433dcd5d2a38bb4b466bf
Author: Dan Doel <dan.doel at gmail.com>
Date:   Mon Dec 21 12:28:16 2015 +0100

    Modify IsString String instance (fixes #10814)
    
    The new instance resolves to `s ~ [Char]` as soon as we know that `s ~
    [a]`, to avoid certain functions (like (++)) causing a situation where
    `a` is ambiguous and (currently) unable to be defaulted.
    
    Reviewers: #core_libraries_committee, hvr, austin, bgamari
    
    Reviewed By: hvr, bgamari
    
    Subscribers: thomie
    
    Differential Revision: https://phabricator.haskell.org/D1572
    
    GHC Trac Issues: #10814


>---------------------------------------------------------------

b225b234a6b11e42fef433dcd5d2a38bb4b466bf
 libraries/base/Data/String.hs                      | 42 +++++++++++++++++++++-
 libraries/base/changelog.md                        | 13 +++----
 .../tests/{ado => overloadedstrings}/Makefile      |  0
 .../should_run}/Makefile                           |  0
 testsuite/tests/overloadedstrings/should_run/all.T |  1 +
 .../should_run/overloadedstringsrun01.hs           |  3 ++
 .../should_run/overloadedstringsrun01.stdout       |  1 +
 7 files changed, 50 insertions(+), 10 deletions(-)

diff --git a/libraries/base/Data/String.hs b/libraries/base/Data/String.hs
index a03569f..df410f0 100644
--- a/libraries/base/Data/String.hs
+++ b/libraries/base/Data/String.hs
@@ -1,5 +1,6 @@
 {-# LANGUAGE Trustworthy #-}
 {-# LANGUAGE NoImplicitPrelude, FlexibleInstances #-}
+{-# LANGUAGE TypeFamilies #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -34,6 +35,45 @@ import Data.List (lines, words, unlines, unwords)
 class IsString a where
     fromString :: String -> a
 
-instance IsString [Char] where
+{-
+Note [IsString String]
+~~~~~~~~~~~~~~~~~~~~~~
+Previously, the IsString instance that covered String was a flexible
+instance for [Char]. This is in some sense the most accurate choice,
+but there are cases where it can lead to an ambiguity, for instance:
+
+  show $ "foo" ++ "bar"
+
+The use of (++) ensures that "foo" and "bar" must have type [t] for
+some t, but a flexible instance for [Char] will _only_ match if
+something further determines t to be Char, and nothing in the above
+example actually does.
+
+So, the above example generates an error about the ambiguity of t,
+and what's worse, the above behavior can be generated by simply
+typing:
+
+   "foo" ++ "bar"
+
+into GHCi with the OverloadedStrings extension enabled.
+
+The new instance fixes this by defining an instance that matches all
+[a], and forces a to be Char. This instance, of course, overlaps
+with things that the [Char] flexible instance doesn't, but this was
+judged to be an acceptable cost, for the gain of providing a less
+confusing experience for people experimenting with overloaded strings.
+
+It may be possible to fix this via (extended) defaulting. Currently,
+the rules are not able to default t to Char in the above example. If
+a more flexible system that enabled this defaulting were put in place,
+then it would probably make sense to revert to the flexible [Char]
+instance, since extended defaulting is enabled in GHCi. However, it
+is not clear at the time of this note exactly what such a system
+would be, and it certainly hasn't been implemented.
+
+A test case (should_run/overloadedstringsrun01.hs) has been added to
+ensure the good behavior of the above example remains in the future.
+-}
+instance (a ~ Char) => IsString [a] where
     fromString xs = xs
 
diff --git a/libraries/base/changelog.md b/libraries/base/changelog.md
index a86a176..82def76 100644
--- a/libraries/base/changelog.md
+++ b/libraries/base/changelog.md
@@ -34,15 +34,7 @@
 
   * New `GHC.Generics.packageName` operation
 
-  * New `GHC.Stack.Types` module now contains the definition of
-    `CallStack` and `SrcLoc`
-
-  * New `GHC.Stack.Types.pushCallStack` function pushes a call-site onto a `CallStack`
-
-  * `GHC.SrcLoc` has been removed
-
-  * `GHC.Stack.showCallStack` and `GHC.SrcLoc.showSrcLoc` are now called
-    `GHC.Stack.prettyCallStack` and `GHC.Stack.prettySrcLoc` respectively
+  * New `GHC.Stack.CallStack` data type
 
   * `Complex` now has `Generic`, `Generic1`, `Functor`, `Foldable`, `Traversable`,
     `Applicative`, and `Monad` instances
@@ -109,6 +101,9 @@
   * Redesign `GHC.Generics` to use type-level literals to represent the
     metadata of generic representation types (#9766)
 
+  * The `IsString` instance for `[Char]` has been modified to eliminate
+    ambiguity arising from overloaded strings and functions like `(++)`.
+
 ## 4.8.2.0  *Oct 2015*
 
   * Bundled with GHC 7.10.3
diff --git a/testsuite/tests/ado/Makefile b/testsuite/tests/overloadedstrings/Makefile
similarity index 100%
copy from testsuite/tests/ado/Makefile
copy to testsuite/tests/overloadedstrings/Makefile
diff --git a/testsuite/tests/annotations/should_compile/Makefile b/testsuite/tests/overloadedstrings/should_run/Makefile
similarity index 100%
copy from testsuite/tests/annotations/should_compile/Makefile
copy to testsuite/tests/overloadedstrings/should_run/Makefile
diff --git a/testsuite/tests/overloadedstrings/should_run/all.T b/testsuite/tests/overloadedstrings/should_run/all.T
new file mode 100644
index 0000000..8248302
--- /dev/null
+++ b/testsuite/tests/overloadedstrings/should_run/all.T
@@ -0,0 +1 @@
+test('overloadedstringsrun01', normal, compile_and_run, [''])
diff --git a/testsuite/tests/overloadedstrings/should_run/overloadedstringsrun01.hs b/testsuite/tests/overloadedstrings/should_run/overloadedstringsrun01.hs
new file mode 100644
index 0000000..87b4303
--- /dev/null
+++ b/testsuite/tests/overloadedstrings/should_run/overloadedstringsrun01.hs
@@ -0,0 +1,3 @@
+{-# LANGUAGE OverloadedStrings #-}
+
+main = print $ "hello" ++ " world."
diff --git a/testsuite/tests/overloadedstrings/should_run/overloadedstringsrun01.stdout b/testsuite/tests/overloadedstrings/should_run/overloadedstringsrun01.stdout
new file mode 100644
index 0000000..ff3e71d
--- /dev/null
+++ b/testsuite/tests/overloadedstrings/should_run/overloadedstringsrun01.stdout
@@ -0,0 +1 @@
+"hello world."



More information about the ghc-commits mailing list