data-validation-0.1.2.5: A library for creating type safe validations.

Safe HaskellSafe
LanguageHaskell2010

Data.Validation

Contents

Synopsis

Basics

Validation generally takes the form of a -> Either f b where:

a
Some unvalidated type.
b
Some validated type.
f
Some failure type.

Consider the following example:

 data MyFailures = EmptyEmailAddress | MalformedEmailAddress
 validateEmailAddress :: String -> Either MyFailures EmailAddress
 

In this case:

  • a ~ String
  • b ~ EmailAddress
  • f ~ MyFailures

Proof

The transformation from a to b is important and provides a type safe way to prove that validation was successful. However, rather than using the Either type, this library uses the Proof type. A Proof represents either a validated type or a collection of failures. Notice, we use the term validation failures instead of errors to differentiate between validation and error handling. The reason we use the Proof type is because it has a custom Applicative instance that will be helpful later.

The Invalid constructor takes a list of global failures and a map of field failures. Field failures are useful for identifying a specific field in a record that is invalid. Fields are identified using a list of Name types. There are two ways to create this type: the TemplateHaskellQuotes extension and the mkName function.

Using the TemplateHaskellQuotes language extension, you can easily create Names using a special syntax. For a records like:

data User = User { emailAddress :: String }

The name can be retrieved by referencing the name with a single quote in front:

let name = 'emailAddress

This allows for the consistant and type safe generation of names. This method does generate a fully qualified name that includes the module name. The base name can be accessed using the nameBase function. This extension is considered safe Haskell while the TemplateHaskell extension is not. See https://ghc.gitlab.haskell.org/ghc/doc/users_guide/exts/template_haskell.html#syntax for details.

Another approach is to use the mkName function. This allows field names to be generated for non-record types. However, it does require managing magic strings.

To finish our discussion on the Proof type, the reason the key is a list of names is because of subfields. Consider a record like this:

 data Contact = Contact { phoneNumber :: String }

 data User
   = User
   { username :: String
   , contact :: Contact
   }
 

In this case, validating the User type requires validating the contact field which is a Contact. In that case, the key would need to identify that the phoneNumber field is a subfield of contact. The key would look like this:

['contact, 'phoneNumber]

data Proof f a Source #

A type that holds either validation failures or a validated value.

Constructors

Valid a

A validated value.

Invalid [f] (Map [Name] [f])

Global and field validation failures.

Instances
Monad (Proof f) Source # 
Instance details

Defined in Data.Validation

Methods

(>>=) :: Proof f a -> (a -> Proof f b) -> Proof f b #

(>>) :: Proof f a -> Proof f b -> Proof f b #

return :: a -> Proof f a #

fail :: String -> Proof f a #

Functor (Proof f) Source # 
Instance details

Defined in Data.Validation

Methods

fmap :: (a -> b) -> Proof f a -> Proof f b #

(<$) :: a -> Proof f b -> Proof f a #

Applicative (Proof f) Source # 
Instance details

Defined in Data.Validation

Methods

pure :: a -> Proof f a #

(<*>) :: Proof f (a -> b) -> Proof f a -> Proof f b #

liftA2 :: (a -> b -> c) -> Proof f a -> Proof f b -> Proof f c #

(*>) :: Proof f a -> Proof f b -> Proof f b #

(<*) :: Proof f a -> Proof f b -> Proof f a #

(Eq a, Eq f) => Eq (Proof f a) Source # 
Instance details

Defined in Data.Validation

Methods

(==) :: Proof f a -> Proof f a -> Bool #

(/=) :: Proof f a -> Proof f a -> Bool #

(Show a, Show f) => Show (Proof f a) Source # 
Instance details

Defined in Data.Validation

Methods

showsPrec :: Int -> Proof f a -> ShowS #

show :: Proof f a -> String #

showList :: [Proof f a] -> ShowS #

Semigroup a => Semigroup (Proof f a) Source # 
Instance details

Defined in Data.Validation

