validated-literals-0.3.1: Compile-time checking for partial smart-constructors
Copyright(C) 2015-2021 Merijn Verstraaten
LicenseBSD-style (see the file LICENSE)
MaintainerMerijn Verstraaten <merijn@inconsistent.nl>
Stabilityexperimental
Portabilityportable
Safe HaskellNone
LanguageHaskell2010

ValidLiterals

Description

To disallow invalid input it is common to define (new)types with hidden data constructors. Forcing the user to go through a smart-constructor that enforces invariants and returns Maybe ResultType, preventing the construction of data with invalid values.

However, it is also common to want to include literal values of such types in source text. Things of textual literals for HTML, HTTP, etc. In such cases smart-constructors force us to handle potential conversion failures at runtime, or abusing functions like fromJust to break away all the safety smart-constructors provide. All this despite the fact that we can statically know at compile time that the conversion will always succeed or always fails.

This package provides a typeclasses for using TH to validate the correctness of provided literals at compile. This lets you define, e.g., newtype Even = Even Integer and write:

x :: Even
x = $$(valid 38)

This will check, at compile time, that the provided Integer is, in fact, even and unwrap it from Maybe, avoiding the runtime check.

Synopsis

Documentation

class Validate a b where Source #

Class for validated, compile-time, partial conversions from type a to b.

Minimal complete definition

fromLiteralWithError | fromLiteral

Methods

fromLiteralWithError :: a -> Either String b Source #

Converts a values into validated b values, Left values are reported in the compilation error.

fromLiteral :: a -> Maybe b Source #

Converts a values into validated b values, Nothing values produce a generic error message. Use fromLiteralWithError for custom error messages.

liftResult :: Proxy a -> b -> Splice Q b Source #

Creates a Typed TH splice for the resulting b values, useful for avoiding the need for orphan Lift instances and allowing complex splices for types that can't be directly lifted. See the ByteString example module for an example.

default liftResult :: Lift b => Proxy a -> b -> Splice Q b Source #

data ValidationFailure Source #

Exception type for failed conversions. Useful for testing and more gracefully handling compile time failures.

valid :: forall a b. Validate a b => a -> Splice Q b Source #

The core function of ValidLiterals, use this together with Typed Template Haskell splices to insert validated literals into your code. For example, if we assume newtype ASCII = ASCII Char where ASCII should only contain ASCII characters, we would write:

Polymorphic literals, such as numbers (or strings when OverloadedStrings is enabled) can result in ambiguous type errors with this function. Enabing the ExtendedDefaultRules extension will allow inputs to valid to be defaulted to Integer or Double allowing code to compile. A more robust solution is to use the various explicitly defaulted functions in this module, such as validInteger.

