uni-util-2.3.0.2: Utilities for the uniform workbench

Safe HaskellNone
LanguageHaskell98

Util.Computation

Contents

Description

 
Synopsis

Documentation

done :: Monad m => m () Source #

(#) :: a -> (a -> b) -> b infixr 2 Source #

exceptions and handlers

try :: Exception e => IO a -> IO (Either e a) #

Similar to catch, but returns an Either result which is (Right a) if no exception of type e was raised, or (Left ex) if an exception of type e was raised and its value is ex. If any other type of exception is raised than it will be propogated up to the next enclosing exception handler.

 try a = catch (Right `liftM` a) (return . Left)

tryUntilOK :: IO a -> IO a Source #

selectors

when :: Applicative f => Bool -> f () -> f () #

Conditional execution of Applicative expressions. For example,

when debug (putStrLn "Debugging")

will output the string Debugging if the Boolean value debug is True, and otherwise do nothing.

unless :: Applicative f => Bool -> f () -> f () #

The reverse of when.

incase :: Maybe a -> (a -> IO b) -> IO () Source #

iterators

forever :: Applicative f => f a -> f b #

forever act repeats the action infinitely.

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

foreach :: Monad m => [a] -> (a -> m b) -> m () Source #

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

configure command

type Config w = w -> IO w Source #

configure :: w -> [Config w] -> IO w Source #

config :: IO () -> Config w Source #

The new-style configuration command

class HasConfig option configuration where Source #

Minimal complete definition

($$), configUsed

Methods

($$) :: option -> configuration -> configuration infixr 0 Source #

configUsed :: option -> configuration -> Bool Source #

Returning results or error messages.

data WithError a Source #

Instances
Monad WithError Source # 
Instance details

Defined in Util.Computation

Methods

(>>=) :: WithError a -> (a -> WithError b) -> WithError b #

(>>) :: WithError a -> WithError b -> WithError b #

return :: a -> WithError a #

fail :: String -> WithError a #

Functor WithError Source # 
Instance details

Defined in Util.Computation

Methods

fmap :: (a -> b) -> WithError a -> WithError b #

(<$) :: a -> WithError b -> WithError a #

Applicative WithError Source # 
Instance details

Defined in Util.Computation

Methods

pure :: a -> WithError a #

(<*>) :: WithError (a -> b) -> WithError a -> WithError b #

liftA2 :: (a -> b -> c) -> WithError a -> WithError b -> WithError c #

(*>) :: WithError a -> WithError b -> WithError b #

(<*) :: WithError a -> WithError b -> WithError a #

mapWithError :: (a -> b) -> WithError a -> WithError b Source #

mapWithErrorIO :: (a -> IO b) -> WithError a -> IO (WithError b) Source #

coerceWithErrorOrBreakIOPrefix :: String -> (String -> a) -> WithError a -> IO a Source #

coerce or use the supplied break function (to be used with addFallOut)

The first argument is prepended to any error message. The value is evaluated immediately.

coerceWithErrorOrBreakPrefix :: String -> (String -> a) -> WithError a -> a Source #

coerce or use the supplied break function (to be used with addFallOut)

The first argument is prepended to any error message.

newtype MonadWithError m a Source #

Constructors

MonadWithError (m (WithError a)) 
Instances
Monad m => Monad (MonadWithError m) Source # 
Instance details

Defined in Util.Computation

Monad m => Functor (MonadWithError m) Source # 
Instance details

Defined in Util.Computation

Methods

fmap :: (a -> b) -> MonadWithError m a -> MonadWithError m b #

(<$) :: a -> MonadWithError m b -> MonadWithError m a #

Monad m => Applicative (MonadWithError m) Source # 
Instance details

Defined in Util.Computation

Methods

pure :: a -> MonadWithError m a #

(<*>) :: MonadWithError m (a -> b) -> MonadWithError m a -> MonadWithError m b #

liftA2 :: (a -> b -> c) -> MonadWithError m a -> MonadWithError m b -> MonadWithError m c #

(*>) :: MonadWithError m a -> MonadWithError m b -> MonadWithError m b #

(<*) :: MonadWithError m a -> MonadWithError m b -> MonadWithError m a #

coerceWithErrorOrBreak :: (String -> a) -> WithError a -> a Source #

coerce or use the supplied break function (to be used with addFallOut)

coerceWithErrorOrBreakIO :: (String -> a) -> WithError a -> IO a Source #

coerce or use the supplied break function (to be used with addFallOut) The value is evaluated immediately.