Methods

(<>) :: Proof f a -> Proof f a -> Proof f a #

sconcat :: NonEmpty (Proof f a) -> Proof f a #

stimes :: Integral b => b -> Proof f a -> Proof f a #

Monoid a => Monoid (Proof f a) Source # 
Instance details

Defined in Data.Validation

Methods

mempty :: Proof f a #

mappend :: Proof f a -> Proof f a -> Proof f a #

mconcat :: [Proof f a] -> Proof f a #

fromVCtx :: VCtx f a -> Proof f a Source #

Converts a VCtx to a Proof.

Internally, this library uses the VCtx type to track validation failures. This is because a validation failure can be partial. For instance, checking that a password has a special character can happen even if the check for a numeric character has already failed. This allows validation to discover as many failures as possible.

However, once validation is complete, the result becomes binary. The validation has either succeeded or failed. In order to convert from a VCtx to a Proof, use the fromVCtx function.

ValueCtx

This library uses composable validations. As such, we need a type that carries information about the thing being validated. Specifically, we need a type to carry its value and, optionally, its name.

A value with a name is a field and will be used to create field failures. A value without a name will be used to create global failures. This is accomplished using the ValueCtx type.

The withField and withValue functions are used to create these types and perform validation at the same time. These functions save the effort of wrapping and unwrapping values with the ValueCtx type.

data ValueCtx a Source #

A type for storing a value to validate and, optionally, its field name.

Constructors

Field Name a

The Field constructor represents a value that is named.

Global a

The Global constructor represents a value that is not named.

Instances
Functor ValueCtx Source # 
Instance details

Defined in Data.Validation

Methods

fmap :: (a -> b) -> ValueCtx a -> ValueCtx b #

(<$) :: a -> ValueCtx b -> ValueCtx a #

Eq a => Eq (ValueCtx a) Source # 
Instance details

Defined in Data.Validation

Methods

(==) :: ValueCtx a -> ValueCtx a -> Bool #

(/=) :: ValueCtx a -> ValueCtx a -> Bool #

Show a => Show (ValueCtx a) Source # 
Instance details

Defined in Data.Validation

Methods

showsPrec :: Int -> ValueCtx a -> ShowS #

show :: ValueCtx a -> String #

showList :: [ValueCtx a] -> ShowS #

getValue :: ValueCtx a -> a Source #

Accessor for a ValueCtx's value.

setValue :: ValueCtx a -> b -> ValueCtx b Source #

Replaces the existing value with a new one without changing the name, if one exists.

withField :: Name -> a -> (ValueCtx a -> VCtx f (ValueCtx b)) -> VCtx f b Source #

Performs some given validation using a Field with a given name and value.

withValue :: a -> (ValueCtx a -> VCtx f (ValueCtx b)) -> VCtx f b Source #

Performs some given validation using a Global with a given value.

Validating Primitives

Validating primitives is a special case because the validated type and unvalidated type are often the same. An email address is just a specially formatted string, so both the unvalidated email address and the validated one have the same types. To get around this, you can wrap a primitive in a `newtype`, hide the constructor, and create a smart constructor that validates the input. This allows for a kind of type safety known as `correct by construction`. Consider the following example.

 module Primitives
 ( MyFailures
 , EmailAddress -- the constructors are not exported
 , mkEmailAddress
 ) where

 data MyFailures = EmptyEmail |

 mkEmailAddress :: String -> Proof MyFailures EmailAddress
 mkEmailAddress s = fromVCtx $ do              -- (1)
   v <- withValue s $ \v -> do                 -- (2)
     isNotNull EmptyEmail v                    -- (3)
     disputeWithFact InvalidEmail (elem '@') v -- (4)
   return $ EmailAddress v                     -- (5)
 

Starting with line (2), the withValue function is used to create a ValueCtx using string passed into the function. The lambda function that follows takes the ValueCtx and runs it through several validators using `do` syntax. This is possible because VCtx has a Monad instance.

