RebindableSyntax on individual do blocks

I have a program that uses both monads and indexed monads, and I'd like to use do-notation for each in the same source file. Is there a way to rebind syntax for only the do blocks that make use of an indexed monad? Thanks, Mark

I don't know anything about indexed monads, but it seems that you can use
the 'where' keyword to rebind (>>) and return for any block you want [1].
An example from [1]:
addNumbers = do
80
60
10
where (>>) = (+)
It might be possible to generate this where block using TH.
There is also a quasi-quoter available for indexed-do-notation [2].
[1]:
https://ocharles.org.uk/blog/guest-posts/2014-12-06-rebindable-syntax.html
[2]: https://github.com/fumieval/indexed-do-notation
On 23 June 2015 at 00:09, Mark Roberts
I have a program that uses both monads and indexed monads, and I'd like to use do-notation for each in the same source file. Is there a way to rebind syntax for only the do blocks that make use of an indexed monad?
Thanks, Mark
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
-- Regards Sumit Sahrawat

Hi Mark,
RebindableSyntax uses whatever (>>), (>>=) and return are in scope. So
if you bind them in a `let` or `where`, you should be able to use
different ones for different do blocks.
Erik
On Mon, Jun 22, 2015 at 8:39 PM, Mark Roberts
I have a program that uses both monads and indexed monads, and I'd like to use do-notation for each in the same source file. Is there a way to rebind syntax for only the do blocks that make use of an indexed monad?
Thanks, Mark
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Ah, I missed that bit. Thank you!
Mark
On Mon, Jun 22, 2015 at 12:18 PM, Erik Hesselink
Hi Mark,
RebindableSyntax uses whatever (>>), (>>=) and return are in scope. So if you bind them in a `let` or `where`, you should be able to use different ones for different do blocks.
Erik
On Mon, Jun 22, 2015 at 8:39 PM, Mark Roberts
wrote: I have a program that uses both monads and indexed monads, and I'd like to use do-notation for each in the same source file. Is there a way to rebind syntax for only the do blocks that make use of an indexed monad?
Thanks, Mark
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe

Here's a pretty elegant (read: hacky?) way of working with RebindableSyntax:
=== Foo.hs
module Foo where
import Prelude hiding (Monad (..))
import qualified Prelude as P
data MyMonad m a b = MyMonad
{ (>>=) :: m a -> (a -> m b) -> m b
, (>>) :: m a -> m b -> m b
, return :: a -> m a
, fail :: String -> m a
}
ioMonad :: MyMonad IO a b
ioMonad = MyMonad (P.>>=) (P.>>) P.return P.fail
=== Bar.hs
{-# OPTIONS -fno-warn-name-shadowing #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE RebindableSyntax #-}
module Bar where
import Prelude
import qualified Foo
normalDo :: Monad m => m ()
normalDo = do
return ()
-- Inferred: ioDo :: IO ()
ioDo = do
return ()
where Foo.MyMonad{..} = Foo.ioMonad
Cheers,
Adam
On Mon, Jun 22, 2015 at 9:19 PM, Mark Roberts
Ah, I missed that bit. Thank you! Mark
On Mon, Jun 22, 2015 at 12:18 PM, Erik Hesselink
wrote: Hi Mark,
RebindableSyntax uses whatever (>>), (>>=) and return are in scope. So if you bind them in a `let` or `where`, you should be able to use different ones for different do blocks.
Erik
On Mon, Jun 22, 2015 at 8:39 PM, Mark Roberts
wrote: I have a program that uses both monads and indexed monads, and I'd like to use do-notation for each in the same source file. Is there a way to rebind syntax for only the do blocks that make use of an indexed monad?
Thanks, Mark
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
_______________________________________________ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
participants (4)
-
Adam Bergmark
-
Erik Hesselink
-
Mark Roberts
-
Sumit Sahrawat, Maths & Computing, IIT (BHU)