grisette-0.11.0.0: Symbolic evaluation as a library
Copyright(c) Sirui Lu 2024
LicenseBSD-3-Clause (see the LICENSE file)
Maintainersiruilu@cs.washington.edu
StabilityExperimental
PortabilityGHC only
Safe HaskellSafe-Inferred
LanguageHaskell2010

Grisette.TH

Description

 
Synopsis

Convenient derivation of all instances relating to Grisette

data EvalModeConfig Source #

Configuration for constraints for evaluation modes tag.

  • EvalModeConstraints specifies a list of constraints for the tag, for example, we may use EvalModeBase and EvalModeBV to specify that the evaluation mode must support both base (boolean and data types) and bit vectors. This should be used when the data type uses bit vectors.
  • EvalModeSpecified specifies a that an evaluation mode tag should be specialized to a specific tag for all the instances.

deriveGADT :: [Name] -> [Name] -> Q [Dec] Source #

Derive the specified classes for a GADT with the given name.

See deriveGADTWith for more details.

allClasses01 :: [Name] Source #

All the classes that can be derived for GADT functors.

This includes all the classes in allClasses0 and allClasses1.

allClasses012 :: [Name] Source #

All the classes that can be derived for GADTfunctors.

This includes all the classes in allClasses0, allClasses1, and allClasses2.

basicClasses0 :: [Name] Source #

Basic classes for GADTs.

This includes:

These classes can be derived for most GADTs.

noExistentialClasses0 :: [Name] Source #

Classes that can only be derived for GADTs without existential type variables.

This includes:

ordClasses0 :: [Name] Source #

Concrete ordered classes that can be derived for GADTs that

  • uses unified evaluation mode, or
  • does not contain any symbolic variables.

This includes:

noExistentialClasses1 :: [Name] Source #

*1 classes that can only be derived for GADT functors without existential type variables.

This includes:

ordClasses1 :: [Name] Source #

*1 concrete ordered classes that can be derived for GADT functors that

  • uses unified evaluation mode, or
  • does not contain any symbolic variables.

This includes:

noExistentialClasses2 :: [Name] Source #

*2 classes that can only be derived for GADT functors without existential type variables.

This includes:

ordClasses2 :: [Name] Source #

*2 concrete ordered classes that can be derived for GADT functors that

  • uses unified evaluation mode, or
  • does not contain any symbolic variables.

This includes:

Smart constructors that merges in a monad

makePrefixedSmartCtor Source #

Arguments

:: String

Prefix for generated wrappers

-> Name

The type to generate the wrappers for

-> Q [Dec] 

Generate constructor wrappers that wraps the result in a container with TryMerge.

makePrefixedSmartCtor "mrg" ''Maybe

generates

mrgNothing :: (Mergeable (Maybe a), Applicative m, TryMerge m) => m (Maybe a)
mrgNothing = mrgSingle Nothing
mrgJust :: (Mergeable (Maybe a), Applicative m, TryMerge m) => a -> m (Maybe a)
mrgJust = \x -> mrgSingle (Just x)

makeNamedSmartCtor Source #

Arguments

:: [String]

Names for generated wrappers

-> Name

The type to generate the wrappers for

-> Q [Dec] 

Generate constructor wrappers that wraps the result in a container with TryMerge with provided names.

makeNamedSmartCtor ["mrgTuple2"] ''(,)

generates

mrgTuple2 :: (Mergeable (a, b), Applicative m, TryMerge m) => a -> b -> u (a, b)
mrgTuple2 = \v1 v2 -> mrgSingle (v1, v2)

makeSmartCtor Source #

Arguments

:: Name

The type to generate the wrappers for

-> Q [Dec] 

Generate constructor wrappers that wraps the result in a container with TryMerge.

makeSmartCtor ''Maybe

generates

nothing :: (Mergeable (Maybe a), Applicative m, TryMerge m) => m (Maybe a)
nothing = mrgSingle Nothing
just :: (Mergeable (Maybe a), Applicative m, TryMerge m) => a -> m (Maybe a)
just = \x -> mrgSingle (Just x)

makeSmartCtorWith :: (String -> String) -> Name -> Q [Dec] Source #

Generate constructor wrappers that wraps the result in a container with TryMerge with provided name transformer.

makeSmartCtorWith (\name -> "mrg" ++ name) ''Maybe

generates

mrgNothing :: (Mergeable (Maybe a), Applicative m, TryMerge m) => m (Maybe a)
mrgNothing = mrgSingle Nothing

Smart constructors that are polymorphic in evaluation modes

makePrefixedUnifiedCtor Source #

Arguments

:: [Name] 
-> String

Prefix for generated wrappers

-> Name

The type to generate the wrappers for

-> Q [Dec] 

Generate smart constructors to create unified values.

For a type T mode a b c with constructors T1, T2, etc., this function will generate smart constructors with the given prefix, e.g., mkT1, mkT2, etc.

The generated smart constructors will contruct values of type GetData mode (T mode a b c).

makeNamedUnifiedCtor Source #

Arguments

:: [Name] 
-> [String]

Names for generated wrappers

-> Name

The type to generate the wrappers for

-> Q [Dec] 

Generate smart constructors to create unified values.

For a type T mode a b c with constructors T1, T2, etc., this function will generate smart constructors with the given names.

The generated smart constructors will contruct values of type GetData mode (T mode a b c).

makeUnifiedCtor Source #

Arguments

:: [Name] 
-> Name

The type to generate the wrappers for

-> Q [Dec] 

Generate smart constructors to create unified values.

For a type T mode a b c with constructors T1, T2, etc., this function will generate smart constructors with the names decapitalized, e.g., t1, t2, etc.

The generated smart constructors will contruct values of type GetData mode (T mode a b c).

makeUnifiedCtorWith :: [Name] -> (String -> String) -> Name -> Q [Dec] Source #

Generate smart constructors to create unified values with provided name transformer.

For a type T mode a b c with constructors T1, T2, etc., this function will generate smart constructors with the name transformed, e.g., given the name transformer (name -> "mk" ++ name), it will generate mkT1, mkT2, mkT2, etc.

The generated smart constructors will contruct values of type GetData mode (T mode a b c).