Line (1) transforms the result from a VCtx to a Proof as discussed above.

Line (3) and (4) demonstrate both a general validator and a custom validator. These will be covered in more detail later.

Line (5) constructs the EmailAddress type and returns it. If any validation failures occur before this point, an Invalid result is generated instead of the EmailAddress.

It is important to note that no instances should be created for the EmailAddress type that allow construction. This includes the FromJSON type class from the aeson library.

Validating Complex Types

In general, validating complex types works the same way as validating primitives. It starts with an unvalidated type that is transformed into a validated type. These unvalidated types are often called "view models". View models should be transformed into models when they are validated. So, like primitives, validating complex types should have the form validate :: a -> Proof f b.

For complex types, this can be accomplished with the 'Validatable f a b' type class. This type class takes 3 parameters: the failure type, the view model type, and the final model type. It requires the implementation of a single function: validation. Then the validate function can be used to perform the actual validation. Consider the following example:

 -- unvalidated type
 data UserCreatableVM
   = UserCreatableVM
   { userCreatableVMEmailAddress         :: String
   , userCreatableVMConfirmEmailAddress  :: String
   , userCreatableVMPassword             :: String
   , userCreatableVMConfirmPassword      :: String
   , userCreatableVMName                 :: Maybe String
   }

 -- validated type
 data UserCreatable
   = UserCreatable                                                                                     -- (1)
   { userCreatableEmailAddress :: EmailAddress
   , userCreatablePassword     :: Password
   , userCreatableName         :: Maybe Name
   }

 instance Validatable MyFailureType UserCreatableVM UserCreatable where                                -- (2)
   validation u =
     let ve = withField 'userCreatableVMEmailAddress (userCreatableVMEmailAddress u) $
           refuteWithProof mkEmailAddress                                                              -- (3)
         vce = withField 'userCreatableVMConfirmEmailAddress (userCreatableVMConfirmEmailAddress u) $
           \ce -> refuteWithProof mkEmailAddress ce
           >>= isMatch MismatchedEmail ve                                                              -- (4)
         vp = withField 'userCreatableVMPassword (userCreatableVMPassword u) $
           refuteWithProof mkPassword
         vcp = withField 'userCreatableVMConfirmPassword (userCreatableVMConfirmPassword u) $
           \ce -> refuteWithProof mkPassword ce
           >>= isMatch MismatchedPassword vp
         vn = optional (userCreatableVMName u) $ \n ->
             withField 'userCreatableVMName n $ refuteWithProof mkName
         otherCheck = withValue u nameNotInPassword
     in pure UserCreatable <*> ve <*> vp <*> vn <! vce <! vcp <! otherCheck                            -- (5)
   where nameNotInPassword = ...
 

The final model does not have all of the same fields on line (1). The confirmation fields were removed because they serve no purpose beyond validation.

The validation function is implemented much like the smart constructors in the previous section. However, it is using the withField function instead of withValue. In addition, there is no call to fromVCtx because validation is expected to return a VCtx. Another function, validate, will use these validations to produce a Proof.

On line (2), the Validatable instance is declared with an application specific failure type. The second and third parameter are the view model and final model types. This represents the transformation from the unvalidated type to the validated types.

On line (3), there is a call to refuteWithProof which validates and constructs a primitive using the smart constructor from the previous example. Line (4) uses the isMatch function to prove that the email address and confirm email address fields match. The function accepts a VCtx to match against making it very easy to compare validated field.

Finally, line (5) is a bit interesting. It constructs the final type using applicative syntax. It uses the applicative instance on VCtx to construct the final type. If all of the parameters are valid, the expression returns a valid UserCreatable. However, if any of the parameters are invalid, the whole expression becomes invalid and contains every failure from every field. This creates the aggregated result.

There is also a call to the '(<!)' function. This function is read as aggregateFailures. In English, it takes the failures from the second parameter, if any, and adds them to the first. This allows the aggregation of failures from fields that are not included in the final type.

