Skip to main content

Validated Constants

As described in Render and Parse, the Parse type class provides a way to parse Textual data types. Unlike Read, it supports returning error messages. TTC provides various functions that use this functionality to validate constants at compile-time, using Template Haskell. All of these functions are used for compile-time constant validation, but each one has different benefits and drawbacks. Choose which one to use based on your project requirements.

Validation Using Typed Expressions

These validation functions make use of Template Haskell typed expressions. Unfortunately, some Haskell tools still do not support typed expressions. If this is a problem in your development environment, functions for validation using untyped expressions are also provided.

valid

The quintessential constant validation function is valid. It is used as follows:

name :: Name
name = $$(TTC.valid "Bill")

The Parse instance of the Name type is used to parse the string within the splice. When parsing results in an error (Left), compilation fails with the error message. When the string is parsed successfully (Right), the Name value is assigned to name.

The type signature of valid is different for different versions of GHC. The type signature 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 signature in older versions of GHC is as follows:

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

As specified in the type signatures, the type being parsed must have a Lift instance. In cases where you are unable to create a Lift instance for your type, consider using mkValid or validOf instead.

validOf

The validOf function provides a way to validate constants of types without a Lift instance using typed expressions. It works by parsing the string twice. First, it parses the string during compile-time. When parsing results in an error (Left), compilation fails with the error message. When the string is parsed successfully (Right), an expression that parses the string again, assuming that it is valid, is assigned to name. When the constant is first used at runtime, that expression is evaluated, parsing the string again.

Unfortunately, the type signature is not sufficient to specify the type when using this method. A Proxy must be passed, as in the following example:

name :: Name
name = $$(TTC.validOf (Proxy :: Proxy Name) "Bill")

The type signature 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 signature in older versions of GHC is as follows:

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

mkValid

Passing a Proxy in every use of validOf can result in quite a bit of boilerplate. The mkValid function is a Template Haskell function that creates a validation function for a specific type using validOf. The type signature of this function is as follows:

mkValid :: String -> Name -> DecsQ

For example, a type module that is used with a qualified import can declare a valid function for that type, as follows:

{-# LANGUAGE TemplateHaskell #-}

module Example.Name
  ( Name
  , valid
  ) where

import Control.Monad (unless)
import Data.Char (isPrint)
import qualified Data.Text as T
import Data.Text (Text)
import qualified Data.TTC as TTC

newtype Name = Name Text

instance TTC.Parse Name where
  parse = TTC.asT $ \t -> do
    unless (T.all isPrint t) . Left $
      TTC.fromS "invalid Name: contains invalid characters"
    pure $ Name t

instance TTC.Render Name where
  render (Name name) = TTC.fromT name

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

The first argument is the name of the function to create, and the second argument is the type. The type signature of the created function is different for different versions of GHC. In GHC 9 or later, the type signature of the valid function created in the example above is as follows:

valid
  :: forall m. (MonadFail m, THS.Quote m)
  => String
  -> THS.Code m Name

The type signature in older versions of GHC is as follows:

valid
  :: String
  -> TH.Q (TH.TExp Name)

When the type module is imported qualified, the created function can be used as follows:

name :: Name
name = $$(Name.valid "Bill")

This is a concise way to declare validated constants using typed expressions for types without a Lift instance.

Validation Using Untyped Expressions

The following validation functions make use of Template Haskell untyped expressions. They are useful if you rely on tools that do not yet support typed expressions.

When using untyped expressions, it is up to the developer to make sure that the type signature of a constant matches the type used by the validation function.

untypedValidOf

The untypedValidOf function is a version of validOf that uses untyped expressions. It works in the same way, by parsing the string at compile-time to validate it and then parsing the same string again at runtime when valid. The type signature is as follows:

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

As with untypedValidOf, a Proxy must be passed to specify the type, as shown in the following example:

name :: Name
name = $(TTC.untypedValidOf (Proxy :: Proxy Name) "Bill")

mkUntypedValidOf

The mkUntypedValidOf function is a Template Haskell function that creates a validation function for a specific type using untypedValidOf. The type signature of this function is as follows:

mkUntypedValid :: String -> Name -> DecsQ

It has the same type signature as mkValid but creates a function that uses untyped expressions instead of typed expressions. The function is used as follows:

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

The type signature of the valid function created is as follows:

valid :: String -> TH.ExpQ

When the type module is imported qualified, the created function can be used as follows:

name :: Name
name = $(Name.valid "Bill")

mkUntypedValidQQ

The mkUntypedValidQQ function works the same as mkUntypedValidOf except that it creates a quasi-quote function instead of a splice function. The type signature of this function is the same:

mkUntypedValidQQ :: String -> Name -> DecsQ

The function is used as follows:

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

When the type module is imported qualified, the created function can be used as follows:

name :: Name
name = [Name.valid|Bill|]

Use of this function is a matter of taste. It does not provide any benefits over mkUntypedValidOf.