| Copyright | (C) 2015-2019 Merijn Verstraaten |
|---|---|
| License | BSD-style (see the file LICENSE) |
| Maintainer | Merijn Verstraaten <merijn@inconsistent.nl> |
| Stability | experimental |
| Portability | portable |
| Safe Haskell | None |
| Language | Haskell2010 |
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
- class Validate a b where
- data ValidationFailure = ValidationFailure String
- valid :: forall a b. Validate a b => a -> Q (TExp b)
- validInteger :: Validate Integer b => Integer -> Q (TExp b)
- validRational :: Validate Rational b => Rational -> Q (TExp b)
- validString :: Validate String b => String -> Q (TExp b)
- validList :: Validate [a] b => [a] -> Q (TExp b)
- class Lift t where
Documentation
class Validate a b where Source #
Class for validated, compile-time, partial conversions from type a to
b.
Minimal complete definition
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 -> Q (TExp 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.
liftResult :: Lift b => Proxy a -> b -> Q (TExp 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.
data ValidationFailure Source #
Exception type for failed conversions. Useful for testing and more
gracefully handling compile time failures.
Constructors
| ValidationFailure String |
Instances
| Show ValidationFailure Source # | |
Methods showsPrec :: Int -> ValidationFailure -> ShowS # show :: ValidationFailure -> String # showList :: [ValidationFailure] -> ShowS # | |
| Exception ValidationFailure Source # | |
Methods toException :: ValidationFailure -> SomeException # | |
valid :: forall a b. Validate a b => a -> Q (TExp 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')
validRational :: Validate Rational b => Rational -> Q (TExp 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 -> Q (TExp b) Source #
Same as validInteger, but for when enabling OverloadedStrings makes
String literals polymorphic.
validList :: Validate [a] b => [a] -> Q (TExp b) Source #
Same as validInteger, but for when enabling OverloadedLists makes list
literals polymorphic.
Re-export from Language.Haskell.TH.Syntax
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 ([| ... |]) but not
at the top level. As an example:
add1 :: Int -> Q Exp 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 for all x, where $(...)
is a Template Haskell splice.
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 LiftMethods
Turn a value into a Template Haskell expression, suitable for use in a splice.
Instances
| Lift Bool | |
| Lift Char | |
| Lift Double | |
| Lift Float | |
| Lift Int | |
| Lift Int8 | |
| Lift Int16 | |
| Lift Int32 | |
| Lift Int64 | |
| Lift Integer | |
| Lift Natural | |
| Lift Word | |
| Lift Word8 | |
| Lift Word16 | |
| Lift Word32 | |
| Lift Word64 | |
| Lift () | |
| Lift a => Lift [a] | |
| Lift a => Lift (Maybe a) | |
| Integral a => Lift (Ratio a) | |
| (Lift a, Lift b) => Lift (Either a b) | |
| (Lift a, Lift b) => Lift (a, b) | |
| (Lift a, Lift b, Lift c) => Lift (a, b, c) | |
| (Lift a, Lift b, Lift c, Lift d) => Lift (a, b, c, d) | |
| (Lift a, Lift b, Lift c, Lift d, Lift e) => Lift (a, b, c, d, e) | |
| (Lift a, Lift b, Lift c, Lift d, Lift e, Lift f) => Lift (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) | |