{-# language Safe #-}
{-# options_ghc -Wno-orphans #-}
module LazyAsync.Orphans where
import LazyAsync.Actions
import LazyAsync.Prelude
import LazyAsync.Types
instance Applicative LazyAsync where
pure :: a -> LazyAsync a
pure = a -> LazyAsync a
forall a. a -> LazyAsync a
pureLazyAsync
<*> :: LazyAsync (a -> b) -> LazyAsync a -> LazyAsync b
(<*>) = LazyAsync (a -> b) -> LazyAsync a -> LazyAsync b
forall a b. LazyAsync (a -> b) -> LazyAsync a -> LazyAsync b
apply
instance Alternative LazyAsync where
empty :: LazyAsync a
empty = LazyAsync a
forall a. LazyAsync a
emptyLazyAsync
<|> :: LazyAsync a -> LazyAsync a -> LazyAsync a
(<|>) = LazyAsync a -> LazyAsync a -> LazyAsync a
forall a. LazyAsync a -> LazyAsync a -> LazyAsync a
choose
instance Applicative Status where
pure :: a -> Status a
pure = a -> Status a
forall a. a -> Status a
pureStatus
<*> :: Status (a -> b) -> Status a -> Status b
(<*>) = Status (a -> b) -> Status a -> Status b
forall a b. Status (a -> b) -> Status a -> Status b
applyStatus
instance Alternative Status where
empty :: Status a
empty = Status a
forall a. Status a
emptyStatus
<|> :: Status a -> Status a -> Status a
(<|>) = Status a -> Status a -> Status a
forall a. Status a -> Status a -> Status a
chooseStatus
instance Applicative Outcome where
pure :: a -> Outcome a
pure = a -> Outcome a
forall a. a -> Outcome a
pureOutcome
<*> :: Outcome (a -> b) -> Outcome a -> Outcome b
(<*>) = Outcome (a -> b) -> Outcome a -> Outcome b
forall a b. Outcome (a -> b) -> Outcome a -> Outcome b
applyOutcome
instance Alternative Outcome where
empty :: Outcome a
empty = Outcome a
forall a. Outcome a
emptyOutcome
<|> :: Outcome a -> Outcome a -> Outcome a
(<|>) = Outcome a -> Outcome a -> Outcome a
forall a. Outcome a -> Outcome a -> Outcome a
chooseOutcome