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

Grisette.Lib.Base

Description

 
Synopsis

Symbolic or mrg* variants for the operations in the base package

mrg* variants for operations in Control.Monad

mrgReturnWithStrategy :: MonadUnion u => MergingStrategy a -> a -> u a Source #

return with MergingStrategy knowledge propagation.

mrgBindWithStrategy :: MonadUnion u => MergingStrategy b -> u a -> (a -> u b) -> u b Source #

>>= with MergingStrategy knowledge propagation.

mrgReturn :: (MonadUnion u, Mergeable a) => a -> u a Source #

return with MergingStrategy knowledge propagation.

(>>=~) :: (MonadUnion u, Mergeable b) => u a -> (a -> u b) -> u b Source #

>>= with MergingStrategy knowledge propagation.

(>>~) :: forall m a b. (MonadUnion m, Mergeable b) => m a -> m b -> m b Source #

>> with MergingStrategy knowledge propagation.

This is usually more efficient than calling the original >> and merge the results.

mrgFoldM :: (MonadUnion m, Mergeable b, Foldable t) => (b -> a -> m b) -> b -> t a -> m b Source #

foldM with MergingStrategy knowledge propagation.

mrgMzero :: forall m a. (MonadUnion m, Mergeable a, MonadPlus m) => m a Source #

mzero with MergingStrategy knowledge propagation.

mrgMplus :: forall m a. (MonadUnion m, Mergeable a, MonadPlus m) => m a -> m a -> m a Source #

mplus with MergingStrategy knowledge propagation.

mrgFmap :: (MonadUnion f, Mergeable b, Functor f) => (a -> b) -> f a -> f b Source #

fmap with MergingStrategy knowledge propagation.

mrg* variants for operations in Data.Foldable

mrgFoldlM :: (MonadUnion m, Mergeable b, Foldable t) => (b -> a -> m b) -> b -> t a -> m b Source #

foldlM with MergingStrategy knowledge propagation.

mrgFoldrM :: (MonadUnion m, Mergeable b, Foldable t) => (a -> b -> m b) -> b -> t a -> m b Source #

foldrM with MergingStrategy knowledge propagation.

mrgTraverse_ :: (MonadUnion m, Foldable t) => (a -> m b) -> t a -> m () Source #

traverse_ with MergingStrategy knowledge propagation.

mrgFor_ :: (MonadUnion m, Foldable t) => t a -> (a -> m b) -> m () Source #

for_ with MergingStrategy knowledge propagation.

mrgMapM_ :: (MonadUnion m, Foldable t) => (a -> m b) -> t a -> m () Source #

mapM_ with MergingStrategy knowledge propagation.

mrgForM_ :: (MonadUnion m, Foldable t) => t a -> (a -> m b) -> m () Source #

forM_ with MergingStrategy knowledge propagation.

mrgSequence_ :: (Foldable t, MonadUnion m) => t (m a) -> m () Source #

sequence_ with MergingStrategy knowledge propagation.

mrgMsum :: forall m a t. (MonadUnion m, Mergeable a, MonadPlus m, Foldable t) => t (m a) -> m a Source #

msum with MergingStrategy knowledge propagation.

mrg* variants for operations in Data.Traversable

mrgTraverse :: forall a b t f. (Mergeable b, Mergeable1 t, MonadUnion f, Traversable t) => (a -> f b) -> t a -> f (t b) Source #

traverse with MergingStrategy knowledge propagation.

mrgSequenceA :: forall a t f. (Mergeable a, Mergeable1 t, MonadUnion f, Traversable t) => t (f a) -> f (t a) Source #

sequenceA with MergingStrategy knowledge propagation.

mrgFor :: (Mergeable b, Mergeable1 t, Traversable t, MonadUnion m) => t a -> (a -> m b) -> m (t b) Source #

for with MergingStrategy knowledge propagation.

mrgMapM :: forall a b t f. (Mergeable b, Mergeable1 t, MonadUnion f, Traversable t) => (a -> f b) -> t a -> f (t b) Source #

mapM with MergingStrategy knowledge propagation.

mrgForM :: (Mergeable b, Mergeable1 t, Traversable t, MonadUnion m) => t a -> (a -> m b) -> m (t b) Source #

forM with MergingStrategy knowledge propagation.

mrgSequence :: forall a t f. (Mergeable a, Mergeable1 t, MonadUnion f, Traversable t) => t (f a) -> f (t a) Source #

sequence with MergingStrategy knowledge propagation.

Symbolic versions for operations in Data.List

(!!~) :: (MonadUnion uf, MonadError e uf, TransformError ArrayException e, Mergeable a) => [a] -> SymInteger -> uf a Source #

Symbolic version of !!, the result would be merged and propagate the mergeable knowledge.

symFilter :: (MonadUnion u, Mergeable a) => (a -> SymBool) -> [a] -> u [a] Source #

Symbolic version of filter, the result would be merged and propagate the mergeable knowledge.

symTake :: (MonadUnion u, Mergeable a) => SymInteger -> [a] -> u [a] Source #

Symbolic version of take, the result would be merged and propagate the mergeable knowledge.

symDrop :: (MonadUnion u, Mergeable a) => SymInteger -> [a] -> u [a] Source #

Symbolic version of drop, the result would be merged and propagate the mergeable knowledge.