ttc-0.1.0.1: Textual Type Classes

CopyrightCopyright (c) 2019 Travis Cardwell
LicenseMIT
Safe HaskellNone
LanguageHaskell2010

Data.TTC

Contents

Description

TTC, an initialism of Textual Type Classes, is a library that provides type classes for conversion between data types and textual data types (strings).

This library is meant to be imported qualified, as follows:

import qualified Data.TTC as TTC
Synopsis

Textual

class Textual t Source #

The Textual type class is used to convert between the following textual data types:

ByteString values are assumed to be UTF-8 encoded text. Invalid bytes are replaced with the Unicode replacement character U+FFFD. In cases where different behavior is required, process ByteString values before using this class.

The key feature of this type class is that it has a single type variable, making it easy to write functions that accepts arguments and/or returns values that may be any of the supported textual data types.

Note that support for additional data types cannot be implemented by writing instances. Adding support for additional data types would require changing the class definition itself. This is the price paid for having only one type variable instead of two.

Minimal complete definition

toS, toT, toTL, toBS, toBSL, convert

convert :: (Textual t, Textual t') => t' -> t Source #

Convert between any supported textual data types

"To" Conversions

These functions are equivalent to convert, but they specify the type being converted to. Use them to avoid having to write type annotations in cases where the type is ambiguous.

toS :: Textual t => t -> String Source #

Convert to a String

toT :: Textual t => t -> Text Source #

Convert to strict Text

toTL :: Textual t => t -> Text Source #

Convert to lazy Text

toBS :: Textual t => t -> ByteString Source #

Convert to a strict ByteString

toBSL :: Textual t => t -> ByteString Source #

Convert to a lazy ByteString

"From" Conversions

These functions are equivalent to convert, but they specify the type being converted from. Use them to avoid having to write type annotations in cases where the type is ambiguous.

fromS :: Textual t => String -> t Source #

Convert from a String

fromT :: Textual t => Text -> t Source #

Convert from strict Text

fromTL :: Textual t => Text -> t Source #

Convert from lazy Text

fromBS :: Textual t => ByteString -> t Source #

Convert from a strict ByteString

fromBSL :: Textual t => ByteString -> t Source #

Convert from a lazy ByteString

"As" Conversions

These functions are used to convert a Textual argument of a function to a specific type. Use them to reduce boilerplate in small function definitions.

asS :: Textual t => (String -> a) -> t -> a Source #

Convert an argument to a String

asT :: Textual t => (Text -> a) -> t -> a Source #

Convert an argument to strict Text

asTL :: Textual t => (Text -> a) -> t -> a Source #

Convert an argument to lazy Text

asBS :: Textual t => (ByteString -> a) -> t -> a Source #

Convert an argument to a strict ByteString

asBSL :: Textual t => (ByteString -> a) -> t -> a Source #

Convert an argument to a lazy ByteString

Other Conversions

These functions are used to convert to/from the following other textual data types:

toTLB :: Textual t => t -> Builder Source #

Convert to a Text Builder

fromTLB :: Textual t => Builder -> t Source #

Convert from a Text Builder

toBSB :: Textual t => t -> Builder Source #

Convert to a ByteString Builder

fromBSB :: Textual t => Builder -> t Source #

Convert from a ByteString Builder

Render

class Render a where Source #

The Render type class renders a data type as a textual data type.

There are no default instances for the Render type class, so that all instances can be customized per project when desired. Instances for some basic data types are available in Data.TTC.Instances.

Methods

render :: Textual t => a -> t Source #

Instances
Render Char Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Char -> t Source #

Render Double Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Double -> t Source #

Render Float Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Float -> t Source #

Render Int Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Int -> t Source #

Render Int8 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Int8 -> t Source #

Render Int16 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Int16 -> t Source #

Render Int32 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Int32 -> t Source #

Render Int64 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Int64 -> t Source #

Render Integer Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Integer -> t Source #

Render Word Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Word -> t Source #

Render Word8 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Word8 -> t Source #

Render Word16 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Word16 -> t Source #

Render Word32 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Word32 -> t Source #

Render Word64 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Word64 -> t Source #

Render String Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => String -> t Source #

Render ByteString Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => ByteString -> t Source #

Render ByteString Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => ByteString -> t Source #

Render Text Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Text -> t Source #

Render Text Source # 
Instance details

Defined in Data.TTC.Instances

Methods

render :: Textual t => Text -> t Source #

Rendering Specific Types

These functions are equivalent to render, but they specify the type being rendered to. Use them to avoid having to write type annotations in cases where the type is ambiguous.

renderS :: Render a => a -> String Source #

Render to a String

renderT :: Render a => a -> Text Source #

Render to strict Text

renderTL :: Render a => a -> Text Source #

Render to lazy Text

renderBS :: Render a => a -> ByteString Source #

Render to a strict ByteString

renderBSL :: Render a => a -> ByteString Source #

Render to a lazy ByteString

Render Utilities

renderWithShow :: (Show a, Textual t) => a -> t Source #

Render a value to a textual data type using the Show instance

Parse

class Parse a where Source #

The Parse type class parses a data type from a textual data type.

There are no default instances for the Parse type class, so that all instances can be customized per project when desired. Instances for some basic data types are available in Data.TTC.Instances.

Methods

parse :: Textual t => t -> Either String a Source #

Instances
Parse Char Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Char Source #

Parse Double Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Double Source #

Parse Float Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Float Source #

Parse Int Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Int Source #

Parse Int8 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Int8 Source #

Parse Int16 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Int16 Source #

Parse Int32 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Int32 Source #

Parse Int64 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Int64 Source #

Parse Integer Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Integer Source #

Parse Word Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Word Source #

Parse Word8 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Word8 Source #

Parse Word16 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Word16 Source #

Parse Word32 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Word32 Source #

Parse Word64 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Word64 Source #

Parse String Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String String Source #

Parse ByteString Source # 
Instance details

Defined in Data.TTC.Instances

Parse ByteString Source # 
Instance details

Defined in Data.TTC.Instances

Parse Text Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Text Source #

Parse Text Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: Textual t => t -> Either String Text Source #

Parsing From Specific Types

These functions are equivalent to parse, but they specify the type being parsed from. Use them to avoid having to write type annotations in cases where the type is ambiguous.

parseS :: Parse a => String -> Either String a Source #

Parse from a String

parseT :: Parse a => Text -> Either String a Source #

Parse from strict Text

parseTL :: Parse a => Text -> Either String a Source #

Parse from lazy Text

parseBS :: Parse a => ByteString -> Either String a Source #

Parse from a strict ByteString

parseBSL :: Parse a => ByteString -> Either String a Source #

Parse from a lazy ByteString

Maybe Parsing

The parseMaybe function parses to a Maybe type instead of an Either type. The rest of the functions are equivalent to parseMaybe, but they specify the type being parsed from. Use them to avoid having to write type annotations in cases where the type is ambiguous.

parseMaybe :: Parse a => Textual t => t -> Maybe a Source #

Parse to a Maybe type

parseMaybeS :: Parse a => String -> Maybe a Source #

Parse from a String to a Maybe type

parseMaybeT :: Parse a => Text -> Maybe a Source #

Parse from strict Text to a Maybe type

parseMaybeTL :: Parse a => Text -> Maybe a Source #

Parse from lazy Text to a Maybe type

parseMaybeBS :: Parse a => ByteString -> Maybe a Source #

Parse from a strict ByteString to a Maybe type

parseMaybeBSL :: Parse a => ByteString -> Maybe a Source #

Parse from a lazy ByteString to a Maybe type

Unsafe Parsing

The parseUnsafe function raises an exception on error instead of using an Either type. It should only be used when an error is not possible. The rest of the functions are equivalent to parseUnsafe, but they specify the type being parsed from. Use them to avoid having to write type annotations in cases where the type is ambiguous.

parseUnsafe :: (Parse a, Textual t) => t -> a Source #

Unsafely parse

parseUnsafeS :: Parse a => String -> a Source #

Unsafely parse to a String

parseUnsafeT :: Parse a => Text -> a Source #

Unsafely parse to strict Text

parseUnsafeTL :: Parse a => Text -> a Source #

Unsafely parse to lazy Text

parseUnsafeBS :: Parse a => ByteString -> a Source #

Unsafely parse to a strict ByteString

parseUnsafeBSL :: Parse a => ByteString -> a Source #

Unsafely parse to a lazy ByteString

Parse Utilities

parseEnum Source #

Arguments

:: (Bounded a, Enum a, Render a, Textual t) 
=> Bool

case-insensitive when True

-> Bool

accept unique prefixes when True

-> e

invalid input error

-> e

ambiguous input error

-> t

textual input to parse

-> Either e a

error or parsed value

Parse a value in an enumeration

parseEnum' Source #

Arguments

:: (Bounded a, Enum a, Render a, Textual t) 
=> String

name to include in error messages

-> Bool

case-insensitive when True

-> Bool

accept unique prefixes when True

-> t

textual input to parse

-> Either String a

error or parsed value

Parse a value in an enumeration, with String error messages

The following English error messages are returned:

  • "invalid {name}" when there are no matches
  • "ambiguous {name}" when there is more than one match

parseWithRead Source #

Arguments

:: (Read a, Textual t) 
=> e

invalid input error

-> t

textual input to parse

-> Either e a

error or parsed value

Parse a value using the Read instance

parseWithRead' Source #

Arguments

:: (Read a, Textual t) 
=> String

name to include in error messages

-> t

textual input to parse

-> Either String a

error or parsed value

Parse a value using the Read instance, with String error messages

The following English error message is returned:

  • "invalid {name}" when the parse fails

readsEnum Source #

Arguments

:: (Bounded a, Enum a, Render a) 
=> Bool

case-insensitive when True

-> Bool

accept unique prefixes when True

-> ReadS a 

Implement ReadS using parseEnum

This implementation expects all of the input to be consumed.

readsWithParse :: Parse a => ReadS a Source #

Implement ReadS using a Parse instance

This implementation expects all of the input to be consumed.

valid :: (Parse a, Lift a) => String -> Q (TExp a) Source #

Validate a constant at compile-time using a Parse instance

This function parses the String at compile-time in order to validate it. When valid, the result is compiled in, so the result type must have a Lift instance. Use validOf when this is inconvenient.

validOf :: Parse a => Proxy a -> String -> Q (TExp a) Source #

Validate a constant at compile-time using a Parse instance

This function parses the String at compile-time in order to validate it. When valid, the String is compiled in, to be parsed again at run-time. Since the result is not compiled in, no Lift instance is required.

mkValid :: String -> Name -> DecsQ Source #

Make a valid function using validOf for the given type