Name for the following combinators?

Dear all, Recently I have found myself using these two combinators a lot: http://lpaste.net/97643 They basically allow composition of any m satisfying (Monad m, Traversable m). I have been thinking about moving them to a separate package and giving them better names (in the original paper, they are simply called join and bind). Does anyone have a better suggestion for the name of the package, module and the two combinators? Should they be called joinDefault, or simply called join and bind to be imported with a qualifier? This might be a bicycle-shed question, but I tend to find stylistic questions important when it comes to improving clarity and readability. Best wishes, Hans

On Sat, Dec 28, 2013 at 04:47:40PM +0100, Hans Höglund wrote:
Recently I have found myself using these two combinators a lot: http://lpaste.net/97643
FYI it looks a lot like these give rise to a monad transformer. Tom

On Sat, Dec 28, 2013 at 03:58:10PM +0000, Tom Ellis wrote:
On Sat, Dec 28, 2013 at 04:47:40PM +0100, Hans Höglund wrote:
Recently I have found myself using these two combinators a lot: http://lpaste.net/97643
FYI it looks a lot like these give rise to a monad transformer.
Specifically, the following. Careful though: I haven't made any effort to check this satisfies the monad or transformer laws. If 'Wrap m n' genuinely satisfies the monad laws then you don't need new combinators. Just Wrap the type constructors and get a real monad. (If 'Wrap m' is genuinely a monad transformer, so much the better!) Tom import Control.Monad.Trans (MonadTrans, lift) import Control.Monad (join) import qualified Data.Traversable as T import Data.Traversable (Traversable) data Wrap m n a = Wrap (m (n a)) unwrap :: Wrap m n a -> m (n a) unwrap (Wrap m) = m mbind :: (Monad m, Monad n, Functor m, Traversable n) => (a -> m (n b)) -> m (n a) -> m (n b) mbind = (join .) . fmap . (fmap join .) . T.mapM instance (Functor m, Traversable n, Monad m, Monad n) => Monad (Wrap m n) where return = Wrap . return . return m >>= f = Wrap (mbind (unwrap . f) (unwrap m)) instance Monad m => MonadTrans (Wrap m) where lift = Wrap . return

On Sat, Dec 28, 2013 at 04:13:52PM +0000, Tom Ellis wrote:
On Sat, Dec 28, 2013 at 03:58:10PM +0000, Tom Ellis wrote:
On Sat, Dec 28, 2013 at 04:47:40PM +0100, Hans Höglund wrote:
Recently I have found myself using these two combinators a lot: http://lpaste.net/97643
FYI it looks a lot like these give rise to a monad transformer.
Specifically, the following. Careful though: I haven't made any effort to check this satisfies the monad or transformer laws.
In fact, since is is 'n' that requires the 'Monad' constraint, I suspect you'll need to swap the order of the type arguments to get a monad transformer: data Wrap n m a = Wrap (m (n a)) Anyway, my main point remains: your first check should be whether what you have can be captured as a genuine monad.
import Control.Monad.Trans (MonadTrans, lift) import Control.Monad (join) import qualified Data.Traversable as T import Data.Traversable (Traversable)
data Wrap m n a = Wrap (m (n a))
unwrap :: Wrap m n a -> m (n a) unwrap (Wrap m) = m
mbind :: (Monad m, Monad n, Functor m, Traversable n) => (a -> m (n b)) -> m (n a) -> m (n b) mbind = (join .) . fmap . (fmap join .) . T.mapM
instance (Functor m, Traversable n, Monad m, Monad n) => Monad (Wrap m n) where return = Wrap . return . return m >>= f = Wrap (mbind (unwrap . f) (unwrap m))
instance Monad m => MonadTrans (Wrap m) where lift = Wrap . return _______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

On Sat, Dec 28, 2013 at 04:18:30PM +0000, Tom Ellis wrote:
On Sat, Dec 28, 2013 at 04:13:52PM +0000, Tom Ellis wrote:
On Sat, Dec 28, 2013 at 03:58:10PM +0000, Tom Ellis wrote:
On Sat, Dec 28, 2013 at 04:47:40PM +0100, Hans Höglund wrote:
Recently I have found myself using these two combinators a lot: http://lpaste.net/97643
FYI it looks a lot like these give rise to a monad transformer.
Specifically, the following. Careful though: I haven't made any effort to check this satisfies the monad or transformer laws.
In fact, since is is 'n' that requires the 'Monad' constraint, I suspect you'll need to swap the order of the type arguments to get a monad transformer:
I keep typing too fast. I mean "it is 'n' that requires the *Traversable* constraint".

On Sat, Dec 28, 2013 at 5:13 PM, Tom Ellis
data Wrap m n a = Wrap (m (n a))
This is Compose [0] from traversable. It doesn't have a Monad instance, though... Erik [0] http://hackage.haskell.org/package/transformers-0.3.0.0/docs/Data-Functor-Co...
participants (3)
-
Erik Hesselink
-
Hans Höglund
-
Tom Ellis