ttc-1.0.0.0: Textual Type Classes
CopyrightCopyright (c) 2019-2021 Travis Cardwell
LicenseMIT
Safe HaskellNone
LanguageHaskell2010

Data.TTC

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.

For more details, see the following article: https://www.extrema.is/articles/ttc-textual-type-classes/textual-type-class

Since: 0.1.0.0

Minimal complete definition

toS, toT, toTL, toBS, toBSL, convert

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

Convert between any supported textual data types

Since: 0.1.0.0

"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

Since: 0.1.0.0

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

Convert to strict Text

Since: 0.1.0.0

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

Convert to lazy Text

Since: 0.1.0.0

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

Convert to a strict ByteString

Since: 0.1.0.0

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

Convert to a lazy ByteString

Since: 0.1.0.0

"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

Since: 0.1.0.0

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

Convert from strict Text

Since: 0.1.0.0

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

Convert from lazy Text

Since: 0.1.0.0

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

Convert from a strict ByteString

Since: 0.1.0.0

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

Convert from a lazy ByteString

Since: 0.1.0.0

"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

Since: 0.1.0.0

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

Convert an argument to strict Text

Since: 0.1.0.0

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

Convert an argument to lazy Text

Since: 0.1.0.0

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

Convert an argument to a strict ByteString

Since: 0.1.0.0

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

Convert an argument to a lazy ByteString

Since: 0.1.0.0

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

Since: 0.1.0.0

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

Convert from a Text Builder

Since: 0.1.0.0

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

Convert to a ByteString Builder

Since: 0.1.0.0

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

Convert from a ByteString Builder

Since: 0.1.0.0

toSBS :: Textual t => t -> ShortByteString Source #

Convert to a ShortByteString

Since: 0.1.0.0

fromSBS :: Textual t => ShortByteString -> t Source #

Convert from a ShortByteString

Since: 0.1.0.0

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.

See the uname and prompt example programs in the examples directory.

For more details, see the following article: https://www.extrema.is/articles/ttc-textual-type-classes/render-and-parse

Since: 0.1.0.0

Methods

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

Instances

Instances details
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

Since: 0.1.0.0

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

Render to strict Text

Since: 0.1.0.0

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

Render to lazy Text

Since: 0.1.0.0

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

Render to a strict ByteString

Since: 0.1.0.0

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

Render to a lazy ByteString

Since: 0.1.0.0

renderTLB :: Render a => a -> Builder Source #

Render to a Text Builder

Since: 0.4.0.0

renderBSB :: Render a => a -> Builder Source #

Render to a ByteString Builder

Since: 0.4.0.0

renderSBS :: Render a => a -> ShortByteString Source #

Render to a ShortByteString

Since: 0.4.0.0

Render Utilities

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

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

Since: 0.1.0.0

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.

See the uname and prompt example programs in the examples directory.

For more details, see the following article: https://www.extrema.is/articles/ttc-textual-type-classes/render-and-parse

Since: 0.3.0.0

Methods

parse :: (Textual t, Textual e) => t -> Either e a Source #

Instances

Instances details
Parse Char Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Char Source #

Parse Double Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Double Source #

Parse Float Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Float Source #

Parse Int Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Int Source #

Parse Int8 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Int8 Source #

Parse Int16 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Int16 Source #

Parse Int32 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Int32 Source #

Parse Int64 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Int64 Source #

Parse Integer Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Integer Source #

Parse Word Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Word Source #

Parse Word8 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Word8 Source #

Parse Word16 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Word16 Source #

Parse Word32 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Word32 Source #

Parse Word64 Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Word64 Source #

Parse String Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e String Source #

Parse ByteString Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e ByteString Source #

Parse ByteString Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e ByteString Source #

Parse Text Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e Text Source #

Parse Text Source # 
Instance details

Defined in Data.TTC.Instances

Methods

parse :: (Textual t, Textual e) => t -> Either e 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, Textual e) => String -> Either e a Source #

Parse from a String

Since: 0.3.0.0

