Correct way of reading from stdin in haskell - haskell

I have a program that depending on the arguments given works in different ways:
If there are 2 arguments - it takes 2nd argument as a filename, reads from it and then simply prints it out.
If there is 1 argument - it reads from stdin and also prints it out.
Here is the code:
main :: IO ()
main = do
-- Read given arguments
args <- getArgs
-- If file containing gramma was given
if length args == 2 then do
hfile <- openFile (last args) ReadMode
content <- hGetContents hfile
let inGramma = getGramma content
doJob (head args) inGramma
hClose hfile
return ()
-- If no file was given - reads from stdin
else if length args == 1 then do
content <- getContents
let inGramma = getGramma content
doJob (head args) inGramma
return ()
else do putStrLn "Invalid count of arguments!"
The problem is, when it reads from stdin, after every new line (enter pressed), it prints that line and than reads next. I need it to wait for the whole input and than print it out (after Ctrl+D).
Here are the functions used in that code:
-- | Structure of gramma
data GrammaStruct = Gramma
{ nonTerminals :: NonTerminals
, terminals :: Terminals
, start :: Start
, rules :: Rules
} deriving (Eq)
-- | Representation of gramma
instance Show GrammaStruct where
show (Gramma n t s r) =
init (showSplit n) ++
"\n" ++ init (showSplit t) ++
"\n" ++ showStart s ++
"\n" ++ init (showRules r)
-- | Print gramma
showGramma :: GrammaStruct -> IO ()
showGramma gr = do
putStrLn $ show gr
-- | Transforms string given from file of stdin into gramma representation in app
getGramma :: String -> GrammaStruct
getGramma hIn = procLns (lines hIn)
-- | Depending on option given, provides required functionality
doJob :: String -> GrammaStruct -> IO ()
doJob op gramma
| op == "-i" = showGramma gramma
Thank you.

The problem here is that getContents uses lazy IO, making the input stream to be processed line-by-line. If you want to force it to read the whole input before starting performing the job you can use the following hack:
...
if length args == 1 then do
content <- getContents
length content `seq` return () -- force the input to be fully read now
let inGramma = getGramma content
doJob (head args) inGramma
return ()
Alternatively, use evaluate, or look in Hackage for a strict IO module providing a strict getContents. For instance, I just found the strict-io package providing System.IO.Strict.getContents. Using that you should be able to write (untested)
import qualified System.IO.Strict as S
...
if length args == 1 then do
content <- run S.getContents
...

That's not answering the question but instead of testing the length of the arguments, you can pattern match against it and return the correct content
main = do
let (opt, contentM) = case getArgs of
[opt] -> (op, getContent)
[opt, file] -> (op, hGetContent file)
_ -> error ("Invalid count of argument")
inGramma <- fmap getGramma contentM
doJob opt inGramma

Related

Why does this function not fail immediately?

I have the following piece of code. main gets the stdin text and sequences it through g, after which f prints it's output and returns an appropriate ExitCode which is commited using exitWith.
My question is why does this program, when run with the sample input, not terminate immediately after the first line (test) is entered, but only fails after it reads the second line (test2)? What I want to happen is for the g function to return immediately after parse1 returns Left "left: test" and not wait until the second line is entered.
Code:
import System.Exit
import Control.Monad
import Data.Either
type ErrType = String
parse1 :: String -> Either ErrType Int
parse1 "test" = Left "left: test"
parse1 _ = Left "left"
parse2 :: String -> Either ErrType Char
parse2 s = Right (head s)
g :: String -> Either String String
g str =
let l1:l2:ls = lines str
in either (Left . show) (Right . show) $ do
a <- parse1 l1
b <- parse2 l2
return "placeholder"
main = getContents >>= f.g >>= exitWith
where f (Right s) = putStrLn s >> return ExitSuccess
f (Left s) = putStrLn s >> return (ExitFailure 1)
Standard input stream:
test
test2
The line
let l1:l2:ls = lines str
means that to evaluate even just l1, the whole pattern l1:l2:ls needs to match, which means that a check needs to be done that str actually contains at least two lines. With lazy input, that causes the behavior you see.
You can fix it with an explicitly lazy pattern that defers the check for the second line:
let l1 : ~(l2:ls) = lines str
or, since a top pattern in a let is implicitly lazy, you could split it up like:
let l1:ls' = lines str
l2:ls = ls'

Technique for reading in multiple lines for Haskell IO

