ttc-1.2.1.0: Textual Type Classes
CopyrightCopyright (c) 2019-2023 Travis Cardwell
LicenseMIT
Safe HaskellSafe-Inferred
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.

This type class has two key features:

  • Type conversion is not done through a fixed type (such as String or Text).
  • It has a single type variable, making it easy to write functions that accept arguments and/or return 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.

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, toTLB, toBS, toBSL, toBSB, toSBS, convert

Instances

Instances details
Textual Builder Source # 
Instance details

Defined in Data.TTC

Textual ByteString Source # 
Instance details

Defined in Data.TTC

Textual ByteString Source # 
Instance details

Defined in Data.TTC

Textual ShortByteString Source # 
Instance details

Defined in Data.TTC

Textual Text Source # 
Instance details

Defined in Data.TTC

Textual Builder Source # 
Instance details

Defined in Data.TTC

Textual Text Source # 
Instance details

Defined in Data.TTC

Textual String Source # 
Instance details

Defined in Data.TTC

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

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

Convert to a Text Builder

Since: 1.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

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

Convert to a ByteString Builder

Since: 1.1.0.0

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

Convert to a ShortByteString

Since: 1.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

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

Convert from a Text Builder

Since: 1.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

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

Convert from a ByteString Builder

Since: 1.1.0.0

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

Convert from a ShortByteString

Since: 1.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

asTLB :: Textual t => (Builder -> a) -> t -> a Source #

Convert an argument to a Text Builder

Since: 1.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

asBSB :: Textual t => (Builder -> a) -> t -> a Source #

Convert an argument to a ByteString Builder

Since: 1.1.0.0

asSBS :: Textual t => (ShortByteString -> a) -> t -> a Source #

Convert an argument to a ShortByteString

Since: 1.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 defined for the RenderDefault type class, however, and you can load the Render instance as follows:

instance TTC.Render Int

Since a type may have at most one instance of a given type class, special care must be taken when defining type class instances in a shared library. In particular, orphan instances should generally not be used in shared libraries since they prevent users of the libraries from writing their own 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

Minimal complete definition

Nothing

Methods

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

default render :: (RenderDefault a, Textual t) => a -> t Source #

class RenderDefault a where Source #

The RenderDefault type class provides some default Render instances.

  • The Char instance renders a single-character string.
  • Numeric type instances all render using the Show instance.
  • Textual type instances all convert to the target Textual data type.

Since: 1.1.0.0

Methods

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

Instances

Instances details
RenderDefault Int16 Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Int32 Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Int64 Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Int8 Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Word16 Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Word32 Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Word64 Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Word8 Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault ByteString Source # 
Instance details

Defined in Data.TTC

RenderDefault ByteString Source # 
Instance details

Defined in Data.TTC

RenderDefault Text Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Text Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault String Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Integer Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Char Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Double Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Float Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Int Source # 
Instance details

Defined in Data.TTC

Methods

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

RenderDefault Word Source # 
Instance details

Defined in Data.TTC

Methods

renderDefault :: Textual t => Word -> 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

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

Render to a Text Builder

Since: 0.4.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

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 defined for the ParseDefault type class, however, and you can load the Parse instance as follows:

instance TTC.Parse Int

Since a type may have at most one instance of a given type class, special care must be taken when defining type class instances in a shared library. In particular, orphan instances should generally not be used in shared libraries since they prevent users of the libraries from writing their own 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

Minimal complete definition

Nothing

Methods

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

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

class ParseDefault a where Source #

The ParseDefault type class provides some default Parse instances.

  • The Char instance parses single-character strings.
  • Numeric type instances all parse using the Read instance.
  • Textual type instances all convert from the source Textual data type.

Since: 1.1.0.0

Methods

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

Instances

Instances details
ParseDefault Int16 Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Int32 Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Int64 Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Int8 Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Word16 Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Word32 Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Word64 Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Word8 Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault ByteString Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault ByteString Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Text Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Text Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault String Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Integer Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Char Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Double Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Float Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Int Source # 
Instance details

Defined in Data.TTC

Methods

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

ParseDefault Word Source # 
Instance details

Defined in Data.TTC

Methods

parseDefault :: (Textual t, Textual e) => t -> Either e Word 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

parseTLB :: (Parse a, Textual e) => Builder -> Either e a Source #

Parse from a Text Builder

Since: 1.1.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

parseBSB :: (Parse a, Textual e) => Builder -> Either e a Source #

Parse from a ByteString Builder

Since: 1.1.0.0

parseSBS :: (Parse a, Textual e) => ShortByteString -> Either e a Source #

Parse from a ShortByteString

Since: 1.1.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

parseMaybeTLB :: Parse a => Builder -> Maybe a Source #

Parse from a Text Builder to a Maybe type

Since: 1.1.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

parseMaybeBSB :: Parse a => Builder -> Maybe a Source #

Parse from a ByteString Builder to a Maybe type

Since: 1.1.0.0

parseMaybeSBS :: Parse a => ShortByteString -> Maybe a Source #

Parse from a ShortByteString to a Maybe type

Since: 1.1.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 :: (HasCallStack, Parse a, Textual t) => t -> a Source #

Unsafely parse

Since: 0.1.0.0

