semigroupoids-6.0.0.1: Semigroupoids: Category sans id
Copyright(C) 2011-2015 Edward Kmett
LicenseBSD-style (see the file LICENSE)
MaintainerEdward Kmett <ekmett@gmail.com>
Stabilityprovisional
Portabilityportable
Safe HaskellTrustworthy
LanguageHaskell2010

Data.Functor.Alt

Description

 
Synopsis

Documentation

class Functor f => Alt f where Source #

Laws:

<!> is associative:             (a <!> b) <!> c = a <!> (b <!> c)
<$> left-distributes over <!>:  f <$> (a <!> b) = (f <$> a) <!> (f <$> b)

If extended to an Alternative then <!> should equal <|>.

Ideally, an instance of Alt also satisfies the "left distribution" law of MonadPlus with respect to <.>:

<.> right-distributes over <!>: (a <!> b) <.> c = (a <.> c) <!> (b <.> c)

IO, Either a, ExceptT e m and STM instead satisfy the "left catch" law:

pure a <!> b = pure a

Maybe and Identity satisfy both "left distribution" and "left catch".

These variations cannot be stated purely in terms of the dependencies of Alt.

When and if MonadPlus is successfully refactored, this class should also be refactored to remove these instances.

The right distributive law should extend in the cases where the a Bind or Monad is provided to yield variations of the right distributive law:

(m <!> n) >>- f = (m >>- f) <!> (m >>- f)
(m <!> n) >>= f = (m >>= f) <!> (m >>= f)

Minimal complete definition

(<!>)

Methods

(<!>) :: f a -> f a -> f a infixl 3 Source #

<|> without a required empty

some :: Applicative f => f a -> f [a] Source #

many :: Applicative f => f a -> f [a] Source #

Instances

Instances details
Alt Identity Source #

Choose the first option every time. While 'choose the last option' every time is also valid, this instance satisfies more laws.

Since: 5.3.6

Instance details

Defined in Data.Functor.Alt

Alt First Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: First a -> First a -> First a Source #

some :: Applicative First => First a -> First [a] Source #

many :: Applicative First => First a -> First [a] Source #

Alt Last Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Last a -> Last a -> Last a Source #

some :: Applicative Last => Last a -> Last [a] Source #

many :: Applicative Last => Last a -> Last [a] Source #

Alt First Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: First a -> First a -> First a Source #

some :: Applicative First => First a -> First [a] Source #

many :: Applicative First => First a -> First [a] Source #

Alt Last Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Last a -> Last a -> Last a Source #

some :: Applicative Last => Last a -> Last [a] Source #

many :: Applicative Last => Last a -> Last [a] Source #

Alt IntMap Source # 
Instance details

Defined in Data.Functor.Alt

Alt Seq Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Seq a -> Seq a -> Seq a Source #

some :: Applicative Seq => Seq a -> Seq [a] Source #

many :: Applicative Seq => Seq a -> Seq [a] Source #

Alt IO Source #

This instance does not actually satisfy the (<.>) right distributive law It instead satisfies the "left catch" law

Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: IO a -> IO a -> IO a Source #

some :: Applicative IO => IO a -> IO [a] Source #

many :: Applicative IO => IO a -> IO [a] Source #

Alt NonEmpty Source # 
Instance details

Defined in Data.Functor.Alt

Alt Maybe Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Maybe a -> Maybe a -> Maybe a Source #

some :: Applicative Maybe => Maybe a -> Maybe [a] Source #

many :: Applicative Maybe => Maybe a -> Maybe [a] Source #

Alt [] Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: [a] -> [a] -> [a] Source #

some :: Applicative [] => [a] -> [[a]] Source #

many :: Applicative [] => [a] -> [[a]] Source #

MonadPlus m => Alt (WrappedMonad m) Source # 
Instance details

Defined in Data.Functor.Alt

Alt (Either a) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Either a a0 -> Either a a0 -> Either a a0 Source #

some :: Applicative (Either a) => Either a a0 -> Either a [a0] Source #

many :: Applicative (Either a) => Either a a0 -> Either a [a0] Source #