Basically I would like to find a way so that a user can enter the number of test cases and then input their test cases. The program can then run those test cases and print out the results in the order that the test cases appear.
So basically I have main which reads in the number of test cases and inputs it into a function that will read from IO that many times. It looks like this:
main = getLine >>= \tst -> w (read :: String -> Int) tst [[]]
This is the method signature of w: w :: Int -> [[Int]]-> IO ()
So my plan is to read in the number of test cases and have w run a function which takes in each test case and store the result into the [[]] variable. So each list in the list will be an output. w will just run recursively until it reaches 0 and print out each list on a separate line. I'd like to know if there is a better way of doing this since I have to pass in an empty list into w, which seems extraneous.
As #bheklilr mentioned you can't update a value like [[]]. The standard functional approach is to pass an accumulator through a a set of recursive calls. In the following example the acc parameter to the loop function is this accumulator - it consists of all of the output collected so far. At the end of the loop we return it.
myTest :: Int -> [String]
myTest n = [ "output line " ++ show k ++ " for n = " ++ show n | k <- [1..n] ]
main = do
putStr "Enter number of test cases: "
ntests <- fmap read getLine :: IO Int
let loop k acc | k > ntests = return $ reverse acc
loop k acc = do
-- we're on the kth-iteration
putStr $ "Enter parameter for test case " ++ show k ++ ": "
a <- fmap read getLine :: IO Int
let output = myTest a -- run the test
loop (k+1) (output:acc)
allOutput <- loop 1 []
print allOutput
As you get more comfortable with this kind of pattern you'll recognize it as a fold (indeed a monadic fold since we're doing IO) and you can implement it with foldM.
Update: To help explain how fmap works, here are equivalent expressions written without using fmap:
With fmap: Without fmap:
n <- fmap read getLine :: IO [Int] line <- getLine
let n = read line :: Int
vals <- fmap (map read . words) getLine line <- getLine
:: IO [Int] let vals = (map read . words) line :: [Int]
Using fmap allows us to eliminate the intermediate variable line which we never reference again anyway. We still need to provide a type signature so read knows what to do.
The idiomatic way is to use replicateM:
runAllTests :: [[Int]] -> IO ()
runAllTests = {- ... -}
main = do
numTests <- readLn
tests <- replicateM numTests readLn
runAllTests tests
-- or:
-- main = readLn >>= flip replicateM readLn >>= runAllTests

Haskell : parsing command line arguments