parseT :: (Parse a, Textual e) => Text -> Either e a Source #

Parse from strict Text

Since: 0.3.0.0

parseTL :: (Parse a, Textual e) => Text -> Either e a Source #

Parse from lazy Text

Since: 0.3.0.0

parseBS :: (Parse a, Textual e) => ByteString -> Either e a Source #

Parse from a strict ByteString

Since: 0.3.0.0

parseBSL :: (Parse a, Textual e) => ByteString -> Either e a Source #

Parse from a lazy ByteString

Since: 0.3.0.0

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

Since: 0.3.0.0

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

Parse from a String to a Maybe type

Since: 0.3.0.0

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

Parse from strict Text to a Maybe type

Since: 0.3.0.0

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

Parse from lazy Text to a Maybe type

Since: 0.3.0.0

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

Parse from a strict ByteString to a Maybe type

Since: 0.3.0.0

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

Parse from a lazy ByteString to a Maybe type

Since: 0.3.0.0

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

Since: 0.1.0.0

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

Unsafely parse to a String

Since: 0.1.0.0

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

Unsafely parse to strict Text

Since: 0.1.0.0

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

Unsafely parse to lazy Text

Since: 0.1.0.0

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

Unsafely parse to a strict ByteString

Since: 0.1.0.0

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

Unsafely parse to a lazy ByteString

Since: 0.1.0.0

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

This function is intended to be used with types that have few choices, as the implementation uses a linear algorithm.

See the enum example program in the examples directory.

Since: 0.1.0.0

parseEnum' Source #

Arguments

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

name to include in error messages

-> Bool

case-insensitive when True

-> Bool

accept unique prefixes when True

-> t

textual input to parse

-> Either e a

error or parsed value

Parse a value in an enumeration, with Textual 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

Since: 0.4.0.0

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

Since: 0.1.0.0

parseWithRead' Source #

Arguments

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

name to include in error messages

-> t

textual input to parse

-> Either e a

error or parsed value

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

The following English error message is returned:

  • "invalid {name}" when the parse fails

Since: 0.3.0.0

maybeParseWithRead Source #

Arguments

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

textual input to parse

-> Maybe a

parsed value or Nothing if invalid

Parse a value to a Maybe type using the Read instance

Since: 0.3.0.0

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.

Since: 0.1.0.0

readsWithParse :: Parse a => ReadS a Source #

Implement ReadS using a Parse instance

This implementation expects all of the input to be consumed.

Since: 0.3.0.0

Constant Validation

The follow functions provide a number of ways to use a Parse instance to validate constants at compile-time.

If you can use Template Haskell typed expressions in your project, use valid, mkValid, or validOf. Use valid to define constants for types that have a Lift instance. For types that do not have a Lift instance, use mkValid to define a validation function for that type using a Proxy, or use validOf to pass the Proxy when defining constants.

Typed expressions were not supported in haskell-src-exts <1.22.0, which causes problems with old versions of hlint. If the issue affects you, you may use mkUntypedValid, mkUntypedValidQQ, or untypedValidOf instead of the above functions. Use mkUntypedValid to define a validation function for a type using a Proxy, or use untypedValidOf to pass the Proxy when defining constants. Alternatively, use mkUntypedValidQQ to define a validation quasi-quoter.

For more details, see the following article: https://www.extrema.is/articles/ttc-textual-type-classes/validated-constants

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 and fails compilation on error. When valid, the result is compiled in, so the result type must have a Lift instance. When this is inconvenient, use one of the alternative functions in this library.

This function uses a Template Haskell typed expression. Typed expressions were not supported in haskell-src-exts <1.22.0, which causes problems with old versions of hlint. If the issue affects you, use hlint -i "Parse error" to ignore parse errors or use one of the alternative functions in this library.

Note that the typed Template Haskell API changed in GHC 9. The type displayed in this documentation is determined by the version of GHC used to build the documentation.

The type of this function in GHC 9 or later is as follows:

valid
  :: (MonadFail m, THS.Quote m, Parse a, THS.Lift a)
  => String
  -> THS.Code m a

The type of this function in previous versions of GHC is as follows:

valid
  :: (Parse a, THS.Lift a)
  => String
  -> TH.Q (TH.TExp a)

This function is used the same way in all GHC versions. See the valid, invalid, and lift example programs in the examples directory. The following is example usage from the valid example:

sample :: Username
sample = $$(TTC.valid "tcard")

Since: 0.1.0.0

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

Validate a constant at compile-time using a Parse instance

This function requires a Proxy of the result type. Use mkValid to avoid having to pass a Proxy during constant definition.

This function parses the String at compile-time and fails compilation on error. 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.

This function uses a Template Haskell typed expression. Typed expressions were not supported in haskell-src-exts <1.22.0, which causes problems with old versions of hlint. If the issue affects you, use hlint -i "Parse error" to ignore parse errors or use untypedValidOf instead.

Note that the typed Template Haskell API changed in GHC 9. The type displayed in this documentation is determined by the version of GHC used to build the documentation.

The type of this function in GHC 9 or later is as follows:

validOf
  :: (MonadFail m, THS.Quote m, Parse a)
  => Proxy a
  -> String
  -> THS.Code m a

The type of this function in previous versions of GHC is as follows:

validOf
  :: Parse a
  => Proxy a
  -> String
  -> TH.Q (TH.TExp a)

This function is used the same way in all GHC versions. See the validof example program in the examples directory. The following is example usage from the validof example:

sample :: Username
sample = $$(TTC.validOf (Proxy :: Proxy Username) "tcard")

Since: 0.1.0.0

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

Make a valid function using validOf for the given type

Create a valid function for a type in order to avoid having to write a Proxy when defining constants.

This function uses a Template Haskell typed expression. Typed expressions were not supported in haskell-src-exts <1.22.0, which causes problems with old versions of hlint. If the issue affects you, use hlint -i "Parse error" to ignore parse errors or use mkUntypedValid instead.

Note that the typed Template Haskell API changed in GHC 9. The type displayed in this documentation is determined by the version of GHC used to build the documentation.

The type of the created valid function in GHC 9 or later is as follows:

$funName
  :: forall m. (MonadFail m, THS.Quote m)
  => String
  -> THS.Code m $resultType

The type of the created valid function in previous versions of GHC is as follows:

$funName
  :: String
  -> TH.Q (TH.TExp $resultType)

This function is used the same way in all GHC versions. See the mkvalid example program in the examples directory. The following is example usage from the mkvalid example:

$(TTC.mkValid "valid" ''Username)

The created valid function can then be used as follows:

sample :: Username
sample = $$(Username.valid "tcard")

Since: 0.1.0.0

untypedValidOf :: Parse a => Proxy a -> String -> ExpQ Source #

Validate a constant at compile-time using a Parse instance

This function requires a Proxy of the result type. Use mkUntypedValid to avoid having to pass a Proxy during constant definition.

This function parses the String at compile-time and fails compilation on error. 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.

See the uvalidof example program in the examples directory. The following is example usage from the uvalidof example:

sample :: Username
sample = $(TTC.untypedValidOf (Proxy :: Proxy Username) "tcard")

Since: 0.2.0.0

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

Make a valid function using untypedValidOf for the given type

Create a valid function for a type in order to avoid having to write a Proxy when defining constants.

See the mkuvalid example program in the examples directory. The following is example usage from the mkuvalid example:

$(TTC.mkUntypedValid "valid" ''Username)

The created valid function can then be used as follows:

sample :: Username
sample = $(Username.valid "tcard")

Since: 0.2.0.0

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

Make a valid quasi-quoter using untypedValidOf for the given type

See the uvalidqq example program in the examples directory. The following is example usage from the uvalidqq example:

$(TTC.mkUntypedValidQQ "valid" ''Username)

The created valid function can then be used as follows:

sample :: Username
sample = [Username.valid|tcard|]

Since: 0.2.0.0