foundation-0.0.29: Alternative prelude with batteries and no dependencies
License BSD-style
Maintainer Vincent Hanquez <vincent@snarc.org>
Stability experimental
Portability portable
Safe Haskell None
Language Haskell2010

Foundation.String

Description

Opaque packed String encoded in UTF8.

The type is an instance of IsString and IsList, which allow OverloadedStrings for string literal, and fromList to convert a [Char] (Prelude String) to a packed representation

{-# LANGUAGE OverloadedStrings #-}
s = "Hello World" :: String
s = fromList ("Hello World" :: Prelude.String) :: String

Each unicode code point is represented by a variable encoding of 1 to 4 bytes,

For more information about UTF8: https://en.wikipedia.org/wiki/UTF-8

Synopsis

Documentation

data String Source #

Opaque packed array of characters in the UTF8 encoding

Instances

Instances details
IsList String
Instance details

Defined in Basement.UTF8.Base

Associated Types

type Item String Source #

Eq String
Instance details

Defined in Basement.UTF8.Base

Data String
Instance details

Defined in Basement.UTF8.Base

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> String -> c String Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c String Source #

toConstr :: String -> Constr Source #

dataTypeOf :: String -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c String ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c String ) Source #

gmapT :: ( forall b. Data b => b -> b) -> String -> String Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> String -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> String -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> String -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> String -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> String -> m String Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> String -> m String Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> String -> m String Source #

Ord String
Instance details

Defined in Basement.UTF8.Base

Show String
Instance details

Defined in Basement.UTF8.Base

IsString String
Instance details

Defined in Basement.UTF8.Base

Semigroup String
Instance details

Defined in Basement.UTF8.Base

Monoid String
Instance details

Defined in Basement.UTF8.Base

NormalForm String
Instance details

Defined in Basement.UTF8.Base

Copy String Source #
Instance details

Defined in Foundation.Collection.Copy

Collection String Source #
Instance details

Defined in Foundation.Collection.Collection

Buildable String Source #
Instance details

Defined in Foundation.Collection.Buildable

IndexedCollection String Source #
Instance details

Defined in Foundation.Collection.Indexed

InnerFunctor String Source #
Instance details

Defined in Foundation.Collection.InnerFunctor

Sequential String Source #
Instance details

Defined in Foundation.Collection.Sequential

Methods

take :: CountOf ( Element String ) -> String -> String Source #

revTake :: CountOf ( Element String ) -> String -> String Source #

drop :: CountOf ( Element String ) -> String -> String Source #

revDrop :: CountOf ( Element String ) -> String -> String Source #

splitAt :: CountOf ( Element String ) -> String -> ( String , String ) Source #

revSplitAt :: CountOf ( Element String ) -> String -> ( String , String ) Source #

splitOn :: ( Element String -> Bool ) -> String -> [ String ] Source #

break :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

breakEnd :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

breakElem :: Element String -> String -> ( String , String ) Source #

takeWhile :: ( Element String -> Bool ) -> String -> String Source #

dropWhile :: ( Element String -> Bool ) -> String -> String Source #

intersperse :: Element String -> String -> String Source #

intercalate :: Element String -> String -> Element String Source #

span :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

spanEnd :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

filter :: ( Element String -> Bool ) -> String -> String Source #

partition :: ( Element String -> Bool ) -> String -> ( String , String ) Source #

reverse :: String -> String Source #

uncons :: String -> Maybe ( Element String , String ) Source #

unsnoc :: String -> Maybe ( String , Element String ) Source #

snoc :: String -> Element String -> String Source #

cons :: Element String -> String -> String Source #

find :: ( Element String -> Bool ) -> String -> Maybe ( Element String ) Source #

sortBy :: ( Element String -> Element String -> Ordering ) -> String -> String Source #

singleton :: Element String -> String Source #

head :: NonEmpty String -> Element String Source #

last :: NonEmpty String -> Element String Source #

tail :: NonEmpty String -> String Source #

init :: NonEmpty String -> String Source #

replicate :: CountOf ( Element String ) -> Element String -> String Source #

isPrefixOf :: String -> String -> Bool Source #

isSuffixOf :: String -> String -> Bool Source #

isInfixOf :: String -> String -> Bool Source #

stripPrefix :: String -> String -> Maybe String Source #

stripSuffix :: String -> String -> Maybe String Source #

Zippable String Source #
Instance details

Defined in Foundation.Collection.Zippable

ParserSource String Source #
Instance details

Defined in Foundation.Parser

Associated Types

type Chunk String Source #

Arbitrary String Source #
Instance details

Defined in Foundation.Check.Arbitrary

IsField String Source #
Instance details

Defined in Foundation.Format.CSV.Types

Hashable String Source #
Instance details

Defined in Foundation.Hashing.Hashable

Methods

hashMix :: Hasher st => String -> st -> st Source #

From AsciiString String
Instance details

Defined in Basement.From

From String ( UArray Word8 )
Instance details

Defined in Basement.From

Show ( ParseError String ) Source #
Instance details

Defined in Foundation.Parser

TryFrom ( UArray Word8 ) String
Instance details

Defined in Basement.From

