data-textual-0.1: Human-friendly textual representations.

Safe HaskellNone

Data.Textual

Contents

Description

Working with human-friendly (as opposed to the compiler-friendly Show and Read) textual representations.

Synopsis

Printing

maybePrint :: (Printer p, Printable α) => Maybe α -> pSource

A shorthand for maybe mempty print.

toString :: Printable α => α -> StringSource

A shorthand for buildString . print.

toText :: Printable α => α -> TextSource

A shorthand for buildText . print.

toLazyText :: Printable α => α -> TextSource

A shorthand for buildLazyText . print.

toAscii :: Printable α => α -> ByteStringSource

A shorthand for buildAscii . print.

toLazyAscii :: Printable α => α -> ByteStringSource

A shorthand for buildLazyAscii . print.

toUtf8 :: Printable α => α -> ByteStringSource

A shorthand for buildUtf8 . print.

toLazyUtf8 :: Printable α => α -> ByteStringSource

A shorthand for buildLazyUtf8 . print.

Parsing

class Printable α => Textual α whereSource

The default parser for values of a type, must satisfy fromString (toString x) = Just x

Methods

textual :: (Monad μ, CharParsing μ) => μ αSource

Standard types proxies

hintType :: α -> Proxy α -> αSource

Hint the type system about the type of the first argument.

hintType1 :: f α -> Proxy f -> f αSource

Hint the type system about the type constructor.

hintTypeArg :: f α -> Proxy α -> f αSource

Hint the type system about the type argument.

aUnit :: Proxy ()Source

() proxy value.

aChar :: Proxy CharSource

Char proxy value.

anInt :: Proxy IntSource

Int proxy value.

anInt8 :: Proxy Int8Source

Int8 proxy value.

anInt16 :: Proxy Int16Source

Int16 proxy value.

anInt32 :: Proxy Int32Source

Int32 proxy value.

anInt64 :: Proxy Int64Source

Int64 proxy value.

aWord :: Proxy WordSource

Word proxy value.

aWord8 :: Proxy Word8Source

Word8 proxy value.

aFloat :: Proxy FloatSource

Float proxy value.

aMaybe :: Proxy MaybeSource

Maybe proxy value.

aMaybeOf :: Proxy α -> Proxy (Maybe α)Source

Maybe α proxy value.

aList :: Proxy []Source

List proxy value.

aListOf :: Proxy α -> Proxy [α]Source

List of α proxy value.

Built-in parser

data Parsed α Source

Parsing result.

Constructors

Parsed α 
Malformed [String] String 

maybeParsed :: Parsed α -> Maybe αSource

Map Parsed values to Just and Malformed to Nothing.

builtInParser :: (forall μ. (Monad μ, CharParsing μ) => μ α) -> String -> Parsed αSource

Use the built-in parser to parse a string. Intended for testing only.

parseString :: Textual α => String -> Parsed αSource

Parse a String to extract the Textual value.

parseStringAs :: Textual α => Proxy α -> String -> Parsed αSource

Provide a hint for the type system when using parseString.

parseText :: Textual α => Text -> Parsed αSource

Parse a Text to extract the Textual value.

parseTextAs :: Textual α => Proxy α -> Text -> Parsed αSource

Provide a hint for the type system when using parseText.

parseLazyText :: Textual α => Text -> Parsed αSource

Parse a lazy Text to extract the Textual value.

parseLazyTextAs :: Textual α => Proxy α -> Text -> Parsed αSource

Provide a hint for the type system when using parseLazyText.

parseAscii :: Textual α => ByteString -> Parsed αSource

Decode and parse an ASCII ByteString to extract the Textual value.

parseAsciiAs :: Textual α => Proxy α -> ByteString -> Parsed αSource

Provide a hint for the type system when using parseAscii.

parseLazyAscii :: Textual α => ByteString -> Parsed αSource

Decode and parse a lazy ASCII ByteString to extract the Textual value.

parseLazyAsciiAs :: Textual α => ByteString -> Parsed αSource

Provide a hint for the type system when using parseLazyAscii.

parseUtf8 :: Textual α => ByteString -> Parsed αSource

Decode and parse a UTF-8 ByteString to extract the Textual value.

parseUtf8As :: Textual α => Proxy α -> ByteString -> Parsed αSource

Provide a hint for the type system when using parseUtf8.

parseLazyUtf8 :: Textual α => ByteString -> Parsed αSource

Decode and parse a lazy UTF-8 ByteString to extract the Textual value.

parseLazyUtf8As :: Textual α => Proxy α -> ByteString -> Parsed αSource

Provide a hint for the type system when using parseLazyUtf8.

fromString :: Textual α => String -> Maybe αSource

A shorthand for maybeParsed . parseString

fromStringAs :: Textual α => Proxy α -> String -> Maybe αSource

Provide a hint for the type system when using fromString.

fromText :: Textual α => Text -> Maybe αSource

A shorthand for maybeParsed . parseText

fromTextAs :: Textual α => Proxy α -> Text -> Maybe αSource

Provide a hint for the type system when using fromText.

fromLazyTextAs :: Textual α => Proxy α -> Text -> Maybe αSource

Provide a hint for the type system when using fromLazyText.

fromAsciiAs :: Textual α => Proxy α -> ByteString -> Maybe αSource

Provide a hint for the type system when using fromAscii.

fromLazyAsciiAs :: Textual α => Proxy α -> ByteString -> Maybe αSource

Provide a hint for the type system when using fromLazyAscii.

fromUtf8 :: Textual α => ByteString -> Maybe αSource

A shorthand for maybeParsed . parseUtf8

fromUtf8As :: Textual α => Proxy α -> ByteString -> Maybe αSource

Provide a hint for the type system when using fromUtf8.

fromLazyUtf8As :: Textual α => Proxy α -> ByteString -> Maybe αSource

Provide a hint for the type system when using fromLazyUtf8.