
Hi all, I'm trying to write a fairly simple program to understand Haskell in practice. I am implementing a simple REPL where I can write some text, and that text can be parsed into a command with arguments. Then, I would like to be able to turn this into a 'plugin' system of sorts, with a module/logic per command. I understand the Text.Parsec library may already provide these things out of the box, but for now, I would prefer to reinvent the wheel. The program below is what I have working right now (very trivial). I want to modify this program, so that the `evaluate input` returns not a String, but a type X that includes information on whether to "continue" and show a prompt after rendering the result, or exit altogether. So the specific questions I have here are: 1. What would be a sensible type signature for X? 2. Assuming X to exist, what is the right way to modify main to use it? My current intuition is to modify the outputStrLn ... loop statements to include an if-then-else, but I'm not sure what the right modification is (all my attempts seemed like imperative programming and failed compilation unsurprisingly). import Evaluator import System.Console.Haskeline main :: IO () main = runInputT defaultSettings loop where loop :: InputT IO () loop = do line <- getInputLine ">> " case line of Nothing -> return () Just "quit" -> return () Just input -> do outputStrLn $ "Executing: " ++ (evaluate input) loop module Evaluator where evaluate :: String -> String evaluate value = value

On Sun, Jul 31, 2016 at 06:44:14PM +0000, Ramnath R Iyer wrote:
The program below is what I have working right now (very trivial). I want to modify this program, so that the `evaluate input` returns not a String, but a type X that includes information on whether to "continue" and show a prompt after rendering the result, or exit altogether. So the specific questions I have here are:
1. What would be a sensible type signature for X?
Hello Ramnath, as now evaluate *has to* return a String because you pass its output as an argument to outputStrLn (which has a ~ `String -> InputT IO ()` signature itself). A quick hack is for `evaluate` to return evaluate :: String -> (String, Bool) where the Bool stands for 'should I exit or not' (using a datatype and/or a type synonym would be better and more clear). You can then write let (s, b) = evaluate input outputStrLn $ "Something " ++ s if b then loop else exit Your code has a very distinct imperative flavour (there are ways to get rid of that case/if cascade), but my opinion is: first make it work, then make it pretty. Does that help? -F

Hi Francesco,
Thank you for your response, it definitely helped. Below is an updated
version of working code. Where I was getting tripped up earlier was in the
commented portion below. Also, if you scroll down further, I have a few
further questions. Thank you for your time.
module Main where
import Evaluator
import System.Console.Haskeline
main :: IO ()
main = runInputT defaultSettings loop
where
loop :: InputT IO ()
loop = do
line <- getInputLine ">> "
case line of
Nothing -> return ()
Just input -> do
let (result, next) = evaluate input
if (next == Return)
then return ()
else (emit result >> loop) -- I had wanted the result to be
emitted only on Continue, not Return. This works, but is it a good way?
emit :: Maybe String -> InputT IO ()
emit Nothing = return ()
emit (Just value) = outputStrLn $ "Executing: " ++ value
module Evaluator where
data Next = Continue | Return
deriving (Eq, Ord)
evaluate :: String -> (Maybe String, Next) -- Now updated to make the
first part of the tuple a Maybe String instead of String
evaluate "quit" = (Nothing, Return)
evaluate value = (Just value, Continue)
** QUESTIONS **
1. If I wanted to write the logic encapsulated in `emit' directly within
main, how would I do that? In my example, I was forced to extract it out as
a separate method specifically to leverage pattern matching.
2. You mentioned outputStrLn has a type `String -> InputT IO ()'. How do
you logically come to this conclusion? Is it because outputStrLn was taking
a single String argument and had to return the same type returned by loop
declared previously?
3. Are there better/simpler/more idiomatic ways of structuring my program?
On Sun, Jul 31, 2016 at 12:01 PM Francesco Ariis
On Sun, Jul 31, 2016 at 06:44:14PM +0000, Ramnath R Iyer wrote:
The program below is what I have working right now (very trivial). I want to modify this program, so that the `evaluate input` returns not a String, but a type X that includes information on whether to "continue" and show a prompt after rendering the result, or exit altogether. So the specific questions I have here are:
1. What would be a sensible type signature for X?
Hello Ramnath,
as now evaluate *has to* return a String because you pass its output as an argument to outputStrLn (which has a ~ `String -> InputT IO ()` signature itself).
A quick hack is for `evaluate` to return
evaluate :: String -> (String, Bool)
where the Bool stands for 'should I exit or not' (using a datatype and/or a type synonym would be better and more clear). You can then write
let (s, b) = evaluate input outputStrLn $ "Something " ++ s if b then loop else exit
Your code has a very distinct imperative flavour (there are ways to get rid of that case/if cascade), but my opinion is: first make it work, then make it pretty.
Does that help? -F _______________________________________________ Beginners mailing list Beginners@haskell.org http://mail.haskell.org/cgi-bin/mailman/listinfo/beginners

On Sun, Jul 31, 2016 at 09:17:09PM +0000, Ramnath R Iyer wrote:
Below is an updated version of working code. [...]
Well done! Now, to the questions:
1. If I wanted to write the logic encapsulated in `emit' directly within main, how would I do that? In my example, I was forced to extract it out as a separate method specifically to leverage pattern matching.
Pattern matching can be done via a `case` statement as well (and you provide an example of this just a few lines above the `emit` call). Personally, I much a prefer separate function as it is clearer (if you don't want to clutter top level use a `where` statement).
2. You mentioned outputStrLn has a type `String -> InputT IO ()'. How do you logically come to this conclusion? Is it because outputStrLn was taking a single String argument and had to return the same type returned by loop declared previously?
Correct, if we ask ghci about `ouputStrLn` it will reply: λ> :t outputStrLn outputStrLn :: Control.Monad.IO.Class.MonadIO m => String -> InputT m () but in this case you have written the signature to `loop` (it's always a good habit), so it's clear our function can only have this concrete data type.
3. Are there better/simpler/more idiomatic ways of structuring my program?
Yes there are: your program checks/pattern matches at every step and for each of those you have a case/if; it could get pretty messy if you were to add a few more actions. There is a nice way to handle these kind of situations, it involves monadic code. But before using monads you need to digest them! So keep following your course (if you are not following any, I like these two, which are gratis [1] [2]) and come back to this .hs after you tamed the mighty monad to refactor it! [1] http://learnyouahaskell.com/ [2] https://www.seas.upenn.edu/~cis194/spring13/lectures.html
participants (3)
-
Francesco Ariis
-
Ramnath R Iyer
-
Ramnath R Iyer