alternators-1.0.0.0: Handy functions when using transformers.

Safe HaskellNone
LanguageHaskell2010

Control.Also

Synopsis

Documentation

class Also f a where Source #

Combining effects where both input effects are used as much as possible. as opposed to Alternative where only the "successful" effect is used.

Minimal complete definition

also, alsoZero

Methods

also :: f a -> f a -> f a infixr 6 Source #

An associative binary operation, where both input effects are used as much as possible.

alsoZero :: f a Source #

The identity of also

Instances
Monoid a => Also IO a Source # 
Instance details

Defined in Control.Also

Methods

also :: IO a -> IO a -> IO a Source #

alsoZero :: IO a Source #

(Monoid a, Applicative f) => Also f a Source #

Overlappable instance for all Applicatives of Monoids.

Instance details

Defined in Control.Also

Methods

also :: f a -> f a -> f a Source #

alsoZero :: f a Source #

Monoid a => Also Identity a Source # 
Instance details

Defined in Control.Also

Also m (Maybe a) => Also (MaybeT m) a Source # 
Instance details

Defined in Control.Also

Methods

also :: MaybeT m a -> MaybeT m a -> MaybeT m a Source #

alsoZero :: MaybeT m a Source #

Also m a => Also (IdentityT m) a Source # 
Instance details

Defined in Control.Also

Methods

also :: IdentityT m a -> IdentityT m a -> IdentityT m a Source #

alsoZero :: IdentityT m a Source #

Also m (Either e a) => Also (ExceptT e m) a Source # 
Instance details

Defined in Control.Also

Methods

also :: ExceptT e m a -> ExceptT e m a -> ExceptT e m a Source #

alsoZero :: ExceptT e m a Source #

(Also m a, Monad m) => Also (StateT s m) a Source #