class Validatable f a b | a -> f b where Source #

A type class that represents a value that can be validated.

The parameters represent the following:

  • f: the type of validation failures.
  • a: the unvalidated type or view model.
  • b: the validated type.

Methods

validation :: a -> VCtx f b Source #

validate :: Validatable f a b => a -> Proof f b Source #

Runs the validations for a given value and returns the proof.

Dispute and Refute

Refuting a value stops all validation efforts on the value. This means that any future failures that could have been detected will not. Dispute, on the other hand, will allow validation to continue. So, why should one be chosen over the other?

First, we have to look at how validation works. Validation transforms values from an unvalidated type to a validated type. So, when a value is being passed through a validation chain, it is being transformed. If a validation fails, the transform fails too; there is no way around this. The new value cannot be retrieved from the validation if it failed.

Consider a Maybe String value that is required and must be at least 3 characters long. First, the value would pass through the isRequired validator. If the value is a Just a, validation succeeds and the value a is passed to the next validator which checks its length. If the value is a Nothing, it is not possible to check its length. Therefore, the validation must be refuted. A refuted value results in an invalid Proof but stops the execution of any further validation.

Now, consider an Int value that must be greater than 2 and even. First, the value would pass though the minValue validator. If the value is greater than 2, validation succeeds and the isEven validator is called. If the value is 2 or less, the validation fails. However, rather than fail completely, the next validator can just use the same value that was passed into the minValue validator. In that case, the validator should dispute the value so that the next validator can be run. This will still result in an invalid Proof but allows for more failures to be detected.

In general, if a validator has the form a -> Either f b, a failure must be refuted because they transform the value. If it has the form a -> Maybe f, it should be disputed because it does not transform the value.

refute :: ValueCtx a -> f -> VCtx f b Source #

Adds a validation failure to the result and ends validation.

refuteMany :: ValueCtx a -> [f] -> VCtx f b Source #

Adds validation failures to the result and ends validation.

refuteWith :: (a -> Either f b) -> ValueCtx a -> VCtx f (ValueCtx b) Source #

Performs a validation using a given function and handles the result. If the result is `Left f`, a validation failure is added to the result and validation ends. If the result is `Right b`, validation continues with the new value.

refuteWithProof :: (a -> Proof f b) -> ValueCtx a -> VCtx f (ValueCtx b) Source #

Performs a validation using a given function and handles the result. If the result is Invalid, the validation failures are added to the result and validation ends. If the result is `Valid b`, validation continues with the new value.

dispute :: ValueCtx a -> f -> VCtx f (ValueCtx a) Source #

Adds a validation failure to the result and continues validation.

disputeMany :: ValueCtx a -> [f] -> VCtx f (ValueCtx a) Source #

Adds validation failures to the result and continues validation.

disputeWith :: (a -> Maybe f) -> ValueCtx a -> VCtx f (ValueCtx a) Source #

Performs a validation using a given function and handles the result. If the result is `Just f`, a validation failure is added to the result and validation continues. If the result is Nothing, validation continues with no failure.

disputeWithFact :: f -> (a -> Bool) -> ValueCtx a -> VCtx f (ValueCtx a) Source #

Similar to disputeWith except that the given failure is added if the given function returns False.

General Validators

isRequired :: f -> ValueCtx (Maybe a) -> VCtx f (ValueCtx a) Source #

Checks that a Maybe value is a Just. If not, it adds the given failure to the result and validation end.

isRequiredWhen :: f -> Bool -> ValueCtx (Maybe a) -> VCtx f (ValueCtx (Maybe a)) Source #

Checks that a Maybe value is a Just when some condition is true. If the condition is met and the value is Just, it adds the given failure to the result and validation continues.

isRequiredUnless :: f -> Bool -> ValueCtx (Maybe a) -> VCtx f (ValueCtx (Maybe a)) Source #

Checks that a Maybe value is a Just when some condition is false. If the condition is not met and the value is Just, it adds the given failure to the result and validation continues.