I want to write a program in Haskell which will take command line arguments. For example: to print the sum of the first 6 elements of the series (which will be calculated by another function), I will write:
sum 6
and the correct answer should be displayed. I have to do this for another 5-7 different commands by checking the command line. How should I do it? Is switch case a good idea? If so, can anyone tell me how it can be done.
SOLUTION:
main = do
--Get some input
f <- getLine
--Split the input into 2 strings; one is COMMAND field and other is the ARGUMENT field using the condition the there is one space between them
let cmd = takeWhile (/=' ') f
let arg = dropWhile (/=' ') f
let val = tail arg
let p = read val::Int
--Check for the COMMAND
case cmd of
"SUM" -> if (empty arg) then do { putStrLn "ERR"; exitWith ExitSuccess} else if (check val) then print (sum1 p) else do { putStrLn "ERR"; exitWith ExitSuccess}
"NTH" -> if (empty arg) then do { putStrLn "ERR"; exitWith ExitSuccess} else if (check val) then print (fact p) else do { putStrLn "ERR"; exitWith ExitSuccess}
"BOUNDS" -> if (empty arg) then do { putStrLn "ERR"; exitWith ExitSuccess} else if (check val == False) then do { putStrLn "ERR"; exitWith ExitSuccess} else if (p > 1) then do { print c; print d} else do { putStrLn"ERR"; exitWith ExitSuccess}
"QUIT" -> if (empty arg) then exitWith ExitSuccess else do { putStrLn "ERR"; exitWith ExitSuccess}
_ -> do { putStrLn "ERR"; exitWith ExitSuccess}
--Repeat main until QUIT
main
optparse-applicative is one example of a library which supports this kind of sub-command parsing.
Let's say your program has two commands for now, "sum" and "mean". We can represent the command and its arguments using an algebraic data type, here called Command.
import Data.Monoid (mconcat)
import Options.Applicative
data Command = Sum Integer
| Mean Integer
-- et cetera
We can build a parser which accepts all of the commands, by writing parsers for each individual command, and composing them.
parseNumber :: Parser Integer
parseNumber = argument auto (metavar "N")
sumParser :: ParserInfo Command
sumParser = info (Sum <$> parseNumber)
(progDesc "Sum first N elements in series")
meanParser :: ParserInfo Command
meanParser = info (Mean <$> parseNumber)
(progDesc "Mean of first N elements in series")
commandParser :: ParserInfo Command
commandParser = info commands $ progDesc "My program" where
commands = subparser $ mconcat [
command "sum" sumParser
, command "mean" meanParser
]
If you are wondering what Parser and ParserInfo are about: Usually we build a Parser, then put it into a ParserInfo, using the info combinator to decorate it with additional information about how it should be run (for example, with progDesc). Parsers may be composed with other Parsers, typically using the applicative combinators, but a ParserInfo is only a Functor, as it represents the entry point to the program.
Since each command is like a little sub-program, we need a ParserInfo for each one. The command and subparser combinators let us take some ParserInfos and wrap them up in a Parser, turning multiple entry points into one.
Once we have a result from the parser, we can dispatch to the appropriate routine by pattern matching on the result.
main :: IO ()
main = do
cmd <- execParser commandParser
case cmd of
Sum n -> return () -- TODO perform sum command
Mean n -> return () -- TODO perform mean command
Of course, if you have the time and the need, is much better to use a command line parser library than a switch case. A proper parser gives you the ability to have flags in any order, automatic documenation etc ... Although if you don't need any of this now, you might need it later.
However, pattern matching allows you check value(s) within a list, but although the size of the list, and this at the same time. This makes writing poor man command line parsing dead-easy in Haskell.
Example
main = do
args <- getArg
case args of
["command1", a, b] -> command1 a b -- 2 argument
["command2", a ] -> command2 a -- 1 argument
"command3":as -> command3 as -- n arguments
otherwise -> putStrLn "Please read the code to see which arguments are acceptable :-)"
So even though I would propably recommend using a parsing library, if you only need a couple of options without flags , and don't have time to learn/choose one, a simple case ... of is pretty neat and much quicker/simpler to write.
You can write your own simple applicative-style parser in just a few lines. The idea is: accept a list of string pairs, where the first string is an option name and the second string is an option value, lookup for a current option name, and if it's found, treat the associated value somehow and delete the pair from the list. If it's not found, return Nothing. So Parser is defined like this:
type Parser = StateT [(String, String)] Maybe
And here is the main function:
option :: (String -> Maybe a) -> String -> Parser a
option f str = StateT $ \xs -> do
(v, xs') <- lookupDelete str xs
v' <- f v
return (v', xs')
where lookupDelete does what it says. Actual option parsers are:
sopt :: String -> Parser String
sopt = option Just
opt :: Read a => String -> Parser a
opt = option $ reads >>> listToMaybe >=> finish
finish (x, []) = Just x
finish _ = Nothing
The opt parser tries to read a string, and it succeeds if the string is read fully.
optPairs [] = Just []
optPairs (('-':'-':name):opt:xs) = ((name, opt) :) <$> optPairs xs
optPairs _ = Nothing
This function splits input into pairs. And lastly
parse :: Parser a -> String -> Maybe a
parse p = words >>> optPairs >=> runStateT p >=> finish
Here is an example:
data SubCommand = SubCommand String (Double, Double)
deriving (Show)
data Command = Sum [Integer]
| Sub SubCommand
deriving (Show)
subcommandParser :: Parser SubCommand
subcommandParser = SubCommand <$> sopt "str" <*> opt "dbls"
commandParser :: Parser Command
commandParser = Sum <$> opt "sum" <|> Sub <$> subcommandParser
main = mapM_ (print . parse commandParser)
[ "--sum [1,2,3,4]"
, "--str option --dbls (2.2,0)"
, "--dbls (2.2,0) --str option"
, "--smth smth"
]
Results in
Just (Sum [1,2,3,4])
Just (Sub (SubCommand "option" (2.2,0.0)))
Just (Sub (SubCommand "option" (2.2,0.0)))
Nothing
The whole code: http://lpaste.net/114365

Why can't I compare result of lookup to Nothing in Haskell?

I have the following code:
import System.Environment
import System.Directory
import System.IO
import Data.List
dispatch :: [(String, [String] -> IO ())]
dispatch = [ ("add", add)
, ("view", view)
, ("remove", remove)
, ("bump", bump)
]
main = do
(command:args) <- getArgs
let result = lookup command dispatch
if result == Nothing then
errorExit
else do
let (Just action) = result
action args
errorExit :: IO ()
errorExit = do
putStrLn "Incorrect command"
add :: [String] -> IO ()
add [fileName, todoItem] = appendFile fileName (todoItem ++ "\n")
view :: [String] -> IO ()
view [fileName] = do
contents <- readFile fileName
let todoTasks = lines contents
numberedTasks = zipWith (\n line -> show n ++ " - " ++ line) [0..] todoTasks
putStr $ unlines numberedTasks
remove :: [String] -> IO ()
remove [fileName, numberString] = do
handle <- openFile fileName ReadMode
(tempName, tempHandle) <- openTempFile "." "temp"
contents <- hGetContents handle
let number = read numberString
todoTasks = lines contents
newTodoItems = delete (todoTasks !! number) todoTasks
hPutStr tempHandle $ unlines newTodoItems
hClose handle
hClose tempHandle
removeFile fileName
renameFile tempName fileName
bump :: [String] -> IO ()
bump [fileName, numberString] = do
handle <- openFile fileName ReadMode
(tempName, tempHandle) <- openTempFile "." "temp"
contents <- hGetContents handle
let number = read numberString
todoTasks = lines contents
bumpedItem = todoTasks !! number
newTodoItems = [bumpedItem] ++ delete bumpedItem todoTasks
hPutStr tempHandle $ unlines newTodoItems
hClose handle
hClose tempHandle
removeFile fileName
renameFile tempName fileName
Trying to compile it gives me the following error:
$ ghc --make todo
[1 of 1] Compiling Main ( todo.hs, todo.o )
todo.hs:16:15:
No instance for (Eq ([[Char]] -> IO ()))
arising from a use of `=='
Possible fix:
add an instance declaration for (Eq ([[Char]] -> IO ()))
In the expression: result == Nothing
In a stmt of a 'do' block:
if result == Nothing then
errorExit
else
do { let (Just action) = ...;
action args }
In the expression:
do { (command : args) <- getArgs;
let result = lookup command dispatch;
if result == Nothing then
errorExit
else
do { let ...;
.... } }
I don't get why is that since lookup returns Maybe a, which I'm surely can compare to Nothing.
The type of the (==) operator is Eq a => a -> a -> Bool. What this means is that you can only compare objects for equality if they're of a type which is an instance of Eq. And functions aren't comparable for equality: how would you write (==) :: (a -> b) -> (a -> b) -> Bool? There's no way to do it.1 And while clearly Nothing == Nothing and Just x /= Nothing, it's the case that Just x == Just y if and only if x == y; thus, there's no way to write (==) for Maybe a unless you can write (==) for a.
There best solution here is to use pattern matching. In general, I don't find myself using that many if statements in my Haskell code. You can instead write:
main = do (command:args) <- getArgs
case lookup command dispatch of
Just action -> action args
Nothing -> errorExit
This is better code for a couple of reasons. First, it's shorter, which is always nice. Second, while you simply can't use (==) here, suppose that dispatch instead held lists. The case statement remains just as efficient (constant time), but comparing Just x and Just y becomes very expensive. Second, you don't have to rebind result with let (Just action) = result; this makes the code shorter and doesn't introduce a potential pattern-match failure (which is bad, although you do know it can't fail here).
1:: In fact, it's impossible to write (==) while preserving referential transparency. In Haskell, f = (\x -> x + x) :: Integer -> Integer and g = (* 2) :: Integer -> Integer ought to be considered equal because f x = g x for all x :: Integer; however, proving that two functions are equal in this way is in general undecidable (since it requires enumerating an infinite number of inputs). And you can't just say that \x -> x + x only equals syntactically identical functions, because then you could distinguish f and g even though they do the same thing.
The Maybe a type has an Eq instance only if a has one - that's why you get No instance for (Eq ([[Char]] -> IO ())) (a function can't be compared to another function).
Maybe the maybe function is what you're looking for. I can't test this at the moment, but it should be something like this:
maybe errorExit (\action -> action args) result
That is, if result is Nothing, return errorExit, but if result is Just action, apply the lambda function on action.

How to do something with data from stdin, line by line, a maximum number of times and printing the number of line in Haskell

This code reads the number of lines to process from the first line of stdin, then it loops number_of_lines_to_process times doing some calculations and prints the result.
I want it to print the line number in "Line #" after "#" but I don't know how to obtain it
import IO
import Control.Monad (replicateM)
main :: IO ()
main = do
hSetBuffering stdin LineBuffering
s <- getLine
let number_of_lines_to_process = read s :: Integer
lines <- replicateM (fromIntegral(number_of_lines_to_process)) $ do
line <- getLine
let number = read line :: Integer
result = number*2 --example
putStrLn ("Line #"++": "++(show result)) --I want to print the number of the iteration and the result
return ()
I guess that the solution to this problem is really easy, but I'm not familiar with Haskell (coding in it for the first time) and I didn't find any way of doing this. Can anyone help?
You could use forM_ instead of replicateM:
import IO
import Control.Monad
main :: IO ()
main = do
hSetBuffering stdin LineBuffering
s <- getLine
let number_of_lines_to_process = read s :: Integer
forM_ [1..number_of_lines_to_process] (\i -> do
line <- getLine
let number = read line :: Integer
result = number * 2
putStrLn $ "Line #" ++ show i ++ ": " ++ show result)
Note that because you use forM_ (which discards the results of each iteration) you don't need the additional return () at the end - the do block returns the value of the last statement, which in this case is the () which is returned by forM_.
The trick is to first create a list of all the line numbers you want to print, and to then loop through that list, printing each number in turn. So, like this:
import Control.Monad
import System.IO
main :: IO ()
main = do
hSetBuffering stdin LineBuffering
s <- getLine
let lineCount = read s :: Int
-- Create a list of the line numbers
lineNumbers = [1..lineCount]
-- `forM_` is like a "for-loop"; it takes each element in a list and performs
-- an action function that takes the element as a parameter
forM_ lineNumbers $ \ lineNumber -> do
line <- getLine
let number = read line :: Integer
result = number*2 --example
putStrLn $ "Line #" ++ show lineNumber ++ ": " ++ show result
return ()
Read the definition of forM_.
By the way, I wouldn't recommend using the old Haskell98 IO library. Use System.IO instead.
You could calculate the results, enumerate them, and then print them:
import IO
import Control.Monad (replicateM)
-- I'm assuming you start counting from zero
enumerate xs = zip [0..] xs
main :: IO ()
main = do
hSetBuffering stdin LineBuffering
s <- getLine
let number_of_lines_to_process = read s :: Integer
lines <- replicateM (fromIntegral(number_of_lines_to_process)) $ do
line <- getLine
let number = read line :: Integer
result = number*2 --example
return result
mapM_ putStrLn [ "Line "++show i++": "++show l | (i,l) <- enumerate lines ]
I'm still new at Haskell, so there could be problems with the program below (it does work). This program is a tail recursive implementation. The doLine helper function carries around the line number. The processing step is factored into process, which you can change according to the problem you are presented.
import System.IO
import Text.Printf
main = do
hSetBuffering stdin LineBuffering
s <- getLine
let number_of_lines_to_process = read s :: Integer
processLines number_of_lines_to_process
return ()
-- This reads "max" lines from stdin, processing each line and
-- printing the result.
processLines :: Integer -> IO ()
processLines max = doLine 0
where doLine i
| i == max = return ()
| otherwise =
do
line <- getLine
let result = process line
Text.Printf.printf "Line #%d: %d\n" (i + 1) result
doLine (i + 1)
-- Just an example. (This doubles the input.)
process :: [Char] -> Integer
process line = let number = read line :: Integer
in
number * 2
I'm a haskell rookie, so any critiques of the above are welcome.
Just as an alternative, I thought that you might enjoy an answer with minimal monad mucking and no do notation. We zip a lazy list of the user's data with an infinite list of the line number using the enumerate function to give us our desired output.
import System.IO
import Control.Monad (liftM)
--Here's the function that does what you really want with the data
example = (* 2)
--Enumerate takes a function, a line number, and a line of input and returns
--an ennumerated line number of the function performed on the data
enumerate :: (Show a, Show b, Read a) => (a->b) -> Integer -> String -> String
enumerate f i x = "Line #" ++
show i ++
": " ++
(show . f . read $ x) -- show . f . read handles our string conversion
-- Runover takes a list of lines and runs
-- an enumerated version of the sample over those lines.
-- The first line is the number of lines to process.
runOver :: [String] -> [String]
runOver (line:lines) = take (read line) $ --We only want to process the number of lines given in the first line
zipWith (enumerate example) [1..] lines -- run the enumerated example
-- over the list of numbers and the list of lines
-- In our main, we'll use liftM to lift our functions into the IO Monad
main = liftM (runOver . lines) getContents

Resources