universum-0.9.2: Custom prelude used in Serokell

Safe HaskellNone
LanguageHaskell2010

String

Contents

Description

Type classes for convertion between different string representations.

Synopsis

Documentation

Text

module Text.Read

module Data.Text

class ConvertUtf8 a b where Source #

Type class for conversion to utf8 representation of text.

Minimal complete definition

encodeUtf8, decodeUtf8, decodeUtf8Strict

Methods

encodeUtf8 :: a -> b Source #

Encode as utf8 string (usually ByteString).

>>> encodeUtf8 @Text @ByteString "патак"
"\208\191\208\176\209\130\208\176\208\186"

decodeUtf8 :: b -> a Source #

Decode from utf8 string.

>>> decodeUtf8 @Text @ByteString "\208\191\208\176\209\130\208\176\208\186"
"\1087\1072\1090\1072\1082"
>>> putStrLn $ decodeUtf8 @Text @ByteString "\208\191\208\176\209\130\208\176\208\186"
патак

decodeUtf8Strict :: b -> Either UnicodeException a Source #

Decode as utf8 string but returning execption if byte sequence is malformed.

>>> decodeUtf8 @Text @ByteString "\208\208\176\209\130\208\176\208\186"
"\65533\65533\1090\1072\1082"
>>> decodeUtf8Strict @Text @ByteString "\208\208\176\209\130\208\176\208\186"
Left Cannot decode byte '\xd0': Data.Text.Internal.Encoding.decodeUtf8: Invalid UTF-8 stream

class ToString a where Source #

Type class for converting other strings to String.

Minimal complete definition

toString

Methods

toString :: a -> String Source #

class ToLText a where Source #

Type class for converting other strings to Text.

Minimal complete definition

toLText

Methods

toLText :: a -> Text Source #

class ToText a where Source #

Type class for converting other strings to Text.

Minimal complete definition

toText

Methods

toText :: a -> Text Source #

Buildable class

class Buildable p #

The class of types that can be rendered to a Builder.

Minimal complete definition

build

Instances

Buildable Bool 

Methods

build :: Bool -> Builder #

Buildable Char 

Methods

build :: Char -> Builder #

Buildable Double 

Methods

build :: Double -> Builder #

Buildable Float 

Methods

build :: Float -> Builder #

Buildable Int 

Methods

build :: Int -> Builder #

Buildable Int8 

Methods

build :: Int8 -> Builder #

Buildable Int16 

Methods

build :: Int16 -> Builder #

Buildable Int32 

Methods

build :: Int32 -> Builder #

Buildable Int64 

Methods

build :: Int64 -> Builder #

Buildable Integer 

Methods

build :: Integer -> Builder #

Buildable Word 

Methods

build :: Word -> Builder #

Buildable Word8 

Methods

build :: Word8 -> Builder #

Buildable Word16 

Methods

build :: Word16 -> Builder #

Buildable Word32 

Methods

build :: Word32 -> Builder #

Buildable Word64 

Methods

build :: Word64 -> Builder #

Buildable WordPtr 

Methods

build :: WordPtr -> Builder #

Buildable IntPtr 

Methods

build :: IntPtr -> Builder #

Buildable Builder 

Methods

build :: Builder -> Builder #

Buildable Text 

Methods

build :: Text -> Builder #

Buildable Text 

Methods

build :: Text -> Builder #

Buildable ZonedTime 

Methods

build :: ZonedTime -> Builder #

Buildable LocalTime 

Methods

build :: LocalTime -> Builder #

Buildable TimeOfDay 

Methods

build :: TimeOfDay -> Builder #

Buildable TimeZone 

Methods

build :: TimeZone -> Builder #

Buildable UniversalTime 
Buildable UTCTime 

Methods

build :: UTCTime -> Builder #

Buildable NominalDiffTime 
Buildable DiffTime 

Methods

build :: DiffTime -> Builder #

Buildable Day 

Methods

build :: Day -> Builder #

Buildable [Char] 

Methods

build :: [Char] -> Builder #

Buildable a => Buildable (Maybe a) 

Methods

build :: Maybe a -> Builder #

(Integral a, Buildable a) => Buildable (Ratio a) 

Methods

build :: Ratio a -> Builder #

Buildable (Ptr a) 

Methods

build :: Ptr a -> Builder #

Integral a => Buildable (Hex a) 

Methods

build :: Hex a -> Builder #

Show a => Buildable (Shown a) 

Methods

build :: Shown a -> Builder #

Show and read functions

readEither :: (ToString a, Read b) => a -> Either Text b Source #

Polymorhpic version of readEither.

>>> readEither @Text @Int "123"
Right 123
>>> readEither @Text @Int "aa"
Left "Prelude.read: no parse"

show :: forall b a. (Show a, IsString b) => a -> b Source #

Generalized version of show.

pretty :: Buildable a => a -> Text Source #

Functions to show pretty output for buildable data types.

prettyL :: Buildable a => a -> LText Source #

Similar to pretty but for LText.

Convenient type aliases

type LText = Text Source #

Type synonym for Text.

type LByteString = ByteString Source #

Type synonym for ByteString.