base-4.19.1.0: Basic libraries
Copyright(c) The University of Glasgow 2007
LicenseBSD-style (see the file libraries/base/LICENSE)
Maintainerlibraries@haskell.org
Stabilitystable
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.String

Description

The String type and associated operations.

Synopsis

Documentation

type String = [Char] Source #

String is an alias for a list of characters.

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.

Note: You can ask the compiler to automatically infer different types with the -XOverloadedStrings language extension, for example "hello world" :: Text. See 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

Expand

[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 package for Unicode text, or the the bytestring package for binary data.

class IsString a where Source #

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 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.

Methods

fromString :: String -> a Source #

Instances

Instances details
IsString a => IsString (Identity a) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.String

a ~ Char => IsString [a] Source #

(a ~ Char) context was introduced in 4.9.0.0

Since: base-2.1

Instance details

Defined in Data.String

Methods

fromString :: String -> [a] Source #

IsString a => IsString (Const a b) Source #

Since: base-4.9.0.0

Instance details

Defined in Data.String

Methods

fromString :: String -> Const a b Source #

Functions on strings

lines :: String -> [String] Source #

Splits the argument into a list of lines stripped of their terminating \n characters. The \n terminator is optional in a final non-empty line of the argument string.

When the argument string is empty, or ends in a \n character, it can be recovered by passing the result of lines to the unlines function. Otherwise, unlines appends the missing terminating \n. This makes unlines . lines idempotent:

(unlines . lines) . (unlines . lines) = (unlines . lines)

Examples

Expand
>>> lines ""           -- empty input contains no lines
[]
>>> lines "\n"         -- single empty line
[""]
>>> lines "one"        -- single unterminated line
["one"]
>>> lines "one\n"      -- single non-empty line
["one"]
>>> lines "one\n\n"    -- second line is empty
["one",""]
>>> lines "one\ntwo"   -- second line is unterminated
["one","two"]
>>> lines "one\ntwo\n" -- two non-empty lines
["one","two"]

words :: String -> [String] Source #

words breaks a string up into a list of words, which were delimited by white space (as defined by isSpace). This function trims any white spaces at the beginning and at the end.

Examples

Expand
>>> words "Lorem ipsum\ndolor"
["Lorem","ipsum","dolor"]
>>> words " foo bar "
["foo","bar"]

unlines :: [String] -> String Source #

Appends a \n character to each input string, then concatenates the results. Equivalent to foldMap (s -> s ++ "\n").

Examples

Expand
>>> unlines ["Hello", "World", "!"]
"Hello\nWorld\n!\n"

Note that unlines . lines /= id when the input is not \n-terminated:

>>> unlines . lines $ "foo\nbar"
"foo\nbar\n"

unwords :: [String] -> String Source #

unwords joins words with separating spaces (U+0020 SPACE).

unwords is neither left nor right inverse of words:

>>> words (unwords [" "])
[]
>>> unwords (words "foo\nbar")
"foo bar"

Examples

Expand
>>> unwords ["Lorem", "ipsum", "dolor"]
"Lorem ipsum dolor"
>>> unwords ["foo", "bar", "", "baz"]
"foo bar  baz"