subcategories-0.1.0.0: Subcategories induced by class constraints

Safe HaskellNone
LanguageHaskell2010

Control.Subcategory.Bind

Documentation

class CFunctor m => CBind m where Source #

Minimal complete definition

Nothing

Methods

(>>-) :: (Dom m a, Dom m b) => m a -> (a -> m b) -> m b infixl 1 Source #

(>>-) :: (Dom m a, Dom m b, Dom m (m b)) => m a -> (a -> m b) -> m b infixl 1 Source #

cjoin :: (Dom m (m a), Dom m a) => m (m a) -> m a Source #

Instances
CBind [] Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom [] a, Dom [] b) => [a] -> (a -> [b]) -> [b] Source #

cjoin :: (Dom [] [a], Dom [] a) => [[a]] -> [a] Source #

CBind Maybe Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom Maybe a, Dom Maybe b) => Maybe a -> (a -> Maybe b) -> Maybe b Source #

cjoin :: (Dom Maybe (Maybe a), Dom Maybe a) => Maybe (Maybe a) -> Maybe a Source #

CBind IO Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom IO a, Dom IO b) => IO a -> (a -> IO b) -> IO b Source #

cjoin :: (Dom IO (IO a), Dom IO a) => IO (IO a) -> IO a Source #

CBind Option Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom Option a, Dom Option b) => Option a -> (a -> Option b) -> Option b Source #

cjoin :: (Dom Option (Option a), Dom Option a) => Option (Option a) -> Option a Source #

CBind Identity Source # 
Instance details

Defined in Control.Subcategory.Bind

CBind STM Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom STM a, Dom STM b) => STM a -> (a -> STM b) -> STM b Source #

cjoin :: (Dom STM (STM a), Dom STM a) => STM (STM a) -> STM a Source #

CBind ReadPrec Source # 
Instance details

Defined in Control.Subcategory.Bind

CBind ReadP Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom ReadP a, Dom ReadP b) => ReadP a -> (a -> ReadP b) -> ReadP b Source #

cjoin :: (Dom ReadP (ReadP a), Dom ReadP a) => ReadP (ReadP a) -> ReadP a Source #

CBind NonEmpty Source # 
Instance details

Defined in Control.Subcategory.Bind

CBind IntMap Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom IntMap a, Dom IntMap b) => IntMap a -> (a -> IntMap b) -> IntMap b Source #

cjoin :: (Dom IntMap (IntMap a), Dom IntMap a) => IntMap (IntMap a) -> IntMap a Source #

CBind Tree Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom Tree a, Dom Tree b) => Tree a -> (a -> Tree b) -> Tree b Source #

cjoin :: (Dom Tree (Tree a), Dom Tree a) => Tree (Tree a) -> Tree a Source #

CBind Seq Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom Seq a, Dom Seq b) => Seq a -> (a -> Seq b) -> Seq b Source #

cjoin :: (Dom Seq (Seq a), Dom Seq a) => Seq (Seq a) -> Seq a Source #

CBind Set Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom Set a, Dom Set b) => Set a -> (a -> Set b) -> Set b Source #

cjoin :: (Dom Set (Set a), Dom Set a) => Set (Set a) -> Set a Source #

CBind HashSet Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom HashSet a, Dom HashSet b) => HashSet a -> (a -> HashSet b) -> HashSet b Source #

cjoin :: (Dom HashSet (HashSet a), Dom HashSet a) => HashSet (HashSet a) -> HashSet a Source #

CBind (Either a) Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom (Either a) a0, Dom (Either a) b) => Either a a0 -> (a0 -> Either a b) -> Either a b Source #

cjoin :: (Dom (Either a) (Either a a0), Dom (Either a) a0) => Either a (Either a a0) -> Either a a0 Source #

Semigroup w => CBind ((,) w) Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom ((,) w) a, Dom ((,) w) b) => (w, a) -> (a -> (w, b)) -> (w, b) Source #

cjoin :: (Dom ((,) w) (w, a), Dom ((,) w) a) => (w, (w, a)) -> (w, a) Source #

CBind (ST s) Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom (ST s) a, Dom (ST s) b) => ST s a -> (a -> ST s b) -> ST s b Source #

cjoin :: (Dom (ST s) (ST s a), Dom (ST s) a) => ST s (ST s a) -> ST s a Source #

CBind (ST s) Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom (ST s) a, Dom (ST s) b) => ST s a -> (a -> ST s b) -> ST s b Source #

cjoin :: (Dom (ST s) (ST s a), Dom (ST s) a) => ST s (ST s a) -> ST s a Source #

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

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom (Map k) a, Dom (Map k) b) => Map k a -> (a -> Map k b) -> Map k b Source #

cjoin :: (Dom (Map k) (Map k a), Dom (Map k) a) => Map k (Map k a) -> Map k a Source #

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

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom (HashMap k) a, Dom (HashMap k) b) => HashMap k a -> (a -> HashMap k b) -> HashMap k b Source #

cjoin :: (Dom (HashMap k) (HashMap k a), Dom (HashMap k) a) => HashMap k (HashMap k a) -> HashMap k a Source #

Monad m => CBind (WrapFunctor m) Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom (WrapFunctor m) a, Dom (WrapFunctor m) b) => WrapFunctor m a -> (a -> WrapFunctor m b) -> WrapFunctor m b Source #

cjoin :: (Dom (WrapFunctor m) (WrapFunctor m a), Dom (WrapFunctor m) a) => WrapFunctor m (WrapFunctor m a) -> WrapFunctor m a Source #

CBind (WrapMono IntSet :: Type -> Type) Source # 
Instance details

Defined in Control.Subcategory.Bind

CBind ((->) a :: Type -> Type) Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom ((->) a) a0, Dom ((->) a) b) => (a -> a0) -> (a0 -> a -> b) -> a -> b Source #

cjoin :: (Dom ((->) a) (a -> a0), Dom ((->) a) a0) => (a -> (a -> a0)) -> a -> a0 Source #

(CBind m, CBind n) => CBind (Product m n) Source # 
Instance details

Defined in Control.Subcategory.Bind

Methods

(>>-) :: (Dom (Product m n) a, Dom (Product m n) b) => Product m n a -> (a -> Product m n b) -> Product m n b Source #

cjoin :: (Dom (Product m n) (Product m n a), Dom (Product m n) a) => Product m n (Product m n a) -> Product m n a Source #

class (CBind f, CPointed f) => CMonad f Source #

Instances
(CBind f, CPointed f) => CMonad f Source # 
Instance details

Defined in Control.Subcategory.Bind

creturn :: (Dom m a, CMonad m) => a -> m a Source #

(-<<) :: (Dom m b, Dom m a, CBind m) => (a -> m b) -> m a -> m b infixr 1 Source #