1
votes

I'm writing interpreter in haskell. I want to do that with monads. I already created parser, so I have a lot of functions :: State -> MyMonad State, and I can run my program using bind. m >>= inst1 >>= inst2. Everything works perfectly fine, but I have no idea how to create instruction print (or read) in my language with that monad.

I don't want simple, but ugly, solutions like keeping strings to print inside State and printing in main at the end. (What if I have infinity while with print?) I couldn't understand texts from web about that part of monad functionality. There were some explanations like "pack inside IO Monad, it's quite straightforward", but without any working examples. And almost all printing tutorials was about printing in main.

To better explain problem, I prepared minimal "interpreter" example (below). There State is just Int, my monad is AutomatM instructions have type :: Int -> AutomatM Int. So possible instruction is:

inc :: Int -> AutomatM Int
inc x = return (x+1)

I designed it as simple as I could think:

import Control.Applicative
import Control.Monad (liftM, ap)
import Control.Monad.IO.Class (MonadIO(..))
import System.IO

data AutomatM a = AutomatError | Running a

instance Show a => Show (AutomatM a) where
    show (AutomatError) = "AutomatError"
    show (Running a) = "Running " ++ show a

instance Functor AutomatM where
  fmap = liftM

instance Applicative AutomatM where
  pure  = return
  (<*>) = ap


instance Monad AutomatM where
  return x = Running x
  m >>= g = case m of
              AutomatError -> AutomatError
              Running x -> g x
magicPrint x = do
    -- print x         -- How can I make print work?
    -- c <- getLine    -- And if that is as simple as print
    b <- return "1000" -- how can I change constant to c?
    return (x + (read b :: Int))

main = do
    a <- getLine
    print $ (Running (read a :: Int)) >>= (\x -> return (x*2)) >>= magicPrint

My main target is to add print x inside magicPrint. However if it's not harder, it would be nice to have getLine.

I changed state in magicPrint, because print in my language has side effects.

I know that I need something with monad transformers and maybe MonadIO, but it's hard to find any tutorial with simple explanation for beginners. Therefore I would very appreciate extending my minimal code example to work with prints (and maybe getLine/other read Int) and some explanations to that (perhaps with links).

Functor and Aplicative code is based on Defining a new monad in haskell raises no instance for Applicative

1
This isn't an answer to your question, but there's a good (but old) read on monad transformers: page.mi.fu-berlin.de/scravy/realworldhaskell/materialien/… It walks through going from a non-monad based interpreter to a full on monad stack. Note that some of the code won't work directly anymore, but it still does a good job of building up the stack carefully in a way that is still applicable today.Marc Talbot
@MarcTalbot thank you, I didn't see that pdf. I'll read it for sure. However, as I don't see any working example (with new Haskell) of such "basic" (printing in monads) functionality, I believe that such minimal example would be very helpful for me and others. Thank you for your answer!Tacet
You will have to either have IO in the stack or return some value and then print it. I answered another question about printing in a State monad. Take a look and see if it makes any sense stackoverflow.com/a/50334665/412417MCH
@MCH I can add additional IO stack to State, if it will allow me printing and reading values, but still I'm not sure how to do that with monads. Just in print function AFlow (x+1, (print x):olds) will work? I'm in process of reading above pdf, so maybe it will be clear for me soon. I still don't know how to move your answer to my code. However, I appreciate your effort.Tacet
@MCH I don't see how to do that, cause rb <- getLine is impossible outside IO monad, same with simple print. Returning like return (sequence [a, px], x + (read b :: Int)) where a is old IO () and px is print x doesn't look like working solution. So I don't know how I should "put on stack IO". Returning values to main is hard, cause I want to print text asap (as interpreter may work very long, and I want to see results as soon as possible).Tacet

1 Answers

7
votes

In order to create a new type with a Monad instance and access IO form inside of it, you will need to create another monad transformer type called AutomatMT and declare an instance of Monad, MonadTrans, etc. for it. It involves a lot of boilerplate code. I'll try to clarify anything that doesn't make sense.

import Control.Applicative
import Control.Monad (liftM, ap)
import Control.Monad.IO.Class (MonadIO(..))
import System.IO
import Control.Monad.Trans.Class (MonadTrans(..), lift)

data AutomatM a = AutomatError | Running a

instance Show a => Show (AutomatM a) where
    show (AutomatError) = "AutomatError"
    show (Running a) = "Running " ++ show a

instance Functor AutomatM where
  fmap = liftM

instance Applicative AutomatM where
  pure  = return
  (<*>) = ap

instance Monad AutomatM where
  return x = Running x
  m >>= g = case m of
              AutomatError -> AutomatError
              Running x -> g x

newtype AutomatMT m a = AutomatMT { runAutomatMT :: m (AutomatM a) }

mapAutomatMT :: (m (AutomatM a) -> n (AutomatM b)) -> AutomatMT m a -> AutomatMT n b
mapAutomatMT f = AutomatMT . f . runAutomatMT

instance (Functor m) => Functor (AutomatMT m) where
    fmap f = mapAutomatMT (fmap (fmap f))

instance MonadTrans AutomatMT where
    lift = AutomatMT . liftM Running

instance (Functor m, Monad m) => Applicative (AutomatMT m) where
    pure = AutomatMT . return . Running

    mf <*> mx = AutomatMT $ do
        mb_f <- runAutomatMT mf
        case mb_f of
            AutomatError -> return AutomatError
            Running f  -> do
                mb_x <- runAutomatMT mx
                case mb_x of
                    AutomatError -> return AutomatError
                    Running x  -> return (Running (f x))

instance (MonadIO m) => MonadIO (AutomatMT m) where
    liftIO = lift . liftIO

instance (Monad m) => Monad (AutomatMT m) where
    x >>= f = AutomatMT $ do
        v <- runAutomatMT x
        case v of
            AutomatError -> return AutomatError
            Running y  -> runAutomatMT (f y)

    fail _ = AutomatMT (return AutomatError)


magicPrint :: String -> (AutomatMT IO String)
magicPrint x = do
  liftIO $ print $ "You gave magic print " ++ x
  let x = "12"
  y <- pure 1
  liftIO $ print y
  pure $ "1"

main = do
  print "Enter some text"
  a <- getLine
  b <- runAutomatMT $ magicPrint a
  pure ()