Copyright | (c) Sirui Lu 2024 |
---|---|
License | BSD-3-Clause (see the LICENSE file) |
Maintainer | siruilu@cs.washington.edu |
Stability | Experimental |
Portability | GHC only |
Safe Haskell | Safe-Inferred |
Language | Haskell2010 |
Grisette.TH
Description
Synopsis
- derive :: Name -> [Name] -> Q [Dec]
- deriveAll :: Name -> Q [Dec]
- deriveAllExcept :: Name -> [Name] -> Q [Dec]
- mkMergeConstructor :: String -> Name -> Q [Dec]
- mkMergeConstructor' :: [String] -> Name -> Q [Dec]
- mkUnifiedConstructor :: String -> Name -> Q [Dec]
- mkUnifiedConstructor' :: [String] -> Name -> Q [Dec]
- class DeriveTypeParamHandler handler where
- handleTypeParams :: Int -> handler -> [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] -> Q [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])]
- handleBody :: handler -> [[Type]] -> Q [Pred]
- data IsFPBits = IsFPBits {}
- data NatShouldBePositive = NatShouldBePositive
- data PrimaryConstraint = PrimaryConstraint {}
- data SomeDeriveTypeParamHandler where
- SomeDeriveTypeParamHandler :: DeriveTypeParamHandler handler => handler -> SomeDeriveTypeParamHandler
- class DeriveInstanceProvider provider where
- instanceDeclaration :: provider -> [[(TyVarBndrUnit, Maybe Type)]] -> [Pred] -> [Type] -> Q [Dec]
- data Strategy
- = Stock { }
- | WithNewtype { }
- | ViaDefault { }
- | ViaDefault1 { }
- | Anyclass { }
- data TypeableMode = TypeableMode
- data PrimaryUnifiedConstraint = PrimaryUnifiedConstraint Name Bool
- data UnifiedInstance = UnifiedInstance {
- _cls :: Name
- _clsWithFunc :: Name
- _withFunc :: Name
- _withFunc1 :: Maybe Name
- deriveWithHandlers :: DeriveInstanceProvider provider => [SomeDeriveTypeParamHandler] -> provider -> Bool -> Int -> [Name] -> Q [Dec]
- derivePredefined :: Name -> Name -> Q [Dec]
- derivePredefinedMultipleClasses :: [Name] -> Name -> Q [Dec]
- deriveBuiltinExtra :: [SomeDeriveTypeParamHandler] -> Maybe [SomeDeriveTypeParamHandler] -> Bool -> Strategy -> [Name] -> Name -> Q [Dec]
- deriveUnifiedInterfaceExtra :: [SomeDeriveTypeParamHandler] -> Name -> Name -> Name -> Q [Dec]
- deriveUnifiedInterface1Extra :: [SomeDeriveTypeParamHandler] -> Name -> Name -> Name -> Name -> Name -> Q [Dec]
- deriveFunctorArgUnifiedInterfaceExtra :: [SomeDeriveTypeParamHandler] -> Name -> Name -> Name -> Name -> Name -> Q [Dec]
Convenient derivation of all instances relating to Grisette
derive :: Name -> [Name] -> Q [Dec] Source #
Derive specified classes for a type with the given name.
Support the same set of classes as deriveAll
.
deriveAll :: Name -> Q [Dec] Source #
Derive all classes related to Grisette for a type with the given name.
Classes that are be derived by this procedure are:
Generic
Show
Eq
Ord
Lift
NFData
Hashable
Serial
AllSyms
EvalSym
ExtractSym
PPrint
Mergeable
SymEq
SymOrd
SubstSym
ToCon
ToSym
UnifiedSymEq
UnifiedSymOrd
Ord
isn't valid for all types (symbolic-only types), so it may be necessary
to exclude it.
deriveAll
needs the following language extensions:
- DeriveAnyClass
- DeriveGeneric
- DeriveLift
- DerivingVia
- FlexibleContexts
- FlexibleInstances
- MonoLocalBinds
- MultiParamTypeClasses
- ScopedTypeVariables
- StandaloneDeriving
- TemplateHaskell
- TypeApplications
- UndecidableInstances
Deriving for a newtype may also need
- GeneralizedNewtypeDeriving
You may get warnings if you don't have the following extensions:
- TypeOperators
It also requires that the Default
data
constructor is visible.
You may get strange errors if you only import
Default
type but not the data constructor.
deriveAllExcept :: Name -> [Name] -> Q [Dec] Source #
Derive all classes related to Grisette for a type with the given name, except for the given classes.
Excluding Ord
or SymOrd
will also exclude UnifiedSymOrd
.
Excluding Eq
or SymEq
will also exclude UnifiedSymEq
.
Smart constructors that merges in a monad
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
.
mkMergeConstructor "mrg" ''Maybe
generates
mrgJust :: (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)
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.
mkMergeConstructor' ["mrgTuple2"] ''(,)
generates
mrgTuple2 :: (Mergeable (a, b), Applicative m, TryMerge m) => a -> b -> u (a, b) mrgTuple2 = \v1 v2 -> mrgSingle (v1, v2)
Smart constructors that are polymorphic in evaluation modes
Arguments
:: 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)
.
mkUnifiedConstructor' Source #
Arguments
:: [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)
.
Tools for building more derivation procedures
Type parameter handlers
class DeriveTypeParamHandler handler where Source #
A derive type param handler handles type parameters and provides constraints or instantiations for them.
The first argument is the number of types that are zipped together. For
most classes, this is 1, but for some classes, like ToCon
, this is
2.
The second argument is the handler itself.
The third argument is a list of type parameters and their constraints. Each
entry in the list corresponds to a type parameter of the datatype. The
first element in the pair is a list of zipped type parameters with possibly
concrete types. For example, if we are deriving ToCon
for
Either
, the argument will be:
[([(e0, Nothing), (e1, Nothing)], Nothing), ([(a0, Nothing), (a1, Nothing)], Nothing)]
We can see that the type parameters for the concrete and symbolic Either
types are zipped together: the first element of the list are for the error
types, and the second element of the list are for the value types.
The handler may concretize some types, or add constraints based on the type parameters.
Methods
handleTypeParams :: Int -> handler -> [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] -> Q [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] Source #
Instances
Ensures that the type parameters are valid for floating point operations.
Instances
data NatShouldBePositive Source #
Ensures that type parameters with the kind Nat
are known and positive.
Constructors
NatShouldBePositive |
Instances
DeriveTypeParamHandler NatShouldBePositive Source # | |
Defined in Grisette.Internal.TH.DeriveTypeParamHandler Methods handleTypeParams :: Int -> NatShouldBePositive -> [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] -> Q [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] Source # handleBody :: NatShouldBePositive -> [[Type]] -> Q [Pred] Source # |
data PrimaryConstraint Source #
Adds a primary constraint to the type parameters. It applies the class to each type parameter that are zipped into a list, with the desired kinds.
For example, if we are deriving ToCon
for Either
, and the input
to this handler is as follows:
[([(e0, Nothing), (e1, Nothing)], Nothing), ([(a0, Nothing), (a1, Nothing)], Nothing)]
Then this will generate constraints for the type parameters of Either
:
[([(e0, Nothing), (e1, Nothing)], Just [ToCon e0 e1]), ([(a0, Nothing), (a1, Nothing)], Just [ToCon a0 a1])]
Type parameters that are already handled by other handlers can be ignored.
Constructors
PrimaryConstraint | |
Fields |
Instances
DeriveTypeParamHandler PrimaryConstraint Source # | |
Defined in Grisette.Internal.TH.DeriveTypeParamHandler Methods handleTypeParams :: Int -> PrimaryConstraint -> [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] -> Q [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] Source # handleBody :: PrimaryConstraint -> [[Type]] -> Q [Pred] Source # |
data SomeDeriveTypeParamHandler where Source #
A type that can handle type parameters.
Constructors
SomeDeriveTypeParamHandler :: DeriveTypeParamHandler handler => handler -> SomeDeriveTypeParamHandler |
Instances
DeriveTypeParamHandler SomeDeriveTypeParamHandler Source # | |
Defined in Grisette.Internal.TH.DeriveTypeParamHandler Methods handleTypeParams :: Int -> SomeDeriveTypeParamHandler -> [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] -> Q [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] Source # handleBody :: SomeDeriveTypeParamHandler -> [[Type]] -> Q [Pred] Source # |
Instance providers
class DeriveInstanceProvider provider where Source #
A derive instance provider provides the instance declaration.
Methods
instanceDeclaration :: provider -> [[(TyVarBndrUnit, Maybe Type)]] -> [Pred] -> [Type] -> Q [Dec] Source #
Instances
DeriveInstanceProvider Strategy Source # | |
Defined in Grisette.Internal.TH.DeriveInstanceProvider | |
DeriveInstanceProvider UnifiedInstance Source # | |
Defined in Grisette.Internal.TH.DeriveUnifiedInterface Methods instanceDeclaration :: UnifiedInstance -> [[(TyVarBndrUnit, Maybe Type)]] -> [Pred] -> [Type] -> Q [Dec] Source # |
A strategy for deriving instances.
Constructors
Stock | |
Fields | |
WithNewtype | |
Fields | |
ViaDefault | |
Fields | |
ViaDefault1 | |
Fields | |
Anyclass | |
Fields |
Instances
For unified interfaces
data TypeableMode Source #
Add a Typeable
constraint to the modes.
Constructors
TypeableMode |
Instances
DeriveTypeParamHandler TypeableMode Source # | |
Defined in Grisette.Internal.TH.DeriveUnifiedInterface Methods handleTypeParams :: Int -> TypeableMode -> [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] -> Q [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] Source # handleBody :: TypeableMode -> [[Type]] -> Q [Pred] Source # |
data PrimaryUnifiedConstraint Source #
Add a primary unified constraint that applies to all the type parameters with the desired kind.
Constructors
PrimaryUnifiedConstraint Name Bool |
Instances
DeriveTypeParamHandler PrimaryUnifiedConstraint Source # | |
Defined in Grisette.Internal.TH.DeriveUnifiedInterface Methods handleTypeParams :: Int -> PrimaryUnifiedConstraint -> [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] -> Q [([(TyVarBndrUnit, Maybe Type)], Maybe [Pred])] Source # handleBody :: PrimaryUnifiedConstraint -> [[Type]] -> Q [Pred] Source # |
data UnifiedInstance Source #
Provide an instance for a unified interface.
Constructors
UnifiedInstance | |
Fields
|
Instances
DeriveInstanceProvider UnifiedInstance Source # | |
Defined in Grisette.Internal.TH.DeriveUnifiedInterface Methods instanceDeclaration :: UnifiedInstance -> [[(TyVarBndrUnit, Maybe Type)]] -> [Pred] -> [Type] -> Q [Dec] Source # |
Other helpers
deriveWithHandlers :: DeriveInstanceProvider provider => [SomeDeriveTypeParamHandler] -> provider -> Bool -> Int -> [Name] -> Q [Dec] Source #
Derive instances for a list of types with a list of handlers and a provider.
derivePredefined :: Name -> Name -> Q [Dec] Source #
Derive instances for a type with the given name, with the predefined strategy.
derivePredefinedMultipleClasses :: [Name] -> Name -> Q [Dec] Source #
Derive instances for a type with the given name, with the predefined strategy.
Multiple classes can be derived at once.
deriveBuiltinExtra :: [SomeDeriveTypeParamHandler] -> Maybe [SomeDeriveTypeParamHandler] -> Bool -> Strategy -> [Name] -> Name -> Q [Dec] Source #
Derive a builtin class for a type, with extra handlers.
deriveUnifiedInterfaceExtra :: [SomeDeriveTypeParamHandler] -> Name -> Name -> Name -> Q [Dec] Source #
Derive an instance for a unified interface, with extra handlers.