foundation-0.0.28: 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

Documentation

data String #

Instances

Instances details
IsList String 
Instance details

Defined in Basement.UTF8.Base

Associated Types

type Item String #

Eq String 
Instance details

Defined in Basement.UTF8.Base

Methods

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

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

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

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 :: forall r r'. (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 
Instance details

Defined in Basement.UTF8.Base

Show String 
Instance details

Defined in Basement.UTF8.Base

Methods

showsPrec :: Int -> String -> ShowS

show :: String -> String0

showList :: [String] -> ShowS

IsString String 
Instance details

Defined in Basement.UTF8.Base

Methods

fromString :: String0 -> String #

Semigroup String 
Instance details

Defined in Basement.UTF8.Base

Methods

(<>) :: String -> String -> String #

sconcat :: NonEmpty String -> String

stimes :: Integral b => b -> String -> String

Monoid String 
Instance details

Defined in Basement.UTF8.Base

NormalForm String 
Instance details

Defined in Basement.UTF8.Base

Methods

toNormalForm :: String -> () #

Copy String Source # 
Instance details

Defined in Foundation.Collection.Copy

Methods

copy :: String -> String Source #

Collection String Source # 
Instance details

Defined in Foundation.Collection.Collection

Buildable String Source # 
Instance details

Defined in Foundation.Collection.Buildable

Associated Types

type Mutable String :: Type -> Type Source #

type Step String Source #

Methods

append :: forall (prim :: Type -> Type) err. PrimMonad prim => Element String -> Builder String (Mutable String) (Step String) prim err () Source #

build :: PrimMonad prim => Int -> Builder String (Mutable String) (Step String) prim err () -> prim (Either err String) Source #

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

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 #

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

Methods

from :: AsciiString -> String

From String (UArray Word8) 
Instance details

Defined in Basement.From

Methods

from :: String -> UArray Word8

Show (ParseError String) Source # 
Instance details

Defined in Foundation.Parser

Methods

showsPrec :: Int -> ParseError String -> ShowS

show :: ParseError String -> String0

showList :: [ParseError String] -> ShowS

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 Mutable String = MutableString
type Step String Source # 
Instance details

Defined in Foundation.Collection.Buildable

type Chunk String Source # 
Instance details

Defined in Foundation.Parser

data Encoding #

Constructors

ASCII7 
UTF8 
UTF16 
UTF32 
ISO_8859_1 

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

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 :: forall r r'. (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 
Instance details

Defined in Basement.String

Show Encoding 
Instance details

Defined in Basement.String

Methods

showsPrec :: Int -> Encoding -> ShowS

show :: Encoding -> String

showList :: [Encoding] -> ShowS

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