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

Grisette.Lib.Data.Foldable

Description

 
Synopsis

Documentation

symElem :: (Foldable t, SEq a) => a -> t a -> SymBool Source #

elem with symbolic equality.

symMaximum :: forall a t. (Foldable t, Mergeable a, SOrd a, ITEOp a) => t a -> a Source #

maximum with result merged with ITEOp.

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

maximum with MergingStrategy knowledge propagation.

symMinimum :: forall a t. (Foldable t, Mergeable a, SOrd a, ITEOp a) => t a -> a Source #

minimum with result merged with ITEOp.

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

minimum with MergingStrategy knowledge propagation.

Special biased folds

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

foldrM with MergingStrategy knowledge propagation.

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

foldlM with MergingStrategy knowledge propagation.

Folding actions

Applicative actions

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

traverse_ with MergingStrategy knowledge propagation.

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

for_ with MergingStrategy knowledge propagation.

mrgSequenceA_ :: (Foldable t, TryMerge m, Applicative m) => t (m a) -> m () Source #

sequence_ with MergingStrategy knowledge propagation.

mrgAsum :: (Alternative f, TryMerge f, Mergeable a, Foldable t) => t (f a) -> f a Source #

asum with MergingStrategy knowledge propagation.

Monadic actions

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

mapM_ with MergingStrategy knowledge propagation.

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

forM_ with MergingStrategy knowledge propagation.

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

sequence_ with MergingStrategy knowledge propagation.

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

msum with MergingStrategy knowledge propagation.

Specialized folds

symAnd :: Foldable t => t SymBool -> SymBool Source #

and on symbolic boolean.

symOr :: Foldable t => t SymBool -> SymBool Source #

or on symbolic boolean.

symAny :: Foldable t => (a -> SymBool) -> t a -> SymBool Source #

any on symbolic boolean.

symAll :: Foldable t => (a -> SymBool) -> t a -> SymBool Source #

all on symbolic boolean.

symMaximumBy :: forall t a. (Foldable t, Mergeable a, ITEOp a) => (a -> a -> UnionM Ordering) -> t a -> a Source #

maximumBy with result merged with ITEOp.

mrgMaximumBy :: forall t a m. (Foldable t, Mergeable a, MonadUnion m) => (a -> a -> UnionM Ordering) -> t a -> m a Source #

maximumBy with MergingStrategy knowledge propagation.

symMinimumBy :: forall t a. (Foldable t, Mergeable a, ITEOp a) => (a -> a -> UnionM Ordering) -> t a -> a Source #

minimumBy with result merged with ITEOp.

mrgMinimumBy :: forall t a m. (Foldable t, Mergeable a, MonadUnion m) => (a -> a -> UnionM Ordering) -> t a -> m a Source #

minimumBy with MergingStrategy knowledge propagation.

Searches

symNotElem :: (Foldable t, SEq a) => a -> t a -> SymBool Source #

elem with symbolic equality.

mrgFind :: (Foldable t, MonadUnion m, Mergeable a) => (a -> SymBool) -> t a -> m (Maybe a) Source #

elem with symbolic equality and MergingStrategy knowledge propagation.