State instances threads the state through both monad of also in the normal left to right order, and so do not prevent early termination from the left monad (eg if the inner monad was a MaybeT or ExceptT. However, it is able to use the also to combine the return value.

Instance details

Defined in Control.Also

Methods

also :: StateT s m a -> StateT s m a -> StateT s m a Source #

alsoZero :: StateT s m a Source #

(Also m a, Monad m) => Also (StateT s m) a Source #

State instances threads the state through both monad of also in the normal left to right order, and so do not prevent early termination from the left monad (eg if the inner monad was a MaybeT or ExceptT. However, it is able to use the also to combine the return value.

Instance details

Defined in Control.Also

Methods

also :: StateT s m a -> StateT s m a -> StateT s m a Source #

alsoZero :: StateT s m a Source #

(Monoid w, Also m a, Monad m) => Also (WriterT w m) a Source #

Writer instances threads the writer through both monad of also in the normal left to right order, and so do not prevent early termination from the left monad (eg if the inner monad was a MaybeT or ExceptT. However, it is able to use the also to combine the return value.

Instance details

Defined in Control.Also

Methods

also :: WriterT w m a -> WriterT w m a -> WriterT w m a Source #

alsoZero :: WriterT w m a Source #

(Monoid w, Also m a, Monad m) => Also (WriterT w m) a Source #

Writer instances threads the writer through both monad of also in the normal left to right order, and so do not prevent early termination from the left monad (eg if the inner monad was a MaybeT or ExceptT. However, it is able to use the also to combine the return value.

Instance details

Defined in Control.Also

Methods

also :: WriterT w m a -> WriterT w m a -> WriterT w m a Source #

alsoZero :: WriterT w m a Source #

Also m r => Also (ContT r m) a Source #

Combine the monads that returns r not a.

Instance details

Defined in Control.Also

Methods

also :: ContT r m a -> ContT r m a -> ContT r m a Source #

alsoZero :: ContT r m a Source #

Also m a => Also (ReaderT r m) a Source # 
Instance details

Defined in Control.Also

Methods

also :: ReaderT r m a -> ReaderT r m a -> ReaderT r m a Source #

alsoZero :: ReaderT r m a Source #

(Monoid w, Also m a, Monad m) => Also (RWST r w s m) a Source #

State instances threads the state through both monad of also in the normal left to right order, and so do not prevent early termination from the left monad (eg if the inner monad was a MaybeT or ExceptT. However, it is able to use the also to combine the return value.

Instance details

Defined in Control.Also

Methods

also :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a Source #

alsoZero :: RWST r w s m a Source #

(Monoid w, Also m a, Monad m) => Also (RWST r w s m) a Source #

State instances threads the state through both monad of also in the normal left to right order, and so do not prevent early termination from the left monad (eg if the inner monad was a MaybeT or ExceptT. However, it is able to use the also to combine the return value.

Instance details

Defined in Control.Also

Methods

also :: RWST r w s m a -> RWST r w s m a -> RWST r w s m a Source #

alsoZero :: RWST r w s m a Source #

newtype Als f a Source #

Monoid under also. Mnemonic: Als for Also, just like Alt for Altenative

Constructors

Als 

Fields

Instances
Monad f => Monad (Als f) Source # 
Instance details

Defined in Control.Also

Methods

(>>=) :: Als f a -> (a -> Als f b) -> Als f b #

(>>) :: Als f a -> Als f b -> Als f b #

return :: a -> Als f a #

fail :: String -> Als f a #

Functor f => Functor (Als f) Source # 
Instance details

Defined in Control.Also

Methods

fmap :: (a -> b) -> Als f a -> Als f b #

(<$) :: a -> Als f b -> Als f a #

Applicative f => Applicative (Als f) Source # 
Instance details

Defined in Control.Also

Methods

pure :: a -> Als f a #

(<*>) :: Als f (a -> b) -> Als f a -> Als f b #

liftA2 :: (a -> b -> c) -> Als f a -> Als f b -> Als f c #

(*>) :: Als f a -> Als f b -> Als f b #

(<*) :: Als f a -> Als f b -> Als f a #

Alternative f => Alternative (Als f) Source # 
Instance details

Defined in Control.Also

Methods

empty :: Als f a #

(<|>) :: Als f a -> Als f a -> Als f a #

some :: Als f a -> Als f [a] #

many :: Als f a -> Als f [a] #

MonadPlus f => MonadPlus (Als f) Source # 
Instance details

Defined in Control.Also

Methods

mzero :: Als f a #

mplus :: Als f a -> Als f a -> Als f a #

Generic1 (Als f :: * -> *) Source # 
Instance details

Defined in Control.Also

Associated Types

type Rep1 (Als f) :: k -> * #

Methods

from1 :: Als f a -> Rep1 (Als f) a #

to1 :: Rep1 (Als f) a -> Als f a #

Enum (f a) => Enum (Als f a) Source # 
Instance details

Defined in Control.Also

Methods

succ :: Als f a -> Als f a #

pred :: Als f a -> Als f a #

toEnum :: Int -> Als f a #

fromEnum :: Als f a -> Int #

enumFrom :: Als f a -> [Als f a] #

enumFromThen :: Als f a -> Als f a -> [Als f a] #

enumFromTo :: Als f a -> Als f a -> [Als f a] #

enumFromThenTo :: Als f a -> Als f a -> Als f a -> [Als f a] #

Eq (f a) => Eq (Als f a) Source # 
Instance details

Defined in Control.Also

Methods

(==) :: Als f a -> Als f a -> Bool #

(/=) :: Als f a -> Als f a -> Bool #

Num (f a) => Num (Als f a) Source # 
Instance details

Defined in Control.Also

Methods

(+) :: Als f a -> Als f a -> Als f a #

(-) :: Als f a -> Als f a -> Als f a #

(*) :: Als f a -> Als f a -> Als f a #

negate :: Als f a -> Als f a #

abs :: Als f a -> Als f a #

signum :: Als f a -> Als f a #

fromInteger :: Integer -> Als f a #

Ord (f a) => Ord (Als f a) Source # 
Instance details

Defined in Control.Also

Methods

compare :: Als f a -> Als f a -> Ordering #

(<) :: Als f a -> Als f a -> Bool #

(<=) :: Als f a -> Als f a -> Bool #

(>) :: Als f a -> Als f a -> Bool #

(>=) :: Als f a -> Als f a -> Bool #

max :: Als f a -> Als f a -> Als f a #

min :: Als f a -> Als f a -> Als f a #

Read (f a) => Read (Als f a) Source # 
Instance details

Defined in Control.Also

Methods

readsPrec :: Int -> ReadS (Als f a) #

readList :: ReadS [Als f a] #

readPrec :: ReadPrec (Als f a) #

readListPrec :: ReadPrec [Als f a] #

Show (f a) => Show (Als f a) Source # 
Instance details

Defined in Control.Also

Methods

showsPrec :: Int -> Als f a -> ShowS #

show :: Als f a -> String #

showList :: [Als f a] -> ShowS #

Generic (Als f a) Source # 
Instance details

Defined in Control.Also

Associated Types

type Rep (Als f a) :: * -> * #

Methods

from :: Als f a -> Rep (Als f a) x #

to :: Rep (Als f a) x -> Als f a #

Also f a => Semigroup (Als f a) Source # 
Instance details

Defined in Control.Also

Methods

(<>) :: Als f a -> Als f a -> Als f a #

sconcat :: NonEmpty (Als f a) -> Als f a #

stimes :: Integral b => b -> Als f a -> Als f a #

Also f a => Monoid (Als f a) Source # 
Instance details

Defined in Control.Also

Methods

mempty :: Als f a #

mappend :: Als f a -> Als f a -> Als f a #

mconcat :: [Als f a] -> Als f a #

Newtype (Als f a) Source # 
Instance details

Defined in Control.Also

Associated Types

type O (Als f a) :: * #

Methods

pack :: O (Als f a) -> Als f a #

unpack :: Als f a -> O (Als f a) #

type Rep1 (Als f :: * -> *) Source # 
Instance details

Defined in Control.Also

type Rep1 (Als f :: * -> *) = D1 (MetaData "Als" "Control.Also" "alternators-1.0.0.0-CUyj9MLFkvaJMknoptjMiE" True) (C1 (MetaCons "Als" PrefixI True) (S1 (MetaSel (Just "getAls") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec1 f)))
type Rep (Als f a) Source # 
Instance details

Defined in Control.Also

type Rep (Als f a) = D1 (MetaData "Als" "Control.Also" "alternators-1.0.0.0-CUyj9MLFkvaJMknoptjMiE" True) (C1 (MetaCons "Als" PrefixI True) (S1 (MetaSel (Just "getAls") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f a))))
type O (Als f a) Source # 
Instance details

Defined in Control.Also

type O (Als f a) = GO (Rep (Als f a))