BPS-0.1.0.0: Translations of classic Truth Maintenance Systems
Copyright(c) John Maraist 2022
LicenseAllRightsReserved
Maintainerhaskell-tms@maraist.org
Stabilityexperimental
PortabilityPOSIX
Safe HaskellNone
LanguageHaskell2010

Data.TMS.Helpers

Description

Unless required by applicable law or agreed to in writing, software distributed under the License is distributed on an "AS IS" BASIS, WITHOUT WARRANTIES OR CONDITIONS OF ANY KIND, either express or implied, for NON-COMMERCIAL use. See the License for the specific language governing permissions and limitations under the License.

Synopsis

Lists and monads

anyByM :: Monad m => (a -> m Bool) -> [a] -> m Bool Source #

Check whether a list contains a value which, when applied to a computation, returns True.

anyMM :: Monad m => (a -> m Bool) -> m [a] -> m Bool Source #

Check whether a returned list contains a value which satisfies some monadic predicate.

allByM :: Monad m => (a -> m Bool) -> [a] -> m Bool Source #

Check whether all of the values of a list, when applied to a computation, return True.

Ordered lists

ordSubsetp :: Ord a => [a] -> [a] -> Bool Source #

Determine whether one list is a subset of the other, under the assumption that both lists are sorted in ascending order.

Even more loops

formatList :: Monad m => String -> (a -> m String) -> [a] -> m String Source #

Convert a list to a string, where the converter for each element is a monadic computation.

forMM_ :: (Monad m, Foldable t) => m (t a) -> (a -> m ()) -> m () Source #

Like forM_, but with both the elements source as well as the loop body as computations over the monad.

whileDo :: Monad m => m Bool -> m () -> m () Source #

A while loop, guard at the top.

whileDoWith :: Monad m => m a -> (a -> Bool) -> (a -> m ()) -> m () Source #

A while loop based on stuff, guard at the top.

forMwhile_ :: Monad m => [a] -> m Bool -> (a -> m ()) -> m () Source #

Like forM_, but with an extra check run after the body of the loop. If the check fails, the loop exits early.

forMMwhile_ :: Monad m => m [a] -> m Bool -> (a -> m ()) -> m () Source #

Like forMwhile_, but the source list is also the result of a monadic computation.

whileReturnJust :: Monad m => m (Maybe a) -> (a -> m ()) -> m () Source #

Like forMM_, except instead of a fixed list, loop over Maybe values returned from a subcomputation, until that subcomputation returns Nothing.

unlessMM :: Monad m => m Bool -> m () -> m () Source #

Like unless, expect both the tested value and the body are returned from a computation in a monad.

Lists under references in the STT monad transformer

nullR :: Monad m => STRef s [a] -> STT s m Bool Source #

Monadic version of null for a list stored in an STRef: returns True when the list is empty.

nonnullR :: Monad m => STRef s [a] -> STT s m Bool Source #

Opposite of nullR, returning False when the referenced list is empty.

whenNonnullR :: (Monad m0, Monad m) => (forall r. STT s m0 r -> m r) -> STRef s [a] -> ([a] -> m ()) -> m () Source #

Like a combination of whenM and nonnullR, where the body receives the (pure) non-null list as an argument.

mapRefs :: Monad m => (a -> b) -> [STRef s a] -> STT s m [b] Source #

Map over the values contained within a list of references.

foldrRefs :: Monad m => (a -> b -> b) -> b -> [STRef s a] -> STT s m b Source #

Fold (right-associatively) the values contained within a list of references.

foldlRefs :: Monad m => (b -> a -> b) -> b -> [STRef s a] -> STT s m b Source #

Fold (left-associatively) the values contained within a list of references.

forRM_ :: (Monad m, Monad m0, Foldable t) => (STT s m0 (t a) -> m (t a)) -> STRef s (t a) -> (a -> m ()) -> m () Source #

Like forM_, but with the list under an STRef. The first argument lifts an STT operation into m.

Stack-like operations

push :: Monad m => a -> STRef s [a] -> STT s m () Source #

Push a value onto the front of the list at the given STT reference.

pushM :: Monad m => m a -> STRef s [a] -> STT s m () Source #

Push the result of a computation onto the front of the list at the given STT reference.

pushAll :: (Monad m, Traversable t) => t a -> STRef s [a] -> STT s m () Source #

Push every value in a collection onto the front of the list at the given STT reference.

pushAllM :: (Monad m, Traversable t) => m (t a) -> STRef s [a] -> STT s m () Source #

Push every value in a collection returned from a computation onto the front of the list at the given STT reference.

pop :: Monad m => STRef s [a] -> STT s m (Maybe a) Source #

Pop a value from the given reference to a list if one exists.

whileListM_ :: (Monad m0, Monad m) => (forall r. STT s m0 r -> m r) -> STRef s [a] -> (a -> m ()) -> m () Source #

Consumes the elements of a referenced list, one at a time, until the list is empty. The first argument is a lift-style function which brings STT operations into the top-level monad of interest. Intended to be compatible with stack-like behavior (such as with push; this function does use pop) where the body of the loop may add elements.

Strings

commaList :: (a -> String) -> [a] -> String Source #

Form a comma-separated string from a list.

unmaybe :: [Maybe a] -> [a] Source #

Remove the Just constructors from the elements of a list, discarding elements which are Nothing.