Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
Synopsis
- class Mergeable a => GenSymConstrained spec a where
- freshConstrained :: (MonadFresh m, MonadError e m, UnionLike m) => e -> spec -> m (UnionM a)
- class Mergeable a => GenSymSimpleConstrained spec a where
- simpleFreshConstrained :: (MonadFresh m, MonadError e m, UnionLike m) => e -> spec -> m a
- genSymConstrained :: forall spec a e. (GenSymConstrained spec a, Mergeable e) => e -> spec -> FreshIdent -> ExceptT e UnionM (UnionM a)
- genSymSimpleConstrained :: forall spec a e. (GenSymSimpleConstrained spec a, Mergeable e) => e -> spec -> FreshIdent -> ExceptT e UnionM a
- derivedFreshConstrainedNoSpec :: forall a m e. (Generic a, GenSymConstrainedNoSpec (Rep a), Mergeable a, MonadFresh m, MonadError e m, UnionLike m) => e -> () -> m (UnionM a)
- derivedSimpleFreshConstrainedNoSpec :: forall a m e. (Generic a, GenSymSimpleConstrainedNoSpec (Rep a), MonadFresh m, MonadError e m, UnionLike m, Mergeable a) => e -> () -> m a
- derivedSimpleFreshConstrainedSameShape :: (Generic a, GenSymConstrainedSameShape (Rep a), Mergeable a, MonadFresh m, MonadError e m, UnionLike m) => e -> a -> m a
- data SOrdUpperBound a spec = SOrdUpperBound a spec
- data SOrdLowerBound a spec = SOrdLowerBound a spec
- data SOrdBound a spec = SOrdBound a a spec
Symbolic value generation with errors
class Mergeable a => GenSymConstrained spec a where Source #
Class of types in which symbolic values can be generated with some specification.
See GenSym
for more details. The difference of this class is that it allows
constraints to be generated along with the generation of symbolic values.
Nothing
freshConstrained :: (MonadFresh m, MonadError e m, UnionLike m) => e -> spec -> m (UnionM a) Source #
Generates a symbolic value with the given specification.
Constraint violations will throw an error in the monadic environment.
>>>
runFreshT (freshConstrained () (SOrdUpperBound (1 :: SymInteger) ())) "a" :: ExceptT () UnionM (UnionM SymInteger)
ExceptT <If (<= 1 a@0) (Left ()) (Right {a@0})>
default freshConstrained :: GenSymSimpleConstrained spec a => (MonadFresh m, MonadError e m, UnionLike m) => e -> spec -> m (UnionM a) Source #
Instances
class Mergeable a => GenSymSimpleConstrained spec a where Source #
Class of types in which symbolic values can be generated with some specification.
See GenSymSimple
for more details. The difference of this class is that it allows
constraints to be generated along with the generation of symbolic values.
simpleFreshConstrained :: (MonadFresh m, MonadError e m, UnionLike m) => e -> spec -> m a Source #
Generates a symbolic value with the given specification.
Constraint violations will throw an error in the monadic environment.
>>>
runFreshT (simpleFreshConstrained () (SOrdUpperBound (1 :: SymInteger) ())) "a" :: ExceptT () UnionM SymInteger
ExceptT <If (<= 1 a@0) (Left ()) (Right a@0)>
Instances
genSymConstrained :: forall spec a e. (GenSymConstrained spec a, Mergeable e) => e -> spec -> FreshIdent -> ExceptT e UnionM (UnionM a) Source #
genSymSimpleConstrained :: forall spec a e. (GenSymSimpleConstrained spec a, Mergeable e) => e -> spec -> FreshIdent -> ExceptT e UnionM a Source #
derivedFreshConstrainedNoSpec :: forall a m e. (Generic a, GenSymConstrainedNoSpec (Rep a), Mergeable a, MonadFresh m, MonadError e m, UnionLike m) => e -> () -> m (UnionM a) Source #
We cannot provide DerivingVia style derivation for GenSymConstrained
, while you can
use this freshConstrained
implementation to implement GenSymConstrained
for your own types.
This freshConstrained
implementation is for the types that does not need any specification.
It will generate product types by generating each fields with ()
as specification,
and generate all possible values for a sum type.
Note: Never use on recursive types.
derivedSimpleFreshConstrainedNoSpec :: forall a m e. (Generic a, GenSymSimpleConstrainedNoSpec (Rep a), MonadFresh m, MonadError e m, UnionLike m, Mergeable a) => e -> () -> m a Source #
We cannot provide DerivingVia style derivation for GenSymSimpleConstrained
, while
you can use this simpleFreshConstrained
implementation to implement GenSymSimpleConstrained
fo
your own types.
This simpleFreshConstrained
implementation is for the types that does not need any specification.
It will generate product types by generating each fields with ()
as specification.
It will not work on sum types.
Note: Never use on recursive types.
derivedSimpleFreshConstrainedSameShape :: (Generic a, GenSymConstrainedSameShape (Rep a), Mergeable a, MonadFresh m, MonadError e m, UnionLike m) => e -> a -> m a Source #
We cannot provide DerivingVia style derivation for GenSymSimpleConstrained
, while
you can use this simpleFreshConstrained
implementation to implement GenSymSimpleConstrained
fo
your own types.
This simpleFreshConstrained
implementation is for the types that can be generated with
a reference value of the same type.
For sum types, it will generate the result with the same data constructor. For product types, it will generate the result by generating each field with the corresponding reference value.
Note: Can be used on recursive types.
Some common GenSymConstrained specifications
data SOrdUpperBound a spec Source #
Exclusive bound, generates the values with the specification, then filters out the ones that are greater than or equal to the bound
SOrdUpperBound a spec |
Instances
(SOrd a, Mergeable a, GenSym spec a) => GenSymConstrained (SOrdUpperBound a spec) a Source # | |
Defined in Grisette.Experimental.GenSymConstrained freshConstrained :: (MonadFresh m, MonadError e m, UnionLike m) => e -> SOrdUpperBound a spec -> m (UnionM a) Source # | |
(SOrd a, Mergeable a, GenSymSimple spec a) => GenSymSimpleConstrained (SOrdUpperBound a spec) a Source # | |
Defined in Grisette.Experimental.GenSymConstrained simpleFreshConstrained :: (MonadFresh m, MonadError e m, UnionLike m) => e -> SOrdUpperBound a spec -> m a Source # |
data SOrdLowerBound a spec Source #
Inclusive bound, generates the values with the specification, then filters out the ones that are less than the bound
SOrdLowerBound a spec |
Instances
(SOrd a, Mergeable a, GenSym spec a) => GenSymConstrained (SOrdLowerBound a spec) a Source # | |
Defined in Grisette.Experimental.GenSymConstrained freshConstrained :: (MonadFresh m, MonadError e m, UnionLike m) => e -> SOrdLowerBound a spec -> m (UnionM a) Source # | |
(SOrd a, Mergeable a, GenSymSimple spec a) => GenSymSimpleConstrained (SOrdLowerBound a spec) a Source # | |
Defined in Grisette.Experimental.GenSymConstrained simpleFreshConstrained :: (MonadFresh m, MonadError e m, UnionLike m) => e -> SOrdLowerBound a spec -> m a Source # |
data SOrdBound a spec Source #
Left-inclusive, right-exclusive bound, generates the values with the specification, then filters out the ones that are out-of-bound
SOrdBound a a spec |
Instances
GenSymConstrained (SOrdBound Integer ()) Integer Source # | |
Defined in Grisette.Experimental.GenSymConstrained freshConstrained :: (MonadFresh m, MonadError e m, UnionLike m) => e -> SOrdBound Integer () -> m (UnionM Integer) Source # | |
(SOrd a, Mergeable a, GenSym spec a) => GenSymConstrained (SOrdBound a spec) a Source # | |
Defined in Grisette.Experimental.GenSymConstrained freshConstrained :: (MonadFresh m, MonadError e m, UnionLike m) => e -> SOrdBound a spec -> m (UnionM a) Source # | |
(SOrd a, Mergeable a, GenSymSimple spec a) => GenSymSimpleConstrained (SOrdBound a spec) a Source # | |
Defined in Grisette.Experimental.GenSymConstrained simpleFreshConstrained :: (MonadFresh m, MonadError e m, UnionLike m) => e -> SOrdBound a spec -> m a Source # |