Alt (Proxy :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Proxy a -> Proxy a -> Proxy a Source #

some :: Applicative Proxy => Proxy a -> Proxy [a] Source #

many :: Applicative Proxy => Proxy a -> Proxy [a] Source #

Alt (U1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: U1 a -> U1 a -> U1 a Source #

some :: Applicative U1 => U1 a -> U1 [a] Source #

many :: Applicative U1 => U1 a -> U1 [a] Source #

Alt (V1 :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: V1 a -> V1 a -> V1 a Source #

some :: Applicative V1 => V1 a -> V1 [a] Source #

many :: Applicative V1 => V1 a -> V1 [a] Source #

Ord k => Alt (Map k) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Map k a -> Map k a -> Map k a Source #

some :: Applicative (Map k) => Map k a -> Map k [a] Source #

many :: Applicative (Map k) => Map k a -> Map k [a] Source #

Alternative f => Alt (WrappedApplicative f) Source # 
Instance details

Defined in Data.Functor.Alt

Alt f => Alt (Lift f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Lift f a -> Lift f a -> Lift f a Source #

some :: Applicative (Lift f) => Lift f a -> Lift f [a] Source #

many :: Applicative (Lift f) => Lift f a -> Lift f [a] Source #

Apply f => Alt (ListT f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: ListT f a -> ListT f a -> ListT f a Source #

some :: Applicative (ListT f) => ListT f a -> ListT f [a] Source #

many :: Applicative (ListT f) => ListT f a -> ListT f [a] Source #

(Functor f, Monad f) => Alt (MaybeT f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: MaybeT f a -> MaybeT f a -> MaybeT f a Source #

some :: Applicative (MaybeT f) => MaybeT f a -> MaybeT f [a] Source #

many :: Applicative (MaybeT f) => MaybeT f a -> MaybeT f [a] Source #

(Hashable k, Eq k) => Alt (HashMap k) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: HashMap k a -> HashMap k a -> HashMap k a Source #

some :: Applicative (HashMap k) => HashMap k a -> HashMap k [a] Source #

many :: Applicative (HashMap k) => HashMap k a -> HashMap k [a] Source #

ArrowPlus a => Alt (WrappedArrow a b) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: WrappedArrow a b a0 -> WrappedArrow a b a0 -> WrappedArrow a b a0 Source #

some :: Applicative (WrappedArrow a b) => WrappedArrow a b a0 -> WrappedArrow a b [a0] Source #

many :: Applicative (WrappedArrow a b) => WrappedArrow a b a0 -> WrappedArrow a b [a0] Source #

Alt f => Alt (Rec1 f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Rec1 f a -> Rec1 f a -> Rec1 f a Source #

some :: Applicative (Rec1 f) => Rec1 f a -> Rec1 f [a] Source #

many :: Applicative (Rec1 f) => Rec1 f a -> Rec1 f [a] Source #

Alt f => Alt (Static f a) Source # 
Instance details

Defined in Data.Semigroupoid.Static

Methods

(<!>) :: Static f a a0 -> Static f a a0 -> Static f a a0 Source #

some :: Applicative (Static f a) => Static f a a0 -> Static f a [a0] Source #

many :: Applicative (Static f a) => Static f a a0 -> Static f a [a0] Source #

Alt f => Alt (Backwards f) Source # 
Instance details

Defined in Data.Functor.Alt

(Functor f, Monad f) => Alt (ErrorT e f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: ErrorT e f a -> ErrorT e f a -> ErrorT e f a Source #

some :: Applicative (ErrorT e f) => ErrorT e f a -> ErrorT e f [a] Source #

many :: Applicative (ErrorT e f) => ErrorT e f a -> ErrorT e f [a] Source #

(Functor f, Monad f, Semigroup e) => Alt (ExceptT e f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: ExceptT e f a -> ExceptT e f a -> ExceptT e f a Source #

some :: Applicative (ExceptT e f) => ExceptT e f a -> ExceptT e f [a] Source #

many :: Applicative (ExceptT e f) => ExceptT e f a -> ExceptT e f [a] Source #

Alt f => Alt (IdentityT f) Source # 
Instance details

Defined in Data.Functor.Alt

Alt f => Alt (ReaderT e f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: ReaderT e f a -> ReaderT e f a -> ReaderT e f a Source #

some :: Applicative (ReaderT e f) => ReaderT e f a -> ReaderT e f [a] Source #

many :: Applicative (ReaderT e f) => ReaderT e f a -> ReaderT e f [a] Source #

Alt f => Alt (StateT e f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: StateT e f a -> StateT e f a -> StateT e f a Source #

some :: Applicative (StateT e f) => StateT e f a -> StateT e f [a] Source #

many :: Applicative (StateT e f) => StateT e f a -> StateT e f [a] Source #

Alt f => Alt (StateT e f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: StateT e f a -> StateT e f a -> StateT e f a Source #

some :: Applicative (StateT e f) => StateT e f a -> StateT e f [a] Source #

many :: Applicative (StateT e f) => StateT e f a -> StateT e f [a] Source #

Alt f => Alt (WriterT w f) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: WriterT w f a -> WriterT w f a -> WriterT w f a Source #

some :: Applicative (WriterT w f) => WriterT w f a -> WriterT w f [a] Source #

many :: Applicative (WriterT w f) => WriterT w f a -> WriterT w f [a] Source #

Alt f => Alt (WriterT w f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: WriterT w f a -> WriterT w f a -> WriterT w f a Source #

some :: Applicative (WriterT w f) => WriterT w f a -> WriterT w f [a] Source #

many :: Applicative (WriterT w f) => WriterT w f a -> WriterT w f [a] Source #

Alt f => Alt (WriterT w f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: WriterT w f a -> WriterT w f a -> WriterT w f a Source #

some :: Applicative (WriterT w f) => WriterT w f a -> WriterT w f [a] Source #

many :: Applicative (WriterT w f) => WriterT w f a -> WriterT w f [a] Source #

Alt f => Alt (Reverse f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Reverse f a -> Reverse f a -> Reverse f a Source #

some :: Applicative (Reverse f) => Reverse f a -> Reverse f [a] Source #

many :: Applicative (Reverse f) => Reverse f a -> Reverse f [a] Source #

(Alt f, Alt g) => Alt (Product f g) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Product f g a -> Product f g a -> Product f g a Source #

some :: Applicative (Product f g) => Product f g a -> Product f g [a] Source #

many :: Applicative (Product f g) => Product f g a -> Product f g [a] Source #

(Alt f, Alt g) => Alt (f :*: g) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: (f :*: g) a -> (f :*: g) a -> (f :*: g) a Source #

some :: Applicative (f :*: g) => (f :*: g) a -> (f :*: g) [a] Source #

many :: Applicative (f :*: g) => (f :*: g) a -> (f :*: g) [a] Source #

Semigroup c => Alt (K1 i c :: Type -> Type) Source #
since 5.3.8
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: K1 i c a -> K1 i c a -> K1 i c a Source #

some :: Applicative (K1 i c) => K1 i c a -> K1 i c [a] Source #

many :: Applicative (K1 i c) => K1 i c a -> K1 i c [a] Source #

(Alt f, Functor g) => Alt (Compose f g) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: Compose f g a -> Compose f g a -> Compose f g a Source #

some :: Applicative (Compose f g) => Compose f g a -> Compose f g [a] Source #

many :: Applicative (Compose f g) => Compose f g a -> Compose f g [a] Source #

(Alt f, Functor g) => Alt (f :.: g) Source #

Since: 5.3.8

Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a Source #

some :: Applicative (f :.: g) => (f :.: g) a -> (f :.: g) [a] Source #

many :: Applicative (f :.: g) => (f :.: g) a -> (f :.: g) [a] Source #

Alt f => Alt (M1 i c f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: M1 i c f a -> M1 i c f a -> M1 i c f a Source #

some :: Applicative (M1 i c f) => M1 i c f a -> M1 i c f [a] Source #

many :: Applicative (M1 i c f) => M1 i c f a -> M1 i c f [a] Source #

Alt f => Alt (RWST r w s f) Source #

Since: 5.3.6

Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: RWST r w s f a -> RWST r w s f a -> RWST r w s f a Source #

some :: Applicative (RWST r w s f) => RWST r w s f a -> RWST r w s f [a] Source #

many :: Applicative (RWST r w s f) => RWST r w s f a -> RWST r w s f [a] Source #

Alt f => Alt (RWST r w s f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: RWST r w s f a -> RWST r w s f a -> RWST r w s f a Source #

some :: Applicative (RWST r w s f) => RWST r w s f a -> RWST r w s f [a] Source #

many :: Applicative (RWST r w s f) => RWST r w s f a -> RWST r w s f [a] Source #

Alt f => Alt (RWST r w s f) Source # 
Instance details

Defined in Data.Functor.Alt

Methods

(<!>) :: RWST r w s f a -> RWST r w s f a -> RWST r w s f a Source #

some :: Applicative (RWST r w s f) => RWST r w s f a -> RWST r w s f [a] Source #

many :: Applicative (RWST r w s f) => RWST r w s f a -> RWST r w s f [a] Source #

optional :: (Alt f, Applicative f) => f a -> f (Maybe a) Source #

One or none.

galt :: (Generic1 f, Alt (Rep1 f)) => f a -> f a -> f a Source #

Generic (<!>). Caveats:

  1. Will not compile if f is a sum type.
  2. Any types where the a does not appear must have a Semigroup instance.

Since: 5.3.8