[Git][ghc/ghc][master] base: Improve String & IsString documentation

Marge Bot (@marge-bot) gitlab at gitlab.haskell.org
Fri Aug 4 16:24:45 UTC 2023



Marge Bot pushed to branch master at Glasgow Haskell Compiler / GHC


Commits:
d751c583 by Profpatsch at 2023-08-04T12:24:26-04:00
base: Improve String & IsString documentation

- - - - -


2 changed files:

- libraries/base/Data/String.hs
- libraries/base/GHC/Base.hs


Changes:

=====================================
libraries/base/Data/String.hs
=====================================
@@ -37,8 +37,26 @@ import Data.Functor.Const (Const (Const))
 import Data.Functor.Identity (Identity (Identity))
 import Data.List (lines, words, unlines, unwords)
 
--- | Class for string-like datastructures; used by the overloaded string
---   extension (-XOverloadedStrings in GHC).
+-- | `IsString` is used in combination with the @-XOverloadedStrings@
+-- language extension to convert the literals to different string types.
+--
+-- For example, if you use the [text](https://hackage.haskell.org/package/text) package,
+-- you can say
+--
+-- @
+-- {-# LANGUAGE OverloadedStrings  #-}
+--
+-- myText = "hello world" :: Text
+-- @
+--
+-- Internally, the extension will convert this to the equivalent of
+--
+-- @
+-- myText = fromString @Text ("hello world" :: String)
+-- @
+--
+-- __Note:__ You can use @fromString@ in normal code as well,
+-- but the usual performance/memory efficiency problems with 'String' apply.
 class IsString a where
     fromString :: String -> a
 


=====================================
libraries/base/GHC/Base.hs
=====================================
@@ -1617,10 +1617,42 @@ otherwise               =  True
 -- Type Char and String
 ----------------------------------------------
 
--- | A 'String' is a list of characters.  String constants in Haskell are values
--- of type 'String'.
+-- | 'String' is an alias for a list of characters.
 --
--- See "Data.List" for operations on lists.
+-- String constants in Haskell are values of type 'String'.
+-- That means if you write a string literal like @"hello world"@,
+-- it will have the type @[Char]@, which is the same as @String at .
+--
+-- __Note:__ You can ask the compiler to automatically infer different types
+-- with the @-XOverloadedStrings@ language extension, for example
+--  @"hello world" :: Text at . See t'Data.String.IsString' for more information.
+--
+-- Because @String@ is just a list of characters, you can use normal list functions
+-- to do basic string manipulation. See "Data.List" for operations on lists.
+--
+-- === __Performance considerations__
+--
+-- @[Char]@ is a relatively memory-inefficient type.
+-- It is a linked list of boxed word-size characters, internally it looks something like:
+--
+-- > ╭─────┬───┬──╮  ╭─────┬───┬──╮  ╭─────┬───┬──╮  ╭────╮
+-- > │ (:) │   │ ─┼─>│ (:) │   │ ─┼─>│ (:) │   │ ─┼─>│ [] │
+-- > ╰─────┴─┼─┴──╯  ╰─────┴─┼─┴──╯  ╰─────┴─┼─┴──╯  ╰────╯
+-- >         v               v               v
+-- >        'a'             'b'             'c'
+--
+-- The @String@ "abc" will use @5*3+1 = 16@ (in general @5n+1@)
+-- words of space in memory.
+--
+-- Furthermore, operations like '(++)' (string concatenation) are @O(n)@
+-- (in the left argument).
+--
+-- For historical reasons, the @base@ library uses @String@ in a lot of places
+-- for the conceptual simplicity, but library code dealing with user-data
+-- should use the [text](https://hackage.haskell.org/package/text)
+-- package for Unicode text, or the the
+-- [bytestring](https://hackage.haskell.org/package/bytestring) package
+-- for binary data.
 type String = [Char]
 
 unsafeChr :: Int -> Char



View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d751c583d29460f033fefb45e685fa40fb3487ad

-- 
View it on GitLab: https://gitlab.haskell.org/ghc/ghc/-/commit/d751c583d29460f033fefb45e685fa40fb3487ad
You're receiving this email because of your account on gitlab.haskell.org.


-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/ghc-commits/attachments/20230804/9af2b1af/attachment-0001.html>


More information about the ghc-commits mailing list