foundation-0.0.6: Alternative prelude with batteries and no dependencies

LicenseBSD-style
MaintainerVincent Hanquez <vincent@snarc.org>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

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

IsList String Source # 

Associated Types

type Item String :: * #

Eq String Source # 

Methods

(==) :: String -> String -> Bool #

(/=) :: String -> String -> Bool #

Data String Source # 

Methods

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

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

toConstr :: String -> Constr #

dataTypeOf :: String -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord String Source # 
Show String Source # 
IsString String Source # 

Methods

fromString :: String -> String #

Monoid String Source # 
Copy String Source # 

Methods

copy :: String -> String Source #

Buildable String Source # 

Associated Types

type Mutable String :: * -> * Source #

type Step String :: * Source #

Collection String Source # 
IndexedCollection String Source # 
InnerFunctor String Source # 
Sequential String Source # 

Methods

take :: Int -> String -> String Source #

revTake :: Int -> String -> String Source #

drop :: Int -> String -> String Source #

revDrop :: Int -> String -> String Source #

splitAt :: Int -> String -> (String, String) Source #

revSplitAt :: Int -> String -> (String, String) Source #

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

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

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

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

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

span :: (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 #

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

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

Zippable String Source # 

Methods

zipWith :: (Sequential a, Sequential b) => (Element a -> Element b -> Element String) -> a -> b -> String Source #

zipWith3 :: (Sequential a, Sequential b, Sequential c) => (Element a -> Element b -> Element c -> Element String) -> a -> b -> c -> String Source #

zipWith4 :: (Sequential a, Sequential b, Sequential c, Sequential d) => (Element a -> Element b -> Element c -> Element d -> Element String) -> a -> b -> c -> d -> String Source #

zipWith5 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element String) -> a -> b -> c -> d -> e -> String Source #

zipWith6 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element String) -> a -> b -> c -> d -> e -> f -> String Source #

zipWith7 :: (Sequential a, Sequential b, Sequential c, Sequential d, Sequential e, Sequential f, Sequential g) => (Element a -> Element b -> Element c -> Element d -> Element e -> Element f -> Element g -> Element String) -> a -> b -> c -> d -> e -> f -> g -> String Source #

Hashable String Source # 

Methods

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

Arbitrary String Source # 
type Item String Source # 
type Element String Source # 
type Mutable String Source # 
type Step String Source # 

data Encoding Source #

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

Constructors

ASCII7 
UTF8 
UTF16 
UTF32 
ISO_8859_1 

Instances

Bounded Encoding Source # 
Enum Encoding Source # 
Eq Encoding Source # 
Data Encoding Source # 

Methods

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

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

toConstr :: Encoding -> Constr #

dataTypeOf :: Encoding -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Encoding Source # 
Show Encoding Source # 

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

words :: String -> [String] Source #

Split words in a string using spaces as separation

words "Hello Foundation"
Hello, Foundation