{-# LANGUAGE TemplateHaskell #-}

import ValidLiterals

x :: ASCII
x = $$(valid 'c')

validInteger :: Validate Integer b => Integer -> Splice Q b Source #

Integer literals lead to obnoxious defaulting complaints by GHC, by using this function you can force the defaulting to Integer, silencing these warnings.

Since Integral literals use fromInteger :: Num a => Integer -> a this function cannot cost you any precision.

validRational :: Validate Rational b => Rational -> Splice Q b Source #

Same as validInteger, but for Fractional values.

Since Fractional literals use fromRational :: Fractional a => Rational -> a this function cannot cost you any precision.

validString :: Validate String b => String -> Splice Q b Source #

Same as validInteger, but for when enabling OverloadedStrings makes String literals polymorphic.

validList :: Validate [a] b => [a] -> Splice Q b Source #

Same as validInteger, but for when enabling OverloadedLists makes list literals polymorphic.

Re-export from Language.Haskell.TH.Syntax

class Lift (t :: TYPE r) where #

A Lift instance can have any of its values turned into a Template Haskell expression. This is needed when a value used within a Template Haskell quotation is bound outside the Oxford brackets ([| ... |] or [|| ... ||]) but not at the top level. As an example:

add1 :: Int -> Q (TExp Int)
add1 x = [|| x + 1 ||]

Template Haskell has no way of knowing what value x will take on at splice-time, so it requires the type of x to be an instance of Lift.

A Lift instance must satisfy $(lift x) ≡ x and $$(liftTyped x) ≡ x for all x, where $(...) and $$(...) are Template Haskell splices. It is additionally expected that lift x ≡ unTypeQ (liftTyped x).

Lift instances can be derived automatically by use of the -XDeriveLift GHC language extension:

{-# LANGUAGE DeriveLift #-}
module Foo where

import Language.Haskell.TH.Syntax

data Bar a = Bar1 a (Bar a) | Bar2 String
  deriving Lift

Levity-polymorphic since template-haskell-2.16.0.0.

Minimal complete definition

liftTyped

Methods

lift :: t -> Q Exp #

Turn a value into a Template Haskell expression, suitable for use in a splice.

liftTyped :: t -> Q (TExp t) #

Turn a value into a Template Haskell typed expression, suitable for use in a typed splice.

Since: template-haskell-2.16.0.0

Instances

Instances details
Lift Bool 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Bool -> Q Exp #

liftTyped :: Bool -> Q (TExp Bool) #

Lift Char 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Char -> Q Exp #

liftTyped :: Char -> Q (TExp Char) #

Lift Double 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Double -> Q Exp #

liftTyped :: Double -> Q (TExp Double) #

Lift Float 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Float -> Q Exp #

liftTyped :: Float -> Q (TExp Float) #

Lift Int 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int -> Q Exp #

liftTyped :: Int -> Q (TExp Int) #

Lift Int8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int8 -> Q Exp #

liftTyped :: Int8 -> Q (TExp Int8) #

Lift Int16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int16 -> Q Exp #

liftTyped :: Int16 -> Q (TExp Int16) #

Lift Int32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int32 -> Q Exp #

liftTyped :: Int32 -> Q (TExp Int32) #

Lift Int64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int64 -> Q Exp #

liftTyped :: Int64 -> Q (TExp Int64) #

Lift Integer 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Integer -> Q Exp #

liftTyped :: Integer -> Q (TExp Integer) #

Lift Natural 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Natural -> Q Exp #

liftTyped :: Natural -> Q (TExp Natural) #

Lift Word 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word -> Q Exp #

liftTyped :: Word -> Q (TExp Word) #

Lift Word8 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word8 -> Q Exp #

liftTyped :: Word8 -> Q (TExp Word8) #

Lift Word16 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word16 -> Q Exp #

liftTyped :: Word16 -> Q (TExp Word16) #

Lift Word32 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word32 -> Q Exp #

liftTyped :: Word32 -> Q (TExp Word32) #

Lift Word64 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word64 -> Q Exp #

liftTyped :: Word64 -> Q (TExp Word64) #

Lift () 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: () -> Q Exp #

liftTyped :: () -> Q (TExp ()) #

Lift Void

Since: template-haskell-2.15.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Void -> Q Exp #

liftTyped :: Void -> Q (TExp Void) #

Lift Int#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Int# -> Q Exp #

liftTyped :: Int# -> Q (TExp Int#) #

Lift Char#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Char# -> Q Exp #

liftTyped :: Char# -> Q (TExp Char#) #

Lift Word#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Word# -> Q Exp #

liftTyped :: Word# -> Q (TExp Word#) #

Lift Addr#

Produces an Addr# literal from the NUL-terminated C-string starting at the given memory address.

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Addr# -> Q Exp #

liftTyped :: Addr# -> Q (TExp Addr#) #

Lift Float#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Float# -> Q Exp #

liftTyped :: Float# -> Q (TExp Float#) #

Lift Double#

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Double# -> Q Exp #

liftTyped :: Double# -> Q (TExp Double#) #

Lift a => Lift ([a] :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: [a] -> Q Exp #

liftTyped :: [a] -> Q (TExp [a]) #

Lift a => Lift (Maybe a :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Maybe a -> Q Exp #

liftTyped :: Maybe a -> Q (TExp (Maybe a)) #

Integral a => Lift (Ratio a :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Ratio a -> Q Exp #

liftTyped :: Ratio a -> Q (TExp (Ratio a)) #

Lift a => Lift (NonEmpty a :: Type)

Since: template-haskell-2.15.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: NonEmpty a -> Q Exp #

liftTyped :: NonEmpty a -> Q (TExp (NonEmpty a)) #

(Lift a, Lift b) => Lift (Either a b :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: Either a b -> Q Exp #

liftTyped :: Either a b -> Q (TExp (Either a b)) #

(Lift a, Lift b) => Lift ((a, b) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (a, b) -> Q Exp #

liftTyped :: (a, b) -> Q (TExp (a, b)) #

(Lift a, Lift b, Lift c) => Lift ((a, b, c) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (a, b, c) -> Q Exp #

liftTyped :: (a, b, c) -> Q (TExp (a, b, c)) #

(Lift a, Lift b, Lift c, Lift d) => Lift ((a, b, c, d) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (a, b, c, d) -> Q Exp #

liftTyped :: (a, b, c, d) -> Q (TExp (a, b, c, d)) #

(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((a, b, c, d, e) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (a, b, c, d, e) -> Q Exp #

liftTyped :: (a, b, c, d, e) -> Q (TExp (a, b, c, d, e)) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((a, b, c, d, e, f) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (a, b, c, d, e, f) -> Q Exp #

liftTyped :: (a, b, c, d, e, f) -> Q (TExp (a, b, c, d, e, f)) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((a, b, c, d, e, f, g) :: Type) 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (a, b, c, d, e, f, g) -> Q Exp #

liftTyped :: (a, b, c, d, e, f, g) -> Q (TExp (a, b, c, d, e, f, g)) #

Lift (# #)

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# #) -> Q Exp #

liftTyped :: (# #) -> Q (TExp (# #)) #

Lift a => Lift ((# a #) :: TYPE ('TupleRep '['LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a #) -> Q Exp #

liftTyped :: (# a #) -> Q (TExp (# a #)) #

(Lift a, Lift b) => Lift ((# a, b #) :: TYPE ('TupleRep '['LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a, b #) -> Q Exp #

liftTyped :: (# a, b #) -> Q (TExp (# a, b #)) #

(Lift a, Lift b) => Lift ((# a | b #) :: TYPE ('SumRep '['LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a | b #) -> Q Exp #

liftTyped :: (# a | b #) -> Q (TExp (# a | b #)) #

(Lift a, Lift b, Lift c) => Lift ((# a, b, c #) :: TYPE ('TupleRep '['LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a, b, c #) -> Q Exp #

liftTyped :: (# a, b, c #) -> Q (TExp (# a, b, c #)) #

(Lift a, Lift b, Lift c) => Lift ((# a | b | c #) :: TYPE ('SumRep '['LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a | b | c #) -> Q Exp #

liftTyped :: (# a | b | c #) -> Q (TExp (# a | b | c #)) #

(Lift a, Lift b, Lift c, Lift d) => Lift ((# a, b, c, d #) :: TYPE ('TupleRep '['LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a, b, c, d #) -> Q Exp #

liftTyped :: (# a, b, c, d #) -> Q (TExp (# a, b, c, d #)) #

(Lift a, Lift b, Lift c, Lift d) => Lift ((# a | b | c | d #) :: TYPE ('SumRep '['LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a | b | c | d #) -> Q Exp #

liftTyped :: (# a | b | c | d #) -> Q (TExp (# a | b | c | d #)) #

(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((# a, b, c, d, e #) :: TYPE ('TupleRep '['LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a, b, c, d, e #) -> Q Exp #

liftTyped :: (# a, b, c, d, e #) -> Q (TExp (# a, b, c, d, e #)) #

(Lift a, Lift b, Lift c, Lift d, Lift e) => Lift ((# a | b | c | d | e #) :: TYPE ('SumRep '['LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a | b | c | d | e #) -> Q Exp #

liftTyped :: (# a | b | c | d | e #) -> Q (TExp (# a | b | c | d | e #)) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((# a, b, c, d, e, f #) :: TYPE ('TupleRep '['LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a, b, c, d, e, f #) -> Q Exp #

liftTyped :: (# a, b, c, d, e, f #) -> Q (TExp (# a, b, c, d, e, f #)) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift ((# a | b | c | d | e | f #) :: TYPE ('SumRep '['LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a | b | c | d | e | f #) -> Q Exp #

liftTyped :: (# a | b | c | d | e | f #) -> Q (TExp (# a | b | c | d | e | f #)) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((# a, b, c, d, e, f, g #) :: TYPE ('TupleRep '['LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a, b, c, d, e, f, g #) -> Q Exp #

liftTyped :: (# a, b, c, d, e, f, g #) -> Q (TExp (# a, b, c, d, e, f, g #)) #

(Lift a, Lift b, Lift c, Lift d, Lift e, Lift f, Lift g) => Lift ((# a | b | c | d | e | f | g #) :: TYPE ('SumRep '['LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep, 'LiftedRep]))

Since: template-haskell-2.16.0.0

Instance details

Defined in Language.Haskell.TH.Syntax

Methods

lift :: (# a | b | c | d | e | f | g #) -> Q Exp #

liftTyped :: (# a | b | c | d | e | f | g #) -> Q (TExp (# a | b | c | d | e | f | g #)) #