ttc: Textual Type Classes

[ data, library, mit, text ] [ Propose Tags ]

This library provides type classes for conversion between data types and textual data types (strings). Please see the README on GitHub at https://github.com/ExtremaIS/ttc-haskell#readme.


[Skip to Readme]

Modules

[Index] [Quick Jump]

Flags

Automatic Flags
NameDescriptionDefault
write-hie

write .hie files

Disabled

Use -f <flag> to enable a flag, or -f -<flag> to disable that flag. More info

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

  • No Candidates
Versions [RSS] 0.1.0.0, 0.1.0.1, 0.2.0.0, 0.2.1.0, 0.2.2.0, 0.2.3.0, 0.3.0.0, 0.4.0.0, 1.0.0.0, 1.1.0.0, 1.1.0.1, 1.1.0.2, 1.1.1.0, 1.1.1.1, 1.2.0.0, 1.2.1.0, 1.3.0.0, 1.4.0.0
Change log CHANGELOG.md
Dependencies base (>=4.7 && <5), bytestring (>=0.10.8 && <0.12), template-haskell (>=2.12 && <2.19), text (>=1.2.3 && <2.1) [details]
License MIT
Copyright Copyright (c) 2019-2021 Travis Cardwell
Author Travis Cardwell <travis.cardwell@extrema.is>
Maintainer Travis Cardwell <travis.cardwell@extrema.is>
Category Data, Text
Home page https://github.com/ExtremaIS/ttc-haskell#readme
Bug tracker https://github.com/ExtremaIS/ttc-haskell/issues
Source repo head: git clone https://github.com/ExtremaIS/ttc-haskell.git
Uploaded by TravisCardwell at 2021-12-25T05:35:26Z
Distributions LTSHaskell:1.4.0.0, NixOS:1.4.0.0, Stackage:1.4.0.0
Reverse Dependencies 2 direct, 0 indirect [details]
Downloads 3890 total (76 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2021-12-25 [all 1 reports]

Readme for ttc-1.1.1.0

[back to package description]

TTC: Textual Type Classes

Project Status: Active – The project has reached a stable, usable state and is being actively developed. GitHub CI Hackage Stackage LTS Stackage Nightly

Overview

TTC, an initialism of Textual Type Classes, is a library that provides Render and Parse type classes for conversion between data types and textual data types (strings). Use the Show and Read type classes for debugging/development, and use the Render and Parse type classes for your own purposes. The library also provides a Textual type class for conversion between textual data types as well as functions for validating constants at compile-time.

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.

Render and Parse are best used with types that have canonical textual representations, such as textual identifiers. When there is more than one way to create a textual representation, such as configurable formatting, using a normal function is probably more appropriate. Such a function can make use of the Textual type class to support multiple textual data types.

This overview includes a brief introduction of the library. The following resources are also available:

Textual

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

  • String
  • Strict Text
  • Lazy Text
  • Text Builder
  • Strict ByteString
  • Lazy ByteString
  • ByteString Builder (and Data.Binary.Builder)
  • ShortByteString

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.

For more details, see the Textual Type Class article.

Render

The Render type class renders a data type as a Textual data type:

class Render a where
  render :: Textual t => a -> t

It is analogous to the Show type class, which can be reserved for debugging/development.

The render function returns any of the supported textual data types. Use the textual data type that is most natural in the implementation of render instances, and return values are converted to other textual data types when necessary. The Show and IsString type classes are not used, so use of the String type is not required.

As a simple example, consider a Username type that is implemented as a newtype over Text:

module Username (Username) where

import Control.Monad (unless, when)
import Data.Char (isAsciiLower)
import qualified Data.Text as T
import Data.Text (Text)
import qualified Data.TTC as TTC

newtype Username = Username Text
  deriving (Eq, Ord, Show)

instance TTC.Render Username where
  render (Username t) = TTC.convert t

If a username needs to be included in a String error message, conversion is automatic:

putStrLn $ "user not found: " ++ TTC.render uname

For more details, see the Render and Parse article.

Parse

The Parse type class parses a data type from a Textual data type:

class Parse a where
  parse :: (Textual t, Textual e) => t -> Either e a

It is analogous to the Read type class, which can be reserved for debugging/development.

The parse function takes any of the supported textual data types as an argument. Use the textual data type that is most natural in the implementation of parse instances, and arguments are converted from other textual data types when necessary. The IsString type class is not used, so use of the String type is not required.

Here is an example instance for Username, implementing some restrictions:

instance TTC.Parse Username where
  parse = TTC.asT $ \t -> first TTC.fromS $ do
    unless (T.all isAsciiLower t) $ Left "username has invalid character(s)"
    let len = T.length t
    when (len < 3) $ Left "username has fewer than 3 characters"
    when (len > 12) $ Left "username has more than 12 characters"
    pure $ Username t

If a username needs to be parsed from a String, conversion is automatic:

case TTC.parse "tcard" :: Either String Username of
  Right uname -> putStrLn $ "valid username: " ++ TTC.render uname
  Left err -> putStrLn $ "invalid username: " ++ err

For more details, see the Render and Parse article.

Constant Validation

TTC provides functions to validate constants at compile-time, using Template Haskell. For example, a Username constant can be defined as follows:

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

For more details, see the Validated Constants article.

Rendering and Parsing

The relude library has polymorphic versions of show and readEither in Relude.String.Conversion, as well as various type classes for converting between string types. This does not encourage using Show and Read instances with syntactically valid Haskell syntax, and it encourages the using of the String data type.

The rio library has a Display type class with a similar goal as TTC.Render. Since the library encourages a uniform usage of textual data types, Display only provides functions for rendering to Text and a builder format. It does not have a type class similar to TTC.Parse.

The text-display library defines a Display type class intended to render user-facing text. It uses a Builder type internally and renders to a Text value.

Harry Garrood has an interesting series of blog posts about type classes and Show:

Validating Constants

The qq-literals library creates a QuasiQuoter from a parse function of type String -> Either String a. The functionality is similar to TTC's mkUntypedValidQQ function. The mkUntypedValidQQ function allows the user to choose the name of the QuasiQuoter because a name like valid is preferred when used via a qualified import while a name like username may be preferred when not using qualified imports. Note that mkUntypedValidQQ also splices in an explicit type signature.

The validated-literals library has a Validate type class that is similar to TTC.Parse but supports conversion between arbitrary types, not just from textual data types. Template Haskell functions are provided to perform validation at compile-time. Result types must either have Lift instances or equivalent implementations.

Chris Done posted a gist about implementing statically checked overloaded strings.

String Type Conversion

There are a number of libraries that simplify conversion between string types.

The following libraries provide type classes with two type variables. The primary benefit of this approach is that one can add support for any string type. The drawback of this approach is that implementations of Render and Parse using such a type class would have to be done via a fixed type, resulting in unnecessary conversion when using other types.

The following library provide type classes with a single type variable, but conversion is done via a fixed type.

  • hxt-regex-xmlschema has a StringLike type class and does conversion via the String type
  • ListLike has a StringLike type class and does conversion via the String type
  • monoid-subclasses provides a TextualMonoid type class that provides an abstract API over textual types, using String as the underlying type
  • stringlike converts via the Text type
  • tagsoup has a StringLike type class that provides an abstract API over textual types and a castString function that converts via the String type
  • text-conversions converts via the Text type
  • textual (deprecated) converts via the String type

Arbitrary Type Conversion

There are also a number of libraries that provide type classes for conversion between arbitrary types, including string types.

  • basement provides type classes for conversion that may fail as well as conversion that cannot fail
  • convertible
  • witch provides type classes for conversion that may fail as well as conversion that cannot fail

Project

Dependencies

Dependency version bounds are strictly specified according to what versions have been tested. If upper bounds need to be bumped when a new package is released or the package has been tested with earlier versions, feel free to submit an issue.

Releases

All releases are tagged in the main branch. Release tags are signed using the security@extrema.is GPG key.

Contribution

Issues and feature requests are tracked on GitHub: https://github.com/ExtremaIS/ttc-haskell/issues

Issues may also be submitted via email to bugs@extrema.is.

License

This project is released under the MIT License as specified in the LICENSE file.