isLeft :: f -> ValueCtx (Either a b) -> VCtx f (ValueCtx a) Source #

Checks that a Either value is a Left. If not, it adds the given failure to the result and validation end.

isRight :: f -> ValueCtx (Either a b) -> VCtx f (ValueCtx b) Source #

Checks that a Either value is a Right. If not, it adds the given failure to the result and validation end.

isNull :: Foldable t => f -> ValueCtx (t a) -> VCtx f (ValueCtx (t a)) Source #

Checks that the Foldable is empty. If not, it adds the given failure to the result and validation continues.

isNotNull :: Foldable t => f -> ValueCtx (t a) -> VCtx f (ValueCtx (t a)) Source #

Checks that the Foldable is not empty. If empty, it adds the given failure to the result and validation continues.

minLength :: Foldable t => Int -> f -> ValueCtx (t a) -> VCtx f (ValueCtx (t a)) Source #

Checks that a Foldable has a length equal to or greater than the given value. If not, it adds the given failure to the result and validation continues.

maxLength :: Foldable t => Int -> f -> ValueCtx (t a) -> VCtx f (ValueCtx (t a)) Source #

Checks that a Foldable has a length equal to or less than the given value. If not, it adds the given failure to the result and validation continues.

isLength :: Foldable t => Int -> f -> ValueCtx (t a) -> VCtx f (ValueCtx (t a)) Source #

Checks that a Foldable has a length equal to the given value. If not, it adds the given failure to the result and validation continues.

isEqual :: Eq a => a -> f -> ValueCtx a -> VCtx f (ValueCtx a) Source #

Checks that a value is equal to another. If not, it adds the given failure to the result and validation continues.

isNotEqual :: Eq a => a -> f -> ValueCtx a -> VCtx f (ValueCtx a) Source #

Checks that a value is not equal to another. If equal, it adds the given failure to the result and validation continues.

isLessThan :: Ord a => a -> f -> ValueCtx a -> VCtx f (ValueCtx a) Source #

Checks that a value is less than another. If not, it adds the given failure to the result and validation continues.

isLessThanOrEqual :: Ord a => a -> f -> ValueCtx a -> VCtx f (ValueCtx a) Source #

Checks that a value is less than or equal to another. If not, it adds the given failure to the result and validation continues.

isGreaterThan :: Ord a => a -> f -> ValueCtx a -> VCtx f (ValueCtx a) Source #

Checks that a value is greater than another. If not, it adds the given failure to the result and validation continues.

isGreaterThanOrEqual :: Ord a => a -> f -> ValueCtx a -> VCtx f (ValueCtx a) Source #

Checks that a value is greater than or equal to another. If not, it adds the given failure to the result and validation continues.

hasElem :: (Foldable t, Eq a) => a -> f -> ValueCtx (t a) -> VCtx f (ValueCtx (t a)) Source #

Checks that a Foldable has a given element. If not, it adds the given failure to the result and validation continues.

doesNotHaveElem :: (Foldable t, Eq a) => a -> f -> ValueCtx (t a) -> VCtx f (ValueCtx (t a)) Source #

Checks that a Foldable does not have a given element. If it has element, it adds the given failure to the result and validation continues.

ifAny :: (a -> Maybe f) -> ValueCtx [a] -> VCtx f (ValueCtx [a]) Source #

If any element is valid, the entire value is valid.

ifAll :: (a -> Maybe f) -> ValueCtx [a] -> VCtx f (ValueCtx [a]) Source #

Every element must be valid.

ifEach :: (a -> Either f b) -> ValueCtx [a] -> VCtx f (ValueCtx [b]) Source #

Validate each element with a given function.

ifEachProven :: (a -> Proof f b) -> ValueCtx [a] -> VCtx f (ValueCtx [b]) Source #

Validate each element with a given function.

isMatch :: Eq a => f -> VCtx f a -> ValueCtx a -> VCtx f (ValueCtx a) Source #

