Copyright | Copyright (c) 2019-2025 Travis Cardwell |
---|---|
License | MIT |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
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).
The Render
type class renders a data type as a textual data type, similar
to Show
. Use Render
in your business logic, and only use Show
for
debugging, as use of Show
instances in business logic is a common source
of bugs.
The Parse
type class parses a data type from a textual data type, similar
to Read
. Unlike Read
, Parse
allows you to specify meaningful error
messages.
Render
and Parse
work with multiple textual data types. They are not
limited to String
(like Show
and Read
), and implementations can use
the textual data type that is most appropriate for each data type.
Conversion between textual data types is managed by the Textual
type
class. This library provides instances to support the following textual
data types:
String
(S
)- Strict
Text
(T
) - Lazy
Text
(TL
) Text
Builder
(TLB
)ShortText
(ST
)- Strict
ByteString
(BS
) - Lazy
ByteString
(BSL
) ByteString
Builder
(BSB
)ShortByteString
(SBS
)
This library is meant to be imported qualified, as follows:
import qualified Data.TTC as TTC
Note that this library has a similar API to the
ETTC library,
which uses a Utf8Convertible
type class instead of Textual
. The TTC
API types are simpler, but it is not possible to add support for additional
textual data types without changing the library itself. The ETTC API types
are more complex, leading to longer compilation times, but one can add
support for additional textual data types by defining new Utf8Convertible
instances. Both libraries are maintained, allowing you to use the one that
best matches the needs of your project.
Synopsis
- class Textual t
- convert :: forall t t'. (Textual t, Textual t') => t -> t'
- toS :: Textual t => t -> String
- toT :: Textual t => t -> Text
- toTL :: Textual t => t -> Text
- toTLB :: Textual t => t -> Builder
- toST :: Textual t => t -> ShortText
- toBS :: Textual t => t -> ByteString
- toBSL :: Textual t => t -> ByteString
- toBSB :: Textual t => t -> Builder
- toSBS :: Textual t => t -> ShortByteString
- fromS :: Textual t => String -> t
- fromT :: Textual t => Text -> t
- fromTL :: Textual t => Text -> t
- fromTLB :: Textual t => Builder -> t
- fromST :: Textual t => ShortText -> t
- fromBS :: Textual t => ByteString -> t
- fromBSL :: Textual t => ByteString -> t
- fromBSB :: Textual t => Builder -> t
- fromSBS :: Textual t => ShortByteString -> t
- asS :: forall t a. Textual t => (String -> a) -> t -> a
- asT :: forall t a. Textual t => (Text -> a) -> t -> a
- asTL :: forall t a. Textual t => (Text -> a) -> t -> a
- asTLB :: forall t a. Textual t => (Builder -> a) -> t -> a
- asST :: forall t a. Textual t => (ShortText -> a) -> t -> a
- asBS :: forall t a. Textual t => (ByteString -> a) -> t -> a
- asBSL :: forall t a. Textual t => (ByteString -> a) -> t -> a
- asBSB :: forall t a. Textual t => (Builder -> a) -> t -> a
- asSBS :: forall t a. Textual t => (ShortByteString -> a) -> t -> a
- class Render a where
- class RenderDefault a where
- renderDefault :: Textual t => a -> t
- renderWithShow :: forall t a. (Show a, Textual t) => a -> t
- renderS :: Render a => a -> String
- renderT :: Render a => a -> Text
- renderTL :: Render a => a -> Text
- renderTLB :: Render a => a -> Builder
- renderST :: Render a => a -> ShortText
- renderBS :: Render a => a -> ByteString
- renderBSL :: Render a => a -> ByteString
- renderBSB :: Render a => a -> Builder
- renderSBS :: Render a => a -> ShortByteString
- class Parse a where
- class ParseDefault a where
- parseDefault :: (Textual t, Textual e) => t -> Either e a
- withError :: forall e' e a. (Textual e', Textual e) => e' -> Maybe a -> Either e a
- withErrorS :: forall e a. Textual e => String -> Maybe a -> Either e a
- withErrorT :: forall e a. Textual e => Text -> Maybe a -> Either e a
- withErrorTL :: forall e a. Textual e => Text -> Maybe a -> Either e a
- withErrorTLB :: forall e a. Textual e => Builder -> Maybe a -> Either e a
- withErrorST :: forall e a. Textual e => ShortText -> Maybe a -> Either e a
- withErrorBS :: forall e a. Textual e => ByteString -> Maybe a -> Either e a
- withErrorBSL :: forall e a. Textual e => ByteString -> Maybe a -> Either e a
- withErrorBSB :: forall e a. Textual e => Builder -> Maybe a -> Either e a
- withErrorSBS :: forall e a. Textual e => ShortByteString -> Maybe a -> Either e a
- prefixError :: forall e' e a. (Monoid e', Textual e', Textual e) => e' -> Either e' a -> Either e a
- prefixErrorS :: forall e a. Textual e => String -> Either String a -> Either e a
- prefixErrorT :: forall e a. Textual e => Text -> Either Text a -> Either e a
- prefixErrorTL :: forall e a. Textual e => Text -> Either Text a -> Either e a
- prefixErrorTLB :: forall e a. Textual e => Builder -> Either Builder a -> Either e a
- prefixErrorST :: forall e a. Textual e => ShortText -> Either ShortText a -> Either e a
- prefixErrorBS :: forall e a. Textual e => ByteString -> Either ByteString a -> Either e a
- prefixErrorBSL :: forall e a. Textual e => ByteString -> Either ByteString a -> Either e a
- prefixErrorBSB :: forall e a. Textual e => Builder -> Either Builder a -> Either e a
- prefixErrorSBS :: forall e a. Textual e => ShortByteString -> Either ShortByteString a -> Either e a
- parseWithRead :: forall t e a. (Read a, Textual t) => e -> t -> Either e a
- parseWithRead' :: forall t e a. (Read a, Textual t, Textual e) => String -> t -> Either e a
- maybeParseWithRead :: forall t a. (Read a, Textual t) => t -> Maybe a
- parseEnum :: forall t e a. (Bounded a, Enum a, Render a, Textual t) => Bool -> Bool -> e -> e -> t -> Either e a
- parseEnum' :: forall t e a. (Bounded a, Enum a, Render a, Textual t, Textual e) => String -> Bool -> Bool -> t -> Either e a
- parseS :: forall e a. (Parse a, Textual e) => String -> Either e a
- parseT :: forall e a. (Parse a, Textual e) => Text -> Either e a
- parseTL :: forall e a. (Parse a, Textual e) => Text -> Either e a
- parseTLB :: forall e a. (Parse a, Textual e) => Builder -> Either e a
- parseST :: forall e a. (Parse a, Textual e) => ShortText -> Either e a
- parseBS :: forall e a. (Parse a, Textual e) => ByteString -> Either e a
- parseBSL :: forall e a. (Parse a, Textual e) => ByteString -> Either e a
- parseBSB :: forall e a. (Parse a, Textual e) => Builder -> Either e a
- parseSBS :: forall e a. (Parse a, Textual e) => ShortByteString -> Either e a
- parseMaybe :: forall t a. (Parse a, Textual t) => t -> Maybe a
- parseMaybeS :: Parse a => String -> Maybe a
- parseMaybeT :: Parse a => Text -> Maybe a
- parseMaybeTL :: Parse a => Text -> Maybe a
- parseMaybeTLB :: Parse a => Builder -> Maybe a
- parseMaybeST :: Parse a => ShortText -> Maybe a
- parseMaybeBS :: Parse a => ByteString -> Maybe a
- parseMaybeBSL :: Parse a => ByteString -> Maybe a
- parseMaybeBSB :: Parse a => Builder -> Maybe a
- parseMaybeSBS :: Parse a => ShortByteString -> Maybe a
- parseOrFail :: forall t a m. (MonadFail m, Parse a, Textual t) => t -> m a
- parseOrFailS :: forall a m. (MonadFail m, Parse a) => String -> m a
- parseOrFailT :: forall a m. (MonadFail m, Parse a) => Text -> m a
- parseOrFailTL :: forall a m. (MonadFail m, Parse a) => Text -> m a
- parseOrFailTLB :: forall a m. (MonadFail m, Parse a) => Builder -> m a
- parseOrFailST :: forall a m. (MonadFail m, Parse a) => ShortText -> m a
- parseOrFailBS :: forall a m. (MonadFail m, Parse a) => ByteString -> m a
- parseOrFailBSL :: forall a m. (MonadFail m, Parse a) => ByteString -> m a
- parseOrFailBSB :: forall a m. (MonadFail m, Parse a) => Builder -> m a
- parseOrFailSBS :: forall a m. (MonadFail m, Parse a) => ShortByteString -> m a
- parseUnsafe :: forall t a. (HasCallStack, Parse a, Textual t) => t -> a
- parseUnsafeS :: (HasCallStack, Parse a) => String -> a
- parseUnsafeT :: (HasCallStack, Parse a) => Text -> a
- parseUnsafeTL :: (HasCallStack, Parse a) => Text -> a
- parseUnsafeTLB :: (HasCallStack, Parse a) => Builder -> a
- parseUnsafeST :: (HasCallStack, Parse a) => ShortText -> a
- parseUnsafeBS :: (HasCallStack, Parse a) => ByteString -> a
- parseUnsafeBSL :: (HasCallStack, Parse a) => ByteString -> a
- parseUnsafeBSB :: (HasCallStack, Parse a) => Builder -> a
- parseUnsafeSBS :: (HasCallStack, Parse a) => ShortByteString -> a
- readsWithParse :: Parse a => ReadS a
- readsEnum :: (Bounded a, Enum a, Render a) => Bool -> Bool -> ReadS a
- valid :: (MonadFail m, Quote m, Parse a, Lift a) => String -> Code m a
- validOf :: (MonadFail m, Quote m, Parse a) => Proxy a -> String -> Code m a
- mkValid :: String -> Name -> DecsQ
- untypedValidOf :: Parse a => Proxy a -> String -> ExpQ
- mkUntypedValid :: String -> Name -> DecsQ
- mkUntypedValidQQ :: String -> Name -> DecsQ
- defaultRenderInstance :: Name -> DecsQ
- defaultRenderInstances :: [Name] -> DecsQ
- defaultParseInstance :: Name -> DecsQ
- defaultParseInstances :: [Name] -> DecsQ
- defaultRenderAndParseInstance :: Name -> DecsQ
- defaultRenderAndParseInstances :: [Name] -> DecsQ
Textual
Convert from one textual data type to another
The following textual data types are supported:
String
(S
)- Strict
Text
(T
) - Lazy
Text
(TL
) Text
Builder
(TLB
)ShortText
(ST
)- Strict
ByteString
(BS
) - Lazy
ByteString
(BSL
) ByteString
Builder
(BSB
)ShortByteString
(SBS
)
Note that support for additional textual data types cannot be implemented by writing instances. Adding support for additional textual data types requires changing the class definition itself. If you need support for additional textual data types, consider using the ETTC library instead.
Encoded values are assumed to be valid UTF-8 encoded text. Conversions
must be pure, and any invalid bytes must be replaced with the Unicode
replacement character U+FFFD
. In cases where different behavior is
required, process encoded values separately.
For more details, see the following article: https://www.extrema.is/articles/ttc-textual-type-classes/textual-type-class
Since: 0.1.0.0
Instances
convert :: forall t t'. (Textual t, Textual t') => t -> t' Source #
Convert from one textual data type to another
The order of the type arguments was changed in version 1.5.0.0.
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. Using these functions may make code
easier to understand even in cases where the types are not ambiguous.
toTLB :: Textual t => t -> Builder Source #
Convert from a textual data type to a Text
Builder
Since: 1.1.0.0
toST :: Textual t => t -> ShortText Source #
Convert from a textual data type to ShortText
Since: 1.4.0.0
toBS :: Textual t => t -> ByteString Source #
Convert from a textual data type to a strict ByteString
Since: 0.1.0.0
toBSL :: Textual t => t -> ByteString Source #
Convert from a textual data type to a lazy ByteString
Since: 0.1.0.0
toBSB :: Textual t => t -> Builder Source #
Convert from a textual data type to a ByteString
Builder
Since: 1.1.0.0
toSBS :: Textual t => t -> ShortByteString Source #
Convert from a textual data type 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. Using these functions may make code
easier to understand even in cases where the types are not ambiguous.
fromS :: Textual t => String -> t Source #
Convert from a String
to a textual data type
Since: 0.1.0.0
fromT :: Textual t => Text -> t Source #
Convert from strict Text
to a textual data type
Since: 0.1.0.0
fromTL :: Textual t => Text -> t Source #
Convert from lazy Text
to a textual data type
Since: 0.1.0.0
fromTLB :: Textual t => Builder -> t Source #
Convert from a Text
Builder
to a textual data type
Since: 1.1.0.0
fromST :: Textual t => ShortText -> t Source #
Convert from a ShortText
to a textual data type
Since: 1.4.0.0
fromBS :: Textual t => ByteString -> t Source #
Convert from a strict ByteString
to a textual data type
Since: 0.1.0.0
fromBSL :: Textual t => ByteString -> t Source #
Convert from a lazy ByteString
to a textual data type
Since: 0.1.0.0
fromBSB :: Textual t => Builder -> t Source #
Convert from a ByteString
Builder
to a textual data type
Since: 1.1.0.0
fromSBS :: Textual t => ShortByteString -> t Source #
Convert from a ShortByteString
to a textual data type
Since: 1.1.0.0
"As" Conversions
These functions are used to convert a textual data type argument to a specific type. Use them to reduce boilerplate in small function definitions.
asS :: forall t a. Textual t => (String -> a) -> t -> a Source #
Convert a textual data type argument to a String
Since: 0.1.0.0
asT :: forall t a. Textual t => (Text -> a) -> t -> a Source #
Convert a textual data type argument to strict Text
Since: 0.1.0.0
asTL :: forall t a. Textual t => (Text -> a) -> t -> a Source #
Convert a textual data type argument to lazy Text
Since: 0.1.0.0
asTLB :: forall t a. Textual t => (Builder -> a) -> t -> a Source #
Convert a textual data type argument to a Text
Builder
Since: 1.1.0.0
asST :: forall t a. Textual t => (ShortText -> a) -> t -> a Source #
Convert a textual data type argument to a ShortText
Since: 1.4.0.0
asBS :: forall t a. Textual t => (ByteString -> a) -> t -> a Source #
Convert a textual data type argument to a strict ByteString
Since: 0.1.0.0
asBSL :: forall t a. Textual t => (ByteString -> a) -> t -> a Source #
Convert a textual data type argument to a lazy ByteString
Since: 0.1.0.0
asBSB :: forall t a. Textual t => (Builder -> a) -> t -> a Source #
Convert a textual data type argument to a ByteString
Builder
Since: 1.1.0.0
asSBS :: forall t a. Textual t => (ShortByteString -> a) -> t -> a Source #
Convert a textual data type argument to a ShortByteString
Since: 1.1.0.0
Render
Render a data type as a textual data type
Use Render
in your business logic, and only use Show
for debugging, as
use of Show
instances in business logic is a common source of bugs.
When defining an instance, render to the textual data type that is most
natural for the data type, and then use convert
to handle the conversion
to any textual data type. This is particularly wrappers around a textual
data type. Example:
newtype Username = Username { usernameText :: Text } instance TTC.Render Username where render = TTC.convert . usernameText
To use render
in a context where the types are ambiguous, use the
TypeApplications
GHC extension to specify one or both types. Example:
-- Render to Text
render _
Text foo
Alternatively, use one of the functions that render to a specific textual
data type (such as renderS
). Using these functions may make code easier
to understand even in cases where the types are not ambiguous.
See the uname
and prompt
example programs in the ttc-examples
directory of the source repository.
For more details, see the following article: https://www.extrema.is/articles/ttc-textual-type-classes/render-and-parse
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. Use newtype
wrappers instead.
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 the Template Haskell functions documented below can be used to load
these definitions with minimal boilerplate.
Since: 0.1.0.0
Minimal complete definition
Nothing
Methods
render :: Textual t => a -> t Source #
Render a data type as a textual data type
Since: 0.1.0.0
default render :: (RenderDefault a, Textual t) => a -> t Source #
Instances
Render WrapperBS Source # | |
Render WrapperBSB Source # | |
Defined in Data.TTC.Wrapper Methods render :: Textual t => WrapperBSB -> t Source # | |
Render WrapperBSL Source # | |
Defined in Data.TTC.Wrapper Methods render :: Textual t => WrapperBSL -> t Source # | |
Render WrapperS Source # | |
Render WrapperSBS Source # | |
Defined in Data.TTC.Wrapper Methods render :: Textual t => WrapperSBS -> t Source # | |
Render WrapperST Source # | |
Render WrapperT Source # | |
Render WrapperTL Source # | |
Render WrapperTLB Source # | |
Defined in Data.TTC.Wrapper Methods render :: Textual t => WrapperTLB -> t Source # |
class RenderDefault a where Source #
Default Render
instances for some common types
- The
Bool
instance renders using theShow
instance. This instance was added in version 1.5.0.0. - The
Char
instance renders a single-character string. - Numeric type instances all render using the
Show
instance. - Textual data type instances all convert to the target textual data type.
Since: 1.1.0.0
Methods
renderDefault :: Textual t => a -> t Source #
Render a data type as a textual data type
Since: 1.1.0.0
Instances
RenderDefault Int16 Source # | |
RenderDefault Int32 Source # | |
RenderDefault Int64 Source # | |
RenderDefault Int8 Source # | |
RenderDefault Word16 Source # | |
RenderDefault Word32 Source # | |
RenderDefault Word64 Source # | |
RenderDefault Word8 Source # | |
RenderDefault Builder Source # | |
RenderDefault ByteString Source # | |
Defined in Data.TTC Methods renderDefault :: Textual t => ByteString -> t Source # | |
RenderDefault ByteString Source # | |
Defined in Data.TTC Methods renderDefault :: Textual t => ByteString -> t Source # | |
RenderDefault ShortByteString Source # | |
Defined in Data.TTC Methods renderDefault :: Textual t => ShortByteString -> t Source # | |
RenderDefault Text Source # | |
RenderDefault Builder Source # | |
RenderDefault Text Source # | |
RenderDefault ShortText Source # | |
RenderDefault String Source # | |
RenderDefault Integer Source # | |
RenderDefault Bool Source # | |
RenderDefault Char Source # | |
RenderDefault Double Source # | |
RenderDefault Float Source # | |
RenderDefault Int Source # | |
RenderDefault Word Source # | |
Render Utility Functions
These functions are used to implement Render
instances.
renderWithShow :: forall t a. (Show a, Textual t) => a -> t Source #
Render a value to a textual data type using a Show
instance
To use this function in a context where the types are ambiguous, use the
TypeApplications
GHC extension to specify one or both types. Example:
-- Render to Text renderWithShow @Text foo
See the enum
example program in the ttc-examples
directory of the
source repository.
Since: 0.1.0.0
Rendering Specific Types
These functions are equivalent to render
, but they specify the textual
data type being rendered to. Use them to avoid having to write type
annotations in cases where the type is ambiguous. Using these functions
may make code easier to understand even in cases where the types are not
ambiguous.
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
renderSBS :: Render a => a -> ShortByteString Source #
Render to a ShortByteString
Since: 0.4.0.0
Parse
Parse a data type from a textual data type
Unlike Read
, Parse
allows you to specify meaningful error messages.
When defining an instance, first convert the textual data type to the
textual data type that is most natural for the data type. The as
functions (such as asS
) provide a convenient way to do this. Note that
error is also a textual data type. The withError
and prefixError
functions can be used to reduce boilerplate. Example:
newtype Username = Username { usernameText :: Text } instance TTC.Parse Username where parse = TTC.asT $ t -> TTC.prefixErrorS "invalid username: " $ do unless (T.all isAsciiLower t) $ Left "not only lowercase ASCII letters" let len = T.length t when (len < 3) $ Left "fewer than 3 characters" when (len > 12) $ Left "more than 12 characters" pure $ Username t
To use parse
in a context where the types are ambiguous, use the
TypeApplications
GHC extension to specify one or more types. Example:
-- Parse from Text parse_
Text foo -- Parse using String errors parse_
_String foo -- Parse from Text using String errors parse
_Text
String foo
Alternatively, use one of the functions that parse from a specific textual
data type (such as renderS
). Using these functions may make code easier
to understand even in cases where the types are not ambiguous.
See the uname
and prompt
example programs in the ttc-examples
directory of the source repository.
For more details, see the following article: https://www.extrema.is/articles/ttc-textual-type-classes/render-and-parse
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. Use newtype
wrappers instead.
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 the Template Haskell functions documented below can be used to load
these definitions with minimal boilerplate.
Since: 0.3.0.0
Minimal complete definition
Nothing
Methods
parse :: (Textual t, Textual e) => t -> Either e a Source #
Parse a data type from a textual data type
Since: 0.3.0.0
Instances
Parse WrapperBS Source # | |
Parse WrapperBSB Source # | |
Defined in Data.TTC.Wrapper | |
Parse WrapperBSL Source # | |
Defined in Data.TTC.Wrapper | |
Parse WrapperS Source # | |
Parse WrapperSBS Source # | |
Defined in Data.TTC.Wrapper | |
Parse WrapperST Source # | |
Parse WrapperT Source # | |
Parse WrapperTL Source # | |
Parse WrapperTLB Source # | |
Defined in Data.TTC.Wrapper |
class ParseDefault a where Source #
The ParseDefault
type class provides some default Parse
instances.
- The
Bool
instance parses using theRead
instance. This instance was added in version 1.5.0.0. - The
Char
instance parses single-character strings. - Numeric type instances all parse using the
Read
instance. - Textual data 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 #
Parse a data type from a textual data type
Since: 1.1.0.0
Instances
Parse Utility Functions
These functions are used to implement Parse
instances.
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.
withErrorBS :: forall e a. 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 :: forall e a. 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
withErrorSBS :: forall e a. 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 :: forall e' e a. (Monoid e', Textual e', Textual e) => e' -> Either e' a -> Either e a Source #
prefixErrorBS :: forall e a. 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 :: forall e a. 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
prefixErrorSBS :: forall e a. 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
Read
Parsing
Arguments
:: forall t e a. (Read a, Textual t) | |
=> e | invalid input error |
-> t | textual input to parse |
-> Either e a | error or parsed value |
Parse a value using a Read
instance
Since: 0.1.0.0
Arguments
:: forall t e a. (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 a Read
instance with default error messages
The following English error message is returned:
- "invalid {name}" when the parse fails
Since: 0.3.0.0
Enum
Parsing
Arguments
:: forall t e a. (Bounded a, Enum a, Render a, Textual t) | |
=> Bool | case-insensitive when |
-> Bool | accept unique prefixes when |
-> 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
The Render
instance determines the textual values to parse from.
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 ttc-examples
directory of the
source repository.
Since: 0.1.0.0
Arguments
:: forall t e a. (Bounded a, Enum a, Render a, Textual t, Textual e) | |
=> String | name to include in error messages |
-> Bool | case-insensitive when |
-> Bool | accept unique prefixes when |
-> t | textual input to parse |
-> Either e a | error or parsed value |
Parse a value in an enumeration using default error messages
The Render
instance determines the textual values to parse from.
The following English error messages are returned:
- "invalid {name}" when there are no matches
- "ambiguous {name}" when there is more than one match
This function is intended to be used with types that have few choices, as the implementation uses a linear algorithm.
Since: 0.4.0.0
Parsing From Specific Types
These functions are equivalent to parse
, but they specify the textual
data type being parsed from. Use them to avoid having to write type
annotations in cases where the type is ambiguous. Using these functions
may make code easier to understand even in cases where the types are not
ambiguous.
parseS :: forall e a. (Parse a, Textual e) => String -> Either e a Source #
Parse from a String
Since: 0.3.0.0
parseT :: forall e a. (Parse a, Textual e) => Text -> Either e a Source #
Parse from strict Text
Since: 0.3.0.0
parseTL :: forall e a. (Parse a, Textual e) => Text -> Either e a Source #
Parse from lazy Text
Since: 0.3.0.0
parseTLB :: forall e a. (Parse a, Textual e) => Builder -> Either e a Source #
Parse from a Text
Builder
Since: 1.1.0.0
parseST :: forall e a. (Parse a, Textual e) => ShortText -> Either e a Source #
Parse from a ShortText
Since: 1.4.0.0
parseBS :: forall e a. (Parse a, Textual e) => ByteString -> Either e a Source #
Parse from a strict ByteString
Since: 0.3.0.0
parseBSL :: forall e a. (Parse a, Textual e) => ByteString -> Either e a Source #
Parse from a lazy ByteString
Since: 0.3.0.0
parseBSB :: forall e a. (Parse a, Textual e) => Builder -> Either e a Source #
Parse from a ByteString
Builder
Since: 1.1.0.0
parseSBS :: forall e a. (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
result instead of an Either
result.
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. Using these functions
may make code easier to understand even in cases where the types are not
ambiguous.
parseMaybe :: forall t a. (Parse a, Textual t) => t -> Maybe a Source #
Parse to a Maybe
result
Since: 0.3.0.0
parseMaybeBS :: Parse a => ByteString -> Maybe a Source #
Parse from a strict ByteString
to a Maybe
result
Since: 0.3.0.0
parseMaybeBSL :: Parse a => ByteString -> Maybe a Source #
Parse from a lazy ByteString
to a Maybe
result
Since: 0.3.0.0
parseMaybeSBS :: Parse a => ShortByteString -> Maybe a Source #
Parse from a ShortByteString
to a Maybe
result
Since: 1.1.0.0
MonadFail
Parsing
The parseOrFail
function fails using MonadFail
on error instead of
using an Either
result.
The rest of the functions are equivalent to parseOrFail
, but they specify
the type being parsed from. Use them to avoid having to write type
annotations in cases where the type is ambiguous. Using these functions
may make code easier to understand even in cases where the types are not
ambiguous.
parseOrFail :: forall t a m. (MonadFail m, Parse a, Textual t) => t -> m a Source #
Parse or fail using MonadFail
Since: 1.3.0.0
parseOrFailBS :: forall a m. (MonadFail m, Parse a) => ByteString -> m a Source #
Parse from a strict ByteString
or fail using MonadFail
Since: 1.3.0.0
parseOrFailBSL :: forall a m. (MonadFail m, Parse a) => ByteString -> m a Source #
Parse from a lazy ByteString
or fail using MonadFail
Since: 1.3.0.0
parseOrFailSBS :: forall a m. (MonadFail m, Parse a) => ShortByteString -> m a Source #
Parse from a ShortByteString
or fail using MonadFail
Since: 1.3.0.0
Unsafe Parsing
The parseUnsafe
function raises an exception on error instead of using an
Either
result. 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. Using these functions
may make code easier to understand even in cases where the types are not
ambiguous.
parseUnsafe :: forall t a. (HasCallStack, Parse a, Textual t) => t -> a Source #
Parse or raise an exception
Since: 0.1.0.0
parseUnsafeS :: (HasCallStack, Parse a) => String -> a Source #
Parse from a String
or raise an exception
Since: 0.1.0.0
parseUnsafeT :: (HasCallStack, Parse a) => Text -> a Source #
Parse from strict Text
or raise an exception
Since: 0.1.0.0
parseUnsafeTL :: (HasCallStack, Parse a) => Text -> a Source #
Parse from lazy Text
or raise an exception
Since: 0.1.0.0
parseUnsafeTLB :: (HasCallStack, Parse a) => Builder -> a Source #
Parse from a Text
Builder
or raise an exception
Since: 1.1.0.0
parseUnsafeST :: (HasCallStack, Parse a) => ShortText -> a Source #
Parse from a ShortText
or raise an exception
Since: 1.4.0.0
parseUnsafeBS :: (HasCallStack, Parse a) => ByteString -> a Source #
Parse from a strict ByteString
or raise an exception
Since: 0.1.0.0
parseUnsafeBSL :: (HasCallStack, Parse a) => ByteString -> a Source #
Parse from a lazy ByteString
or raise an exception
Since: 0.1.0.0
parseUnsafeBSB :: (HasCallStack, Parse a) => Builder -> a Source #
Parse from a ByteString
Builder
or raise an exception
Since: 1.1.0.0
parseUnsafeSBS :: (HasCallStack, Parse a) => ShortByteString -> a Source #
Parse from a ShortByteString
or raise an exception
Since: 1.1.0.0
ReadS
Instances
readsWithParse :: Parse a => ReadS a Source #
Template Haskell
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
and invalid
example programs in the ttc-examples
directory of the
source repository. 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 ttc-examples
directory of the source repository.
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 ttc-examples
directory of the source repository.
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 ttc-examples
directory of the
source repository. 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 ttc-examples
directory of the
source repository. 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 mkuvalidqq
example program in the ttc-examples
directory of the
source repository. The following is example usage from the mkuvalidqq
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
Default Instances
These Template Haskell functions provide an easy way to load default
Render
and Parse
instances for common types. See the documentation for
Render
and Parse
for details about default instances. Remember that
loading such default instances should be avoided in libraries.
defaultRenderInstance :: Name -> DecsQ Source #
defaultRenderInstances :: [Name] -> DecsQ Source #
Load the default Render
instances for any number of types
Example:
TTC.defaultRenderInstances [''Int, ''Int8, ''Int16, ''Int32, ''Int64]
Since: 1.5.0.0
defaultParseInstance :: Name -> DecsQ Source #
defaultParseInstances :: [Name] -> DecsQ Source #
Load the default Parse
instances for any number of types
Example:
TTC.defaultParseInstances [''Int, ''Int8, ''Int16, ''Int32, ''Int64]
Since: 1.5.0.0
defaultRenderAndParseInstances :: [Name] -> DecsQ Source #
Orphan instances
(MonadFail m, Quote m, Parse a, Lift a) => IsString (Code m a) Source # | This instance enables use of 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 instance in GHC 9 or later is as follows: (MonadFail m, THS.Quote m, Parse a, THS.Lift a) => IsString (THS.Code m a) The type of this instance in previous versions of GHC is as follows: (Parse a, THS.Lift a) => IsString (TH.Q (TH.TExp a)) This functionality can be used as follows in all supported versions of GHC.
The following is example usage from the sample2 :: Username sample2 = $$("alice") The parenthesis are not required from GHC 9. The following is example
usage from the sample2 :: Username sample2 = $$"alice" Since: 1.3.0.0 |
Methods fromString :: String -> Code m a # |