[Haskell-cafe] RebindableSyntax on individual do blocks

Adam Bergmark adam at bergmark.nl
Mon Jun 22 19:27:53 UTC 2015


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 <markandrusroberts at gmail.com>
wrote:

> Ah, I missed that bit. Thank you!
> Mark
>
> On Mon, Jun 22, 2015 at 12:18 PM, Erik Hesselink <hesselink at gmail.com>
> 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
>> <markandrusroberts at gmail.com> 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 at haskell.org
>> > http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>> >
>>
>
>
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://mail.haskell.org/cgi-bin/mailman/listinfo/haskell-cafe
>
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://mail.haskell.org/pipermail/haskell-cafe/attachments/20150622/c9eaba65/attachment.html>


More information about the Haskell-Cafe mailing list