Checks that two fields are equal. If not, it adds the given failure to the result and validation continues.

Validation Helpers

validateField :: Validatable f a b => ValueCtx a -> VCtx f (ValueCtx b) Source #

Validates a value that implements Validatable and includes any failures under the parent field.

Consider the following example:

 data ContactVM = ContactVM { phoneNumber :: String }
 data Contact = ...
 instance Validatable MyFailureType ContactVM Contact where
   ...

 data UserCreatableVM
   = UserCreatableVM
   { userCreatableVMEmailAddress         :: String
   , userCreatableVMConfirmEmailAddress  :: String
   , userCreatableVMPassword             :: String
   , userCreatableVMConfirmPassword      :: String
   , userCreatableVMContact              :: ContactVM
   }
 data UserCreatable = ...

 instance Validatable MyFailureType UserCreatableVM UserCreatable where
   validation u =
     let vc = withField 'userCreatableVMContact (userCreatableVMContact u) $
           validateField                                                      -- (1)
         ...
     in pure UserCreatable <*> ve <*> vp <*> vc <! vce <! vcp
 

In line (1), the validateField function uses the Validatable instance on ContactVM to validate the type. All field specific validation failures are stored in a map where the key is the name of the field. However, in this case, there are the fields in the ContactVM and the parent field in UserCreatableVM. These names need to be combined so that the consumer can see if any errors came from nested fields. Using the validateField function, any validation failures found in the ContactVM value have field names that include the parent field. A ContactVM with an invalid phone number might have a result like this: `Invalid [] [(['phoneNumber], [InvalidPhoneNumber])]` where `['phoneNumber]` is the key to the map. The validationField merges this with the UserCreatable result to create something like this: `Invalid [] [(['contact, 'phoneNumber], [InvalidPhoneNumber])]`. This allows the consumer to determine exactly what field caused the failure.

optional :: Maybe a -> (a -> VCtx f b) -> VCtx f (Maybe b) Source #

Allows for validation of an optional value. See `Validating Complex Types` for an example.

whenJust :: (ValueCtx a -> VCtx f (ValueCtx b)) -> ValueCtx (Maybe a) -> VCtx f (ValueCtx (Maybe b)) Source #

Allows for validation of an optional value. See `Validating Complex Types` for an example.

aggregateFailures :: VCtx f a -> VCtx f b -> VCtx f a Source #

Takes the failures from the second parameter and adds them to the first.

(<!) :: VCtx f a -> VCtx f b -> VCtx f a Source #

Takes the failures from the right-hand-side, if any, and adds them to the left-hand-side.

isValid :: Proof f a -> Bool Source #

tests if a Proof is valid.

isInvalid :: Proof f a -> Bool Source #

tests if a Proof is invalid.

flattenProofs :: [Proof f a] -> Proof f [a] Source #

Flatten a list of proofs into a proof of the list

Re-exports

data VCtx f a Source #

A type that holds aggregated validation failures.

Instances
Monad (VCtx f) Source # 
Instance details

Defined in Data.Validation.Internal

Methods

(>>=) :: VCtx f a -> (a -> VCtx f b) -> VCtx f b #

(>>) :: VCtx f a -> VCtx f b -> VCtx f b #

return :: a -> VCtx f a #

fail :: String -> VCtx f a #

Functor (VCtx f) Source # 
Instance details

Defined in Data.Validation.Internal

Methods

fmap :: (a -> b) -> VCtx f a -> VCtx f b #

(<$) :: a -> VCtx f b -> VCtx f a #

Applicative (VCtx f) Source # 
Instance details

Defined in Data.Validation.Internal

Methods

pure :: a -> VCtx f a #

(<*>) :: VCtx f (a -> b) -> VCtx f a -> VCtx f b #

liftA2 :: (a -> b -> c) -> VCtx f a -> VCtx f b -> VCtx f c #

(*>) :: VCtx f a -> VCtx f b -> VCtx f b #