IsProperty ( String , Bool ) Source #
Instance details

Defined in Foundation.Check.Property

type Item String
Instance details

Defined in Basement.UTF8.Base

type Element String Source #
Instance details

Defined in Foundation.Collection.Element

type Mutable String Source #
Instance details

Defined in Foundation.Collection.Buildable

type Step String Source #
Instance details

Defined in Foundation.Collection.Buildable

type Chunk String Source #
Instance details

Defined in Foundation.Parser

data Encoding Source #

Various String Encoding that can be use to convert to and from bytes

Instances

Instances details
Bounded Encoding
Instance details

Defined in Basement.String

Enum Encoding
Instance details

Defined in Basement.String

Eq Encoding
Instance details

Defined in Basement.String

Data Encoding
Instance details

Defined in Basement.String

Methods

gfoldl :: ( forall d b. Data d => c (d -> b) -> d -> c b) -> ( forall g. g -> c g) -> Encoding -> c Encoding Source #

gunfold :: ( forall b r. Data b => c (b -> r) -> c r) -> ( forall r. r -> c r) -> Constr -> c Encoding Source #

toConstr :: Encoding -> Constr Source #

dataTypeOf :: Encoding -> DataType Source #

dataCast1 :: Typeable t => ( forall d. Data d => c (t d)) -> Maybe (c Encoding ) Source #

dataCast2 :: Typeable t => ( forall d e. ( Data d, Data e) => c (t d e)) -> Maybe (c Encoding ) Source #

gmapT :: ( forall b. Data b => b -> b) -> Encoding -> Encoding Source #

gmapQl :: (r -> r' -> r) -> r -> ( forall d. Data d => d -> r') -> Encoding -> r Source #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> ( forall d. Data d => d -> r') -> Encoding -> r Source #

gmapQ :: ( forall d. Data d => d -> u) -> Encoding -> [u] Source #

gmapQi :: Int -> ( forall d. Data d => d -> u) -> Encoding -> u Source #

gmapM :: Monad m => ( forall d. Data d => d -> m d) -> Encoding -> m Encoding Source #

gmapMp :: MonadPlus m => ( forall d. Data d => d -> m d) -> Encoding -> m Encoding Source #

gmapMo :: MonadPlus m => ( forall d. Data d => d -> m d) -> Encoding -> m Encoding Source #

Ord Encoding
Instance details

Defined in Basement.String

Show Encoding
Instance details

Defined in Basement.String

fromBytes :: Encoding -> UArray Word8 -> ( String , Maybe ValidationFailure , UArray Word8 ) Source #

Convert a ByteArray to a string assuming a specific encoding.

It returns a 3-tuple of:

  • The string that has been succesfully converted without any error
  • An optional validation error
  • The remaining buffer that hasn't been processed (either as a result of an error, or because the encoded sequence is not fully available)

Considering a stream of data that is fetched chunk by chunk, it's valid to assume that some sequence might fall in a chunk boundary. When converting chunks, if the error is Nothing and the remaining buffer is not empty, then this buffer need to be prepended to the next chunk

fromBytesLenient :: UArray Word8 -> ( String , UArray Word8 ) Source #

Convert a UTF8 array of bytes to a String.

If there's any error in the stream, it will automatically insert replacement bytes to replace invalid sequences.

In the case of sequence that fall in the middle of 2 chunks, the remaining buffer is supposed to be preprended to the next chunk, and resume the parsing.

fromBytesUnsafe :: UArray Word8 -> String Source #

Convert a Byte Array representing UTF8 data directly to a string without checking for UTF8 validity

If the input contains invalid sequences, it will trigger runtime async errors when processing data.

In doubt, use fromBytes

toBytes :: Encoding -> String -> UArray Word8 Source #

Convert a String to a bytearray in a specific encoding

if the encoding is UTF8, the underlying buffer is returned without extra allocation or any processing

In any other encoding, some allocation and processing are done to convert.

lines :: String -> [ String ] Source #

Split lines in a string using newline as separation.

Note that carriage return preceding a newline are also strip for maximum compatibility between Windows and Unix system.

words :: String -> [ String ] Source #

Split words in a string using spaces as separation

words "Hello Foundation"
Hello , Foundation

upper :: String -> String Source #

Convert a String to the upper-case equivalent.

lower :: String -> String Source #

Convert a String to the upper-case equivalent.

replace :: String -> String -> String -> String Source #

Replace all the occurrencies of needle with replacement in the haystack string.

indices :: String -> String -> [ Offset8 ] Source #

Finds where are the insertion points when we search for a needle within an haystack .

toBase64 :: String -> String Source #

Transform string src to base64 binary representation.

toBase64URL :: Bool -> String -> String Source #

Transform string src to URL-safe base64 binary representation. The result will be either padded or unpadded, depending on the boolean padded argument.

toBase64OpenBSD :: String -> String Source #

Transform string src to OpenBSD base64 binary representation.

breakLine :: String -> Either Bool ( String , String ) Source #

Same as break but cut on a line feed with an optional carriage return.

This is the same operation as 'breakElem LF' dropping the last character of the string if it's a CR.

Also for efficiency reason (streaming), it returns if the last character was a CR character.