IsString [Char] instance

Herbert Valerio Riedel hvr at gnu.org
Mon May 18 10:27:43 UTC 2015


On 2015-05-18 at 11:29:25 +0200, Simon Peyton Jones wrote:
> Have you tested this?  If GHC sees two overlapping instances
>                instance ... => IsString [a]
>                instance IsString [Char]
> it’ll refrain from using the former until it knows that the latter
>                can’t match.

FWIW, the original stated problem of having GHC be able to infer

  "hi" ++ "bye"

under the influence of -XOverloadedStrings which would cause GHC to
complain

  λ:2> "foo" ++ "bar"
  <interactive>:2:1:
      Non type-variable argument in the constraint: Data.String.IsString [a]
      (Use FlexibleContexts to permit this)
      When checking that ‘it’ has the inferred type
        it :: forall a. Data.String.IsString [a] => [a]

is actually resolved by the following patch (which I tried w/ GHC HEAD):

--8<---------------cut here---------------start------------->8---
diff --git a/libraries/base/Data/String.hs b/libraries/base/Data/String.hs
index a03569f..2bed477 100644
--- a/libraries/base/Data/String.hs
+++ b/libraries/base/Data/String.hs
@@ -1,5 +1,5 @@
 {-# LANGUAGE Trustworthy #-}
-{-# LANGUAGE NoImplicitPrelude, FlexibleInstances #-}
+{-# LANGUAGE NoImplicitPrelude, GADTs #-}
 
 -----------------------------------------------------------------------------
 -- |
@@ -34,6 +34,6 @@ import Data.List (lines, words, unlines, unwords)
 class IsString a where
     fromString :: String -> a
 
-instance IsString [Char] where
+instance (a ~ Char) => IsString [a] where
     fromString xs = xs
--8<---------------cut here---------------end--------------->8---




More information about the Libraries mailing list