(<*) :: VCtx f a -> VCtx f b -> VCtx f a #

(Eq a, Eq f) => Eq (VCtx f a) Source # 
Instance details

Defined in Data.Validation.Internal

Methods

(==) :: VCtx f a -> VCtx f a -> Bool #

(/=) :: VCtx f a -> VCtx f a -> Bool #

(Show a, Show f) => Show (VCtx f a) Source # 
Instance details

Defined in Data.Validation.Internal

Methods

showsPrec :: Int -> VCtx f a -> ShowS #

show :: VCtx f a -> String #

showList :: [VCtx f a] -> ShowS #

Semigroup a => Semigroup (VCtx f a) Source # 
Instance details

Defined in Data.Validation.Internal

Methods

(<>) :: VCtx f a -> VCtx f a -> VCtx f a #

sconcat :: NonEmpty (VCtx f a) -> VCtx f a #

stimes :: Integral b => b -> VCtx f a -> VCtx f a #

Monoid a => Monoid (VCtx f a) Source # 
Instance details

Defined in Data.Validation.Internal

Methods

mempty :: VCtx f a #

mappend :: VCtx f a -> VCtx f a -> VCtx f a #

mconcat :: [VCtx f a] -> VCtx f a #

data Name #

An abstract type representing names in the syntax tree.

Names can be constructed in several ways, which come with different name-capture guarantees (see Language.Haskell.TH.Syntax for an explanation of name capture):

  • the built-in syntax 'f and ''T can be used to construct names, The expression 'f gives a Name which refers to the value f currently in scope, and ''T gives a Name which refers to the type T currently in scope. These names can never be captured.
  • lookupValueName and lookupTypeName are similar to 'f and ''T respectively, but the Names are looked up at the point where the current splice is being run. These names can never be captured.
  • newName monadically generates a new name, which can never be captured.
  • mkName generates a capturable name.

Names constructed using newName and mkName may be used in bindings (such as let x = ... or x -> ...), but names constructed using lookupValueName, lookupTypeName, 'f, ''T may not.

Instances
Eq Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

(==) :: Name -> Name -> Bool #

(/=) :: Name -> Name -> Bool #

Data Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Name -> c Name #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Name #

toConstr :: Name -> Constr #

dataTypeOf :: Name -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Name) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Name) #

gmapT :: (forall b. Data b => b -> b) -> Name -> Name #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Name -> r #

gmapQ :: (forall d. Data d => d -> u) -> Name -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Name -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Name -> m Name #

Ord Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

compare :: Name -> Name -> Ordering #

(<) :: Name -> Name -> Bool #

(<=) :: Name -> Name -> Bool #

(>) :: Name -> Name -> Bool #

(>=) :: Name -> Name -> Bool #

max :: Name -> Name -> Name #

min :: Name -> Name -> Name #

Show Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Methods

showsPrec :: Int -> Name -> ShowS #

show :: Name -> String #

showList :: [Name] -> ShowS #

Generic Name 
Instance details

Defined in Language.Haskell.TH.Syntax

Associated Types

type Rep Name :: Type -> Type #

Methods

from :: Name -> Rep Name x #

to :: Rep Name x -> Name #

type Rep Name 
Instance details

Defined in Language.Haskell.TH.Syntax

mkName :: String -> Name #

Generate a capturable name. Occurrences of such names will be resolved according to the Haskell scoping rules at the occurrence site.

For example:

f = [| pi + $(varE (mkName "pi")) |]
...
g = let pi = 3 in $f

In this case, g is desugared to

g = Prelude.pi + 3

Note that mkName may be used with qualified names:

mkName "Prelude.pi"

See also dyn for a useful combinator. The above example could be rewritten using dyn as

f = [| pi + $(dyn "pi") |]

nameBase :: Name -> String #

The name without its module prefix.

Examples

Expand
>>> nameBase ''Data.Either.Either
"Either"
>>> nameBase (mkName "foo")
"foo"
>>> nameBase (mkName "Module.foo")
"foo"