parseUnsafeS :: (HasCallStack, Parse a) => String -> a Source #

Unsafely parse to a String

Since: 0.1.0.0

parseUnsafeT :: (HasCallStack, Parse a) => Text -> a Source #

Unsafely parse to strict Text

Since: 0.1.0.0

parseUnsafeTL :: (HasCallStack, Parse a) => Text -> a Source #

Unsafely parse to lazy Text

Since: 0.1.0.0

parseUnsafeTLB :: (HasCallStack, Parse a) => Builder -> a Source #

Unsafely parse to a Text Builder

Since: 1.1.0.0

parseUnsafeBS :: (HasCallStack, Parse a) => ByteString -> a Source #

Unsafely parse to a strict ByteString

Since: 0.1.0.0

parseUnsafeBSL :: (HasCallStack, Parse a) => ByteString -> a Source #

Unsafely parse to a lazy ByteString

Since: 0.1.0.0

parseUnsafeBSB :: (HasCallStack, Parse a) => Builder -> a Source #

Unsafely parse to a ByteString Builder

Since: 1.1.0.0

parseUnsafeSBS :: (HasCallStack, Parse a) => ShortByteString -> a Source #

Unsafely parse to a ShortByteString

Since: 1.1.0.0

Parse With A Single Error Message

The withError function takes an error message and a Maybe value. It returns a Parse result: the error when the Maybe value is Nothing, or the value inside the Just. This provides a convenient way to return the same error message for any parse error. The rest of the functions are equivalent to withError, but they specify the type of the error message. Use them to avoid having to write type annotations in cases where the type is ambiguous.

withError :: (Textual e', Textual e) => e' -> Maybe a -> Either e a Source #

Create a Parse result from a Textual error message and a Maybe value

Since: 1.2.0.0

withErrorS :: Textual e => String -> Maybe a -> Either e a Source #

Create a Parse result from a String error message and a Maybe value

Since: 1.2.0.0

withErrorT :: Textual e => Text -> Maybe a -> Either e a Source #

Create a Parse result from a Text error message and a Maybe value

Since: 1.2.0.0

withErrorTL :: Textual e => Text -> Maybe a -> Either e a Source #

Create a Parse result from a Text error message and a Maybe value

Since: 1.2.0.0

withErrorTLB :: Textual e => Builder -> Maybe a -> Either e a Source #

Create a Parse result from a Builder error message and a Maybe value

Since: 1.2.0.0

withErrorBS :: Textual e => ByteString -> Maybe a -> Either e a Source #

Create a Parse result from a ByteString error message and a Maybe value

Since: 1.2.0.0

withErrorBSL :: Textual e => ByteString -> Maybe a -> Either e a Source #

Create a Parse result from a ByteString error message and a Maybe value

Since: 1.2.0.0

withErrorBSB :: Textual e => Builder -> Maybe a -> Either e a Source #

Create a Parse result from a Builder error message and a Maybe value

Since: 1.2.0.0

withErrorSBS :: Textual e => ShortByteString -> Maybe a -> Either e a Source #

Create a Parse result from a ShortByteString error message and a Maybe value

Since: 1.2.0.0

Parse With An Error Prefix

The prefixError function adds a common prefix to error messages of a Parse result. The rest of the functions are equivalent to prefixError, but they specify the type of the error message. Use them to avoid having to write type annotations in cases where the type is ambiguous.

prefixError :: (Monoid e', Textual e', Textual e) => e' -> Either e' a -> Either e a Source #

Add a prefix to Textual error messages of a Parse result

Since: 1.2.0.0

prefixErrorS :: Textual e => String -> Either String a -> Either e a Source #

Add a prefix to String error messages of a Parse result

Since: 1.2.0.0

prefixErrorT :: Textual e => Text -> Either Text a -> Either e a Source #

Add a prefix to Text error messages of a Parse result

Since: 1.2.0.0

prefixErrorTL :: Textual e => Text -> Either Text a -> Either e a Source #

Add a prefix to Text error messages of a Parse result

Since: 1.2.0.0

prefixErrorTLB :: Textual e => Builder -> Either Builder a -> Either e a Source #

Add a prefix to Builder error messages of a Parse result

Since: 1.2.0.0

prefixErrorBS :: Textual e => ByteString -> Either ByteString a -> Either e a Source #

Add a prefix to ByteString error messages of a Parse result

Since: 1.2.0.0

prefixErrorBSL :: Textual e => ByteString -> Either ByteString a -> Either e a Source #

Add a prefix to ByteString error messages of a Parse result

Since: 1.2.0.0

prefixErrorBSB :: Textual e => Builder -> Either Builder a -> Either e a Source #

Add a prefix to Builder error messages of a Parse result

Since: 1.2.0.0

prefixErrorSBS :: Textual e => ShortByteString -> Either ShortByteString a -> Either e a Source #

Add a prefix to ShortByteString error messages of a Parse result

Since: 1.2.0.0

Parse Enums

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

Read Instances

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 :: (MonadFail m, Quote m, Parse a, Lift a) => String -> Code m 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 :: (MonadFail m, Quote m, Parse a) => Proxy a -> String -> Code m 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