{-# LANGUAGE Trustworthy #-}
{-# LANGUAGE NoImplicitPrelude, FlexibleInstances #-}
{-# LANGUAGE TypeFamilies #-}

-----------------------------------------------------------------------------
-- |
-- Module      :  Data.String
-- Copyright   :  (c) The University of Glasgow 2007
-- License     :  BSD-style (see the file libraries/base/LICENSE)
--
-- Maintainer  :  libraries@haskell.org
-- Stability   :  experimental
-- Portability :  portable
--
-- The @String@ type and associated operations.
--
-----------------------------------------------------------------------------

module Data.String (
   String
 , IsString(..)

 -- * Functions on strings
 , lines
 , words
 , unlines
 , unwords
 ) where

import GHC.Base
import Data.Functor.Const (Const (Const))
import Data.List (lines, words, unlines, unwords)

-- | Class for string-like datastructures; used by the overloaded string
--   extension (-XOverloadedStrings in GHC).
class IsString a where
    fromString :: String -> a

{- 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
         -- See Note [IsString String]
    fromString xs = xs

instance IsString a => IsString (Const a b) where
    fromString = Const . fromString