Parse binary tree from file in Haskell - haskell

I have task to write Quiz Animal game. I have to read Tree data from file (the structure of file is free). After end of game is possible to be added new data in tree(actually (Animal) to be replace by (Node (Animal) (Animal)).
My problem is that i can't parse content of "database.txt" in AnimalsTree
Example "database.txt" (this content is generated with writing before call 'New Game'):
Question "Is it fly?" (Animal "Bird") (Question "Is it swim?" (Animal "Fish") (Animal "Dog"))
EDIT
This is full code:
module Main where
import System.IO
data AnimalsTree = Animal String | Question String AnimalsTree AnimalsTree deriving (Read, Show)
-- Видовете отговори на потребителя
data Answer = Yes | No
main :: IO ()
main = do root <- "database.txt"
play (read root)
return ()
play :: AnimalsTree -> IO AnimalsTree
play root = do putStrLn "Think of an animal, I will try to guess what it is..."
newRoot <- play' root
writeFile "database.txt" (show newRoot)
playAgain <- ask "Do you want to play again?"
case playAgain of
Yes -> play newRoot
No -> do putStrLn "Bye!"
return newRoot
play' :: AnimalsTree -> IO AnimalsTree
play' question#(Question q l r) = do ans <- ask q
case ans of
Yes -> do y <- play' l
return $ Question q y r
No -> do n <- play' r
return $ Question q l n
play' animal#(Animal _) = do ans <- ask $ "Are you thinking of " ++ show' animal ++ "?"
case ans of
Yes -> do putStrLn "I win! :)"
return animal
No -> do putStrLn "I give up, you win!"
getNewAnimal animal
getNewAnimal :: AnimalsTree -> IO AnimalsTree
getNewAnimal animal = do putStrLn "Please help me!"
putStrLn "What is name of yout animal?"
name <- getLine
let newAnimal = Animal name
putStrLn $ "Now please enter a question that answers yes for " ++ show' newAnimal ++ " and no for " ++ show' animal
question <- getLine
return $ Question question newAnimal animal
ask :: String -> IO Answer
ask s = do putStrLn $ s ++ " (Yes/No)"
getAnswer
getAnswer :: IO Answer
getAnswer = do ans <- getLine
putStrLn ""
case ans of
"y" -> return Yes
"Y" -> return Yes
"yes" -> return Yes
"Yes" -> return Yes
"n" -> return No
"N" -> return No
"no" -> return No
"No" -> return No
_ -> putStrLn "This is incorect answer! Please try again with value in 'Yes' or 'No'!" >> getAnswer
show' (Animal name) = (if elem (head name) "AEIOUaeiou" then "an " else "a ") ++ name
show' (Question q _ _) = q
But I get following error:
test3.hs:10:19:
No instance for (Read (IO AnimalsTree))
arising from a use of ‘read’
In a stmt of a 'do' block: root <- read "database.txt"
In the expression:
do { root <- read "database.txt";
play (root);
return () }
In an equation for ‘main’:
main
= do { root <- read "database.txt";
play (root);
return () }

This looks like a great start! I only needed to add readFile to your main function to get it to compile:
main = do root <- readFile "database.txt"
It is possible that you may need to switch from readFile to explicitly opening the file for reading, doing the reading, and closing the file. This is because readFile does not guarantee when it will close the file, and writeFile is allowed to fail if it is given a path to a file that's already open.
You can read the documentation for openFile, hGetLine, and hClose for further details on how to do this (but beware hGetContents, as it has the same caveats readFile does).

Related

'getLine' not working as intended, being skipped

I am fairly new to Haskell and am writing some simple text/file manipulation functions. I am currently attempting to modify a string before adding it to a file.
I have a function 'insertChar' which adds a character at any given position in a string (using the solution of problem 21 from 99 problems in Haskell https://wiki.haskell.org/99_questions/21_to_28).
import System.Environment
import System.Directory
import System.IO
import Data.List
main :: IO ()
main = do
putStrLn "Insert a string"
word <- getLine
putStrLn "Insert a char"
char <- getChar
putStrLn "Insert a position"
pos <- getLine *line which is skipped*
let x = (read pos :: Int) *converts string into int*
putStrLn "Adding char to list..."
let newS = [(insertChar char word x)] *result of insertChar is set to
newS*
putStrLn "Printed list: "
print (newS) *print new string*
putStrLn "Insert file name"
file <- getLine
putStrLn "Adding new string to file..."
add file newS
insertChar :: a -> [a] -> Int -> [a]
insertChar x ys 1 = x:ys
insertChar x (y:ys) n = y:insertChar x ys (n-1)
add :: String -> [String] -> IO ()
add fileName [item] = appendFile fileName item
The user is asked to enter a string, then a character they wish to add to this string and finally the position in the string where they wish to add the character. I can input the string fine but when I press enter after inputting the character, the 'getLine' for inputting the position is skipped and the following error is produced;
GHCI>main
Insert a string
hello world
Insert a char
s
Insert a position
Adding char to list...
Printed list:
["*** Exception: Prelude.read: no parse
I have seen this stack overflow post; haskell -skipping getLine
and have attempted to follow that answer changing the code to;
import System.Environment
import System.Directory
import System.IO (hSetBuffering, stdin, BufferMode(NoBuffering)) *New line*
import Data.List
main :: IO ()
main = do
hSetBuffering stdin NoBuffering *New line*
putStrLn "Insert a string"
word <- getLine
putStrLn "Insert a char"
char <- getChar
putStrLn "Insert a position"
pos <- getLine
let x = (read pos :: Int)
putStrLn "Adding char to list..."
let newS = [(insertChar char word x)]
putStrLn "Printed list: "
print (newS)
putStrLn "Insert file name"
file <- getLine
putStrLn "Adding new string to file..."
add file newS
insertChar :: a -> [a] -> Int -> [a]
insertChar x ys 1 = x:ys
insertChar x (y:ys) n = y:insertChar x ys (n-1)
add :: String -> [String] -> IO ()
add fileName [item] = appendFile fileName item
However, it still produces the same error. Any clue what I am doing wrong?
Thanks to Willem Van Onsem's comment on my original question I have been able to find a solution. I added a "getLine" after the line 'putStrLn "Insert a position"' so the code now looks like;
import System.Environment
import System.Directory
import System.IO
import Data.List
main :: IO ()
main = do
putStrLn "Insert a string"
word <- getLine
putStrLn "Insert a char"
char <- getChar
putStrLn "Insert a position"
temp <- getLine *line that has been added*
pos <- getLine
let x = (read pos :: Int)
putStrLn "Adding char to list..."
let newS = [(insertChar char word x)]
putStrLn "Printed list: "
print (newS)
putStrLn "Insert file name"
file <- getLine
putStrLn "Adding new string to file..."
add file newS
insertChar :: a -> [a] -> Int -> [a]
insertChar x ys 1 = x:ys
insertChar x (y:ys) n = y:insertChar x ys (n-1)
add :: String -> [String] -> IO ()
add fileName [item] = appendFile fileName item
You imported the right stuff, but never actually called it! Try this:
main = do
hSetBuffering stdin NoBuffering
-- ...all the rest of your original main, exactly as it used to be
This way, when it gets to the getChar line, it will return from the getChar as soon as you press a key -- not wait until you press enter. The UI will make more sense, and the code will, too, because you don't need to swallow a phantom newline that the user didn't actually want to enter anyway.

Let block gives indentation error

I know what an indentation error is, but I have no idea why I'm getting this error here, while every is aligned, trying to solve it for 2 hours.
Account.hs:40:25: error:
parse error (possibly incorrect indentation or mismatched brackets)
|
40 | let amount = readLn :: IO Int
| ^
Failed, 0 modules loaded.
main = do
putStrLn $ "Press one to create a new account"
let g = getLine
enteredValue = read g :: Int
if g == 1
then do putStrLn $ "Enter your name "
let name = getLine
putStrLn $ "Enter the initial amount"
let amount = readLn :: IO Int
value = Account (name,1,amount) Saving
show value
else do putStrLn $ "Nothing"
I also tried this version but this also gives incorrect indentation or mismatched brackets:
main = do
putStrLn $ "Press one to create a new account"
let g = getLine
enteredValue = read g :: Int
if g == 1
then do putStrLn $ "Enter your name "
let name = getLine
putStrLn $ "Enter the initial amount"
amount = readLn :: IO Int
value = Account (name,1,amount) Saving
show value
else do putStrLn $ "Nothing"
The problem is here:
-- |<---- "column 0" of this 'do' block
then do putStrLn $ "Enter your name "
-- | still good; a 'let' statement:
let name = getLine
-- |<---- "column 0" of this 'let' block
putStrLn $ "Enter the initial amount"
-- | Huh, there's no '=' in ^this^ declaration?
let amount = readLn :: IO Int
-- ^^^ Why is there a 'let' within another let binding?
-- I still haven't seen a '='. Better throw a parse error.
Basically, putStrLn $ "Enter the initial amount" is aligned with name = ... in the preceding line, so the compiler reads it as a declaration (part of the same let block).
To fix your indentation errors, it should be:
main = do
putStrLn $ "Press one to create a new account"
let g = getLine
enteredValue = read g :: Int
if g == 1
then do putStrLn $ "Enter your name "
let name = getLine
putStrLn $ "Enter the initial amount"
let amount = readLn :: IO Int
value = Account (name,1,amount) Saving
show value
else do putStrLn $ "Nothing"
But then you'll run into type errors:
read g is wrong: read takes a String, but g :: IO String
g == 1 is wrong: 1 is an Int, but g :: IO String
show value is wrong: show returns a String, but you're using it as an IO action
You haven't shown the declaration of Account, but you're likely going to have issues with name and amount, too
You probably want something like:
main = do
putStrLn $ "Press one to create a new account"
g <- getLine
let enteredValue = read g :: Int
if enteredValue == 1
then do putStrLn $ "Enter your name "
name <- getLine
putStrLn $ "Enter the initial amount"
amount <- readLn :: IO Int
let value = Account (name,1,amount) Saving
putStrLn (show value)
else do putStrLn $ "Nothing"
Basically, use v <- expr to go from expr :: IO Something to v :: Something.
Other notes:
g <- getLine; let enteredValue = read g :: Int better written as enteredValue <- readLn :: IO Int
putStrLn (show value) can be shortened to print value
you don't need do for a single expression (nor $ for a single operand): ... else putStrLn "Nothing"
There is more wrong to your code than just the Indentation Errors - so my first suggestion would be reading a bit of learn you a haskell for great good.
Next there are two assignment operators in haskell - one binds the result of an action … <- … and the other one is a local definition/declaration of a pure computation let … = ….
Moreover you can improve your reading a value by taking account of the possible false input, that someone could give you (intentionally and unintentionally) by replacing read with readMaybe, where the latter returns a Maybe something, for example readMaybe "1" = Just 1 :: Maybe Int or readMaybe "foo" = Nothing :: Maybe Int.
Regarding your indentation it is best that you compare one solution to your program with yours own:
import Text.Read (readMaybe)
data Type = Saving | Checking
deriving (Show)
data Account = Account (String,Int,Int) Type
deriving (Show)
main :: IO ()
main = do
putStrLn "Press one to create a new account"
g <- getLine
let enteredValue = readMaybe g :: Maybe Int
here the result of getLine and entered value have the same scope so they have the same indentation - we only change the scope after the next if where the then-block - and the else-block do not share the 'declarations' of each branch, so you couldn't use name in the else-block, but enteredValue can be used in both.
if enteredValue == Just 1
then do putStrLn "Enter your name "
name <- getLine
putStrLn "Enter the initial amount"
amount' <- fmap readMaybe getLine
here again name and amount' share the same scope, and pattern matching on amount' creates a new scope where amount is visible and the match on Nothing where you cannot use this variable.
case amount' of
Just amount -> print $ Account (name,1,amount) Saving
Nothing -> putStrLn "Nothing"
else putStrLn "Nothing"
let is for binding values, which is done in the form let x = y+z, where x is the name (aka "identifier") being bound, and y+z is the expression to which it is being bound.
In your example, I see three bindings: name, amount, and value. The rest are not value bindings, but actions.
In the do notation, actions do not need a let. You just write them one after another. So:
let name = getLine
putStrLn $ "Enter the initial amount"
let amount = readLn :: IO Int
let value = Account (name,1,amount) Saving
show value
But wait! This is not all!
getLine is not actually an expression of type String, as you seem to be hoping here. Rather, getLine is an action. In order to get it to "run" and "produce" a String value, you need to use the <- construct instead of let:
name <- getLine
Similarly with readLn:
amount <- readLn :: IO Int
Finally, show value is not actually an action that would print the value to the screen. show is a function that takes a value and return a String. It doesn't "do" anything (i.e. doesn't produce any outside effects), so you can't use it in place of an action in the do notation. If you wanted an action that would print a value to the screen, that would be print:
print value
Gathering everything together:
name <- getLine
putStrLn $ "Enter the initial amount"
amount <- readLn :: IO Int
let value = Account (name,1,amount) Saving
print value
And after fixing all of that, you'll have similar difficulties with the first part of your program, where you have let g = getLine instead of g <- getLine.

Making io program more modular [closed]

Closed. This question needs to be more focused. It is not currently accepting answers.
Want to improve this question? Update the question so it focuses on one problem only by editing this post.
Closed 6 years ago.
Improve this question
I am attempting to make a program that let's a user manipulate a database (a text file).
In the code I am posting, I show only 2 of the menu choices, namely "createdb" and "deletedb", and a few functions I made to desperately make the functions more compact. But my problem is that the pattern is similiar for all the other menu options. I ask the user to either enter the name of the database or "b" to return to the menu, and then check if the file exists.
Is there a way I can easily separate this to make my code more compact? I tried to do this part in the menu and have the choice functions be of type
FilePath -> IO ()
But then my menu looked really terrible. Here is a small part of the code:
type Choice = (String, String, IO ())
choices :: [Choice]
choices =
[("a", "create a database", createdb),
("b", "delete a database", deletedb),
("c", "insert an entry to a database", insert),
("d", "print a database", selectall),
("e", "select entries from a database", select),
-- more similiar choices
menu :: IO ()
menu = do
(mapM_ putStrLn . map showChoice) choices
c <- get "Enter the letter corresonding to the action of choice:"
case filter ((== c) . fst3) choices of
[] -> back "Not a valid choice. Try again"
(_, _, f) : _ -> f
createdb :: IO ()
createdb = do
n <- maybeName
if isNothing n then menu else do
let name = fromJust n
fp <- maybeFile name
if isJust fp
then back $ "Error: \"" ++ name ++ "\" already exist."
else do
cols <- get "Enter unique column names in the form n1,n2,...,n (No spaces):"
let spl = (splitOnComma . toLower') cols
case filter (== True) (hasDuplicates spl : map (elem ' ') spl) of
[] -> writeFile (name ++ ".txt") (cols ++ "\n")
_ -> back "Error: Column names must be unique and have no spaces."
deletedb :: IO ()
deletedb = do
n <- maybeName
if isNothing n then menu else do
let name = fromJust n
fp <- maybeFile name
if isJust fp
then removeFile (fromJust fp)
else back $ "Error: Could not find " ++ name
maybeName :: IO (Maybe String)
maybeName = do
input <- get "Enter database name or 'b' to go back to the menu."
return $ case input of
"b" -> Nothing
_ -> Just input
maybeFile :: String -> IO (Maybe FilePath)
maybeFile name = do
let fn = name ++ ".txt"
exists <- doesFileExist fn
return $ if exists then Just fn else Nothing
back :: String -> IO ()
back msg = do
putStrLn msg
menu
get :: String -> IO String
get msg = do
putStrLn msg
getLine
You're looking for the Exception monad transformer.
An example of how you might use it:
import Control.Monad.Except
data ExitType = ToMenu | Error String
deletedb :: ExceptT ExitType IO ()
deletedb = do
name <- getName
fp <- getFile name
liftIO $ removeFile fp
(or even the equivalent one-liner deletedb = liftIO . removeFile =<< getFile =<< getName !)
Then you can do better exit handling in getName etc:
getName :: ExceptT ExitType IO String
getName = do
input <- liftIO $ get "Enter database name or 'b' to go back to the menu."
case input of
"b" -> throwError ToMenu
_ -> return input
A small example of running it:
menu :: IO ()
menu = do
let action = deletedb -- display menu here to choose action
r <- runExcept action
case r of
Left ToMenu -> menu
Left (Error errmsg) -> putStrLn errmsg >> menu
Right result -> print result

'Either' propagation with IO()

I am learning Haskell, and having a great time. One of the things I especially enjoy is using the monad error types to propagate error conditions behind the scene in fmap or >>=. For example, in this code, I am using hoauth2 for an authenticated connection. It defines OAuth2Result using Either...
type OAuth2Result a = Either ByteString a -- from OAuth2
getEntries :: Manager -> AccessToken -> IO(OAuth2Result [Entry])
-- code omitted
filterResults :: [Entry] -> OAuth2Result [Entry]
filterResults = return $ filter hasUrl
printEntries :: [Entry] -> IO() -- What type can I use here?
printEntries Left l = -- code omitted
printEntries Right r = -- code omitted
main = do
entriesResult <- getEntries mgr token -- This is an OAuth2Result
let filtered = entriesResult >>= filterResults
printEntries filtered
The problem that I am having is when a function has IO like printEntries. In this case, I have to explicitly pattern match to do the error handling. I would sure love to be able to hide it somehow as I did with the filterResults call.
How can I do this?
Thanks!
Here's how to do it with runEitherT which requires some lifting and hoisting to get the types right:
import Control.Monad
import Control.Monad.Trans
import Control.Error
import Data.List (isInfixOf)
type Entry = String
type Result a = Either String a
sampleEntries = [ "good 1", "good 2", "good 3", "bad 4", "good 5", "bad 6", "good 7" ]
getEntries :: Int -> IO (Result [Entry])
getEntries n = if n >= 0 && n <= length sampleEntries
then return $ Right $ take n sampleEntries
else return $ Left $ "invalid n: " ++ show n
filterEntries :: [Entry] -> Result [Entry]
filterEntries ents = if all isGood ents
then Right $ ents
else Left "found a bad entry"
where isGood str = isInfixOf "good" str
printEntries :: [Entry] -> IO ()
printEntries ents = forM_ (zip [1..] ents) $ \(i,e) -> print (i,e)
doit n = do
ents <- (lift $ getEntries n) >>= hoistEither
filtered <- hoistEither $ filterEntries ents
lift $ printEntries filtered
main n = do result <- runEitherT $ doit n
case result of
Left e -> putStrLn $ "Error: " ++ e
Right _ -> putStrLn $ "no errors"
Note the following behavior:
main 100 fails because getEntries returns an error
main 4 fails because filterEntries returns an error
main 3 succeeds

Getting Haskeline to quit early

I am trying to use Haskeline to write a program which asks the user a sequence of questions, each one optionally with a default value in [brackets], and reads in their responses. I want the user to be able to
Press Enter to submit the [default] value;
Type in a string, edit it if needed, and then press Enter to submit this value;
Press Ctrl-C to reset all values to the defaults and start over; and,
Press Ctrl-D or enter "quit" to quit, in which case all the values which they submitted are lost.
I have been able to get points 1-3 working, but I cannot get point 4 to work: pressing Ctrl-D (or entering "quit") just brings up the next prompt instead of making the program quit the questioning. Looking at my program (please see below) I understand why this happens, but I am not able to figure out how to fix this so that Ctrl-D (or "quit") actually makes the questioning stop. How do I fix the program to make this happen?
I did see this question which seems to ask something similar, but I could not get much from there; I am not even sure that they are asking the same question as I am.
As a secondary question: my current program has quite a few case statements which switch on Maybe values. In particular, I currently check for Nothing two or three levels deep so that I can correctly return a Nothing when the user presses Ctrl-D. I have a feeling that this could be simplified using (something like) the monadic >>= operator, but I am unable to figure out how to do this in this case. Is my hunch right? Is there a way to do away with all this pattern matching which looks for Nothing?
Also: please tell me anything else which could improve my code below. I am quite new to this, so it is very likely that I am missing many obvious things here.
My program asks the user about the composition of a fruit basket. The information associated with a fruit basket consists of the name of the owner of the fruit basket and the names of the different kinds of fruit in the basket. To be able to ask for the latter, I first ask for the number of different kind of fruit in the basket, and then ask for the name of each kind. We start with a default fruit basket whose information is then modified as per what the user tells us.
module Main where
import System.Console.Haskeline
type PersonName = String
type FruitName = String
data FruitBasket = FruitBasket { ownerName :: PersonName,
fruitCount :: Int,
fruitNames :: [FruitName]
} deriving Show
defaultBasket = FruitBasket "Mary" 2 ["Apple", "Peach"]
main :: IO ()
main = do
basket <- getBasketData defaultBasket
putStrLn $ "Got: " ++ show(basket)
-- Prompt the user for information about a fruit basket, and
-- return a FruitBasket instance containing this information. The
-- first argument is an instance of FruitBasket from which we get
-- the default values for the various prompts. The return value
-- has a Maybe type because the user may abort the questioning, in
-- which case we get nothing from them.
getBasketData :: FruitBasket -> IO (Maybe FruitBasket)
getBasketData basket = runInputT defaultSettings $ withInterrupt $ getData basket
where
getData :: FruitBasket -> InputT IO (Maybe FruitBasket)
getData initialBasket = handleInterrupt f $ do
outputStrLn banner
input <- getInputLine $ "Who owns this basket? [" ++ defaultOwner ++ "] : "
basket <- case input of
Nothing -> return Nothing -- User pressed Ctrl-D with the input being empty
Just "" -> return (Just initialBasket) -- User pressed Enter with the input being empty
Just "quit" -> return Nothing -- User typed in "quit" and pressed Enter
Just newOwner -> return (Just initialBasket{ownerName = newOwner})
input <- getInputLine $ "Number of kinds of fruit in the basket? [" ++ show defaultCount ++ "] : "
basket' <- case input of
Nothing -> return Nothing
Just "" -> return basket
Just "quit" -> return Nothing
Just count -> return $ updateFruitCount basket (read count)
where updateFruitCount Nothing _ = Nothing
updateFruitCount (Just realBasket) newCount = Just $ realBasket{fruitCount = newCount}
let defaultFruitNames = pruneOrPadNames basket'
newNames <- getFruitNames defaultFruitNames 1
case newNames of
Nothing -> return (Just defaultBasket)
Just newSetOfNames -> return $ updateFruitNames basket' newSetOfNames
where updateFruitNames Nothing _ = Nothing
updateFruitNames (Just realBasket) realNewNames = Just $ realBasket{fruitNames = realNewNames}
where f = (outputStrLn "Press Ctrl-D or enter \"quit\" to quit." >> getData initialBasket)
defaultOwner = ownerName initialBasket
defaultCount = fruitCount initialBasket
banner :: String
banner = "Please enter details of the fruit basket below. At each prompt you can do one of the following:\n\
\\t (a) Press Enter to submit the [default] value;\n\
\\t (b) Type in a string, edit it if needed, and then press Enter to submit this value;\n\
\\t (c) Press Ctrl-C to reset all values to the defaults and start over;\n\
\\t (d) Press Ctrl-D or enter \"quit\" to quit; all the values you submitted will be lost."
pruneOrPadNames :: Maybe FruitBasket -> Maybe [String]
pruneOrPadNames Nothing = Nothing
pruneOrPadNames (Just basket) = Just $ pruneOrPad (fruitNames basket) (fruitCount basket)
-- When requiredLength is not larger than (length inputList),
-- (pruneOrPad inputList requiredLength) is the prefix of
-- inputList of length requiredLength. Otherwise, it is inputList
-- padded with as many empty strings as required to make the total
-- length equal to requiredLength.
pruneOrPad :: [String] -> Int -> [String]
pruneOrPad inputList requiredLength
| requiredLength <= inputLength = take requiredLength inputList
| otherwise = inputList ++ (replicate difference "")
where inputLength = length inputList
difference = requiredLength - inputLength
getFruitNames Nothing _ = return Nothing
getFruitNames (Just []) _ = return $ Just [""]
getFruitNames (Just (name:names)) count = do
input <- getInputLine $ "Name of fruit " ++ (show count) ++ " [" ++ name ++ "] : "
newNames <- case input of
Nothing -> return Nothing
Just "" -> do -- Keep the default name for this fruit ...
newNames' <- getFruitNames (Just names) (count + 1)
case newNames' of
Nothing -> return Nothing
-- ... unless the user chose to quit
-- while entering a name
Just [""] -> return $ Just [name]
-- At this point names = [] so it is
-- already time to stop asking for
-- more names.
Just furtherNames -> return $ Just (name : furtherNames)
Just "quit" -> return Nothing
Just name' -> do
newNames' <- getFruitNames (Just names) (count + 1)
case newNames' of
Nothing -> return Nothing
Just [""] -> return $ Just [name']
Just furtherNames -> return $ Just (name' : furtherNames)
return newNames
With help from some of the advice here on the haskell-beginners mailing list I have managed to solve my problems, the Ctrl-D question entirely and the factoring question to my own satisfaction (as of now!). I am posting the answer here in the hope it helps others in my predicament.
First, the trouble with the Ctrl-D: The problem was that I was throwing away the control logic offered by the Maybe monad and just using the values from the monad, by referring to various variable names which contained these values. The first place where I do this is here, in the getBasketData function:
basket <- case input of ...
input <- getInputLine ...
basket' <- case input of
Nothing -> return Nothing
Just "" -> return basket
Notice how, in computing basket', I
Ignore the case where basket could have been Nothing, and
Use the value encapsulated by basket by referring to (and pattern matching on, when needed) the variable basket which is still in scope inside the expression for basket'.
This is the where the Ctrl-D was lost. Here, for contrast, is code for getBasketData which does not let the Nothings slip through the gaps (I renamed the basket variables to maybeBasket, because they are really instances of Maybe FruitBasket):
getBasketData basket = runInputT defaultSettings $ withInterrupt $ getData basket
where
getData :: FruitBasket -> InputT IO (Maybe FruitBasket)
getData initialBasket = handleInterrupt f $ do
outputStrLn banner
input <- getInputLine $ "Who owns this basket? [" ++ defaultOwner ++ "] : "
maybeBasket <- case input of
Nothing -> return $ Nothing -- User pressed Ctrl-D with the input being empty
Just "" -> return $ Just initialBasket -- User pressed Enter with the input being empty
Just "quit" -> return $ Nothing -- User typed in "quit" and pressed Enter
Just newOwner -> return $ Just initialBasket{ownerName = newOwner}
maybeBasket' <- case maybeBasket of
Nothing -> return $ Nothing
Just realBasket -> do input <- getInputLine $ "Number of kinds of fruit in the basket? [" ++ show defaultCount ++ "] : "
case input of
Nothing -> return $ Nothing
Just "" -> return $ maybeBasket
Just "quit" -> return $ Nothing
Just count -> return $ Just $ realBasket{fruitCount = (read count)}
maybeBasket'' <- case maybeBasket' of
Nothing -> return $ Nothing
Just realBasket -> do let defaultFruitNames = pruneOrPad (fruitNames realBasket) (fruitCount realBasket)
newNames <- getFruitNames defaultFruitNames 1
case newNames of
Nothing -> return $ Nothing
Just newSetOfNames -> return $ Just $ realBasket{fruitNames = newSetOfNames}
return maybeBasket''
where f = (outputStrLn interruptMessage >> getData initialBasket)
defaultOwner = ownerName initialBasket
defaultCount = fruitCount initialBasket
Thus, for instance, we try to do any real computation to get maybeBasket' --- including presenting the prompt for the number of different kinds of fruit --- only if maybeBasket is not Nothing.
This solves the Ctrl-D problem: the program now stops questioning and returns Nothing if the user presses Ctrl-D in response to any question.
Now onto the factoring. This is where advice from the mailing list answer helped: I started out by splitting up the big getData function into three pieces, one for each "big" use of the <- operator, and put these pieces into separate functions. This cleared up the logic a lot for me (indeed, this is how I found the fix to the Ctrl-D problem as well). Starting with this, I kept rephrasing the various parts till I got the following version which looks good enough to me. Notice how small and clean the getBasketData function has become!
module Main where
import System.Console.Haskeline
type PersonName = String
type FruitName = String
data FruitBasket = FruitBasket { ownerName :: PersonName,
fruitCount :: Int,
fruitNames :: [FruitName]
} deriving Show
defaultBasket :: FruitBasket
defaultBasket = FruitBasket "Mary" 2 ["Apple", "Peach"]
main :: IO ()
main = do
basket <- getBasketData defaultBasket
putStrLn $ "Got: " ++ show(basket)
-- Prompt the user for information about a fruit basket, and
-- return a FruitBasket instance containing this information. The
-- first argument is an instance of FruitBasket from which we get
-- the default values for the various prompts. The return value
-- has a Maybe type because the user may abort the questioning, in
-- which case we get nothing from them.
getBasketData :: FruitBasket -> IO (Maybe FruitBasket)
getBasketData basket = runInputT defaultSettings $ withInterrupt $ getData basket
where
getData :: FruitBasket -> InputT IO (Maybe FruitBasket)
getData initialBasket = handleInterrupt f $ do
outputStrLn banner
(ownerQ initialBasket) >>= (processOwner initialBasket) >>= processCount >>= processNames
where f = (outputStrLn interruptMessage >> getData initialBasket)
ownerQ :: FruitBasket -> InputT IO (Maybe PersonName)
ownerQ basket = getInputLine $ "Who owns this basket? [" ++ (ownerName basket) ++ "] : "
processOwner :: FruitBasket -> Maybe PersonName -> InputT IO (Maybe FruitBasket)
processOwner _ Nothing = return Nothing
processOwner _ (Just "quit") = return Nothing
processOwner basket (Just "") = return $ Just basket
processOwner basket (Just newOwner) = return $ Just basket{ownerName = newOwner}
processCount :: Maybe FruitBasket -> InputT IO (Maybe FruitBasket)
processCount Nothing = return Nothing
processCount (Just basket) = (fruitTypesQ basket) >>= processCount'
where processCount' :: Maybe String -> InputT IO (Maybe FruitBasket)
processCount' Nothing = return Nothing
processCount' (Just "quit") = return Nothing
processCount' (Just "") = return $ Just basket
processCount' (Just count) = return $ Just basket{fruitCount = (read count)}
fruitTypesQ :: FruitBasket -> InputT IO (Maybe String)
fruitTypesQ basket = getInputLine $ "Number of kinds of fruit in the basket? [" ++ show (fruitCount basket) ++ "] : "
processNames :: Maybe FruitBasket -> InputT IO (Maybe FruitBasket)
processNames Nothing = return Nothing
processNames (Just basket) = input >>= processNames'
where input = getFruitNames defaultFruitNames 1
defaultFruitNames = pruneOrPad (fruitNames basket) (fruitCount basket)
processNames' :: Maybe [FruitName] -> InputT IO (Maybe FruitBasket)
processNames' Nothing = return Nothing
processNames' (Just newSetOfNames) = return $ Just basket{fruitNames = newSetOfNames}
banner :: String
banner = "Please enter details of the fruit basket below. At each prompt you can do one of the following:\n\
\\t (a) Press Enter to submit the [default] value;\n\
\\t (b) Type in a string, edit it if needed, and then press Enter to submit this value;\n\
\\t (c) Press Ctrl-C to reset all values to the defaults and start over;\n\
\\t (d) Press Ctrl-D or enter \"quit\" to quit; all the values you submitted will be lost."
interruptMessage :: String
interruptMessage = "#################################################\n\
\You pressed Ctrl-C.\n\
\We will now reset all values and start over.\n\
\To quit, press Ctrl-D or enter \"quit\".\n\
\#################################################\n"
pruneOrPadNames :: Maybe FruitBasket -> Maybe [String]
pruneOrPadNames Nothing = Nothing
pruneOrPadNames (Just basket) = Just $ pruneOrPad (fruitNames basket) (fruitCount basket)
-- When requiredLength is not larger than (length inputList),
-- (pruneOrPad inputList requiredLength) is the prefix of
-- inputList of length requiredLength. Otherwise, it is inputList
-- padded with as many empty strings as required to make the total
-- length equal to requiredLength.
pruneOrPad :: [String] -> Int -> [String]
pruneOrPad inputList requiredLength
| requiredLength <= inputLength = take requiredLength inputList
| otherwise = inputList ++ (replicate difference "")
where inputLength = length inputList
difference = requiredLength - inputLength
getFruitNames :: [FruitName] -> Int -> InputT IO (Maybe [FruitName])
getFruitNames [] _ = return $ Just [""]
getFruitNames (name:names) count = do
input <- getInputLine $ "Name of fruit " ++ (show count) ++ " [" ++ name ++ "] : "
newNames <- case input of
Nothing -> return Nothing
Just "" -> do -- Keep the default name for this fruit ...
newNames' <- getFruitNames names (count + 1)
case newNames' of
Nothing -> return Nothing
-- ... unless the user chose to quit
-- while entering a name
Just [""] -> return $ Just [name]
-- At this point names = [] so it is
-- already time to stop asking for
-- more names.
Just furtherNames -> return $ Just (name : furtherNames)
Just "quit" -> return Nothing
Just name' -> do
newNames' <- getFruitNames names (count + 1)
case newNames' of
Nothing -> return Nothing
Just [""] -> return $ Just [name']
Just furtherNames -> return $ Just (name' : furtherNames)
return newNames
The moral of this story seems to be: "When confused, break things down."
I think your hunch is right here. Much of the pattern matching done via case can be replaced with using the Maybe Monad a bit more.
Instead of
basket <- case input of
Nothing -> return Nothing -- User pressed Ctrl-D with the input being empty
Just "" -> return (Just initialBasket) -- User pressed Enter with the input being empty
Just "quit" -> return Nothing -- User typed in "quit" and pressed Enter
Just newOwner -> return (Just initialBasket{ownerName = newOwner})
you could write something like
let basket' = do
i <- input
guard $ i /= "quit"
b <- basket
return $ if (null i) then b else b{fruitCount = read i}
you could even introduce some helpers like
guardInput :: Maybe String -> (String -> Maybe a) -> Maybe a
guardInput input λ = input >>= \i -> ((guard $ i /= "quit") >> λ i)
-- | Custom ternary operator .)
True ? (a, _) = a
False ? (_, b) = b
to write
let basket = guardInput input $
\i -> return $ (null i) ? (initialBasket, initialBasket{ownerName = i})
Sorry - I know this doesn't answer your problem with Ctrl+D, but I haven't figured that one out myself (yet).

Resources