Advance a simple calculator parser to read floating point numbers

Hello, I’m a newbie here, so this topic means to be my first activity with Haskell community. I’m trying to make a very simple calculator parser using Parsec. Since it reads and processes strings by drawing out some integers, this parser empowers addition, multiplication, subtraction, division, negation and factorial. There are some code lines I added into source file in prior to respective function definitions:

type Parser a = Parsec String () a

digit :: Parser Char
digit = oneOf ['0'..'9']

number :: Parser Integer 
number = read <$> many1 digit   

applyMany :: a -> [a -> a] -> a
applyMany x [] = x
applyMany x (h:t) = applyMany (h x) t

div_ :: Parser (Integer -> Integer -> Integer)
div_= do
	char '/'
	return div
	
star :: Parser (Integer -> Integer -> Integer)
star = do
	char '*'	
	return (*)	
	
plus :: Parser (Integer -> Integer -> Integer)
plus = do
	char '+'	
	return (+)
	
minus :: Parser (Integer -> Integer -> Integer)
minus = do
	char '-'	
	return (-)	
	
multiplication :: Parser Integer
multiplication = do
	spaces
	lhv <- atom
	spaces
	t <- many tail
	return $ applyMany lhv t
	where tail =
				do
					f <- star <|> div_
					spaces
					rhv <- atom
					spaces
					return (`f` rhv)
 	
	
addition :: Parser Integer
addition = do
	spaces
	lhv <- multiplication
	spaces
	t <- many tail
	return $ applyMany lhv t
	where tail =
				do
					f <- plus <|> minus
					spaces
					rhv <- multiplication
					spaces
					return (`f` rhv)
					
atom :: Parser Integer
atom = number <|> do
	char '('
	res <- addition
	char ')'
	return res

-- factorial 	
fact' :: Parser Integer
fact' = do
	spaces
	char '!'
	rhv <- atom 
	return $ factorial rhv  
	
factorial :: Integer -> Integer
factorial n
	| n == 0 || n == 1 = 1
	| otherwise = acc n 1
	where
	acc 0 a = a
	acc b a = acc (b-1) (b * a)  

-- negation	
neg' :: Parser Integer
neg' = do
	spaces
	char '~'
	rhv <- atom
	spaces
	return $ negate rhv

As you can see, this parser is compatible only with integer numbers. However, I need to extend its features by floating point operations to have an option to perform those as orderly as in cases of integers. May you give any tip how to manage that considering the code provided?

If you want to keep things simple, one way to do this would be to introduce an auxiliary datatype for numbers, e.g.:

data Number = IntegerN Integer | FloatingN Double

And then you can provide implementations for addition, and the other operations you are interested in.

However, I would recommend going a step further and adding an “expression” type, along the lines of:

data Expr
  = LiteralE Number
  | AddE Expr Expr
  | MulE Expr Expr
  | ...

… since that allows you to separate the “parsing” bits from the “evaluation” bits.

Thank you a lot. I intend adding a function which is thought to read floating point inputs for parser running. There is a stuff I use:

fp_char :: Parser String
fp_char = many1 digit

fp_number :: Parser Double
fp_number = read <$> parser where
parser = (++) <$> fp_char <> (option “” $ ( : ) <$> char ‘.’ <> fp_char)

It looks pretty well until someone enters kind of “423a.54” or “55.2ur” nonsense regarding the calculator operability. The current definition doesn’t compliant with requirement to filter out same or similar inputs blocking further computation. Following that, I assume that it would make a sense if adding a function like that:

isValidInput :: Parser String -> Bool
isValidInput a -> isValidInput (x:xs) = if x elem [‘0’…‘9’] then isValidInput xs else False

Most likely, elem use is a good idea to compare String elements against list [‘0’…‘9’], but my module fails when compiling that code due to an inappropriate type result:

Couldn’t match type [Char]' withParsecT String () Data.Functor.Identity.Identity String’
Expected type: Parser String
Actual type: [Char]

Is there any tip how to fix that error? Would the general approach be an intelligent way to proceed with fp parsing?

Just a general meta pointer: you can create code blocks on this website by wrapping the code with ```, which makes it a bit more readable. More info here.

What you need for floating point numbers is roughly “starting to read digits; then a dot (.), and then more digits”. This means that if you encounter any other characters after you’ve consumed a few, you would want to backtrack.

This can be achieved in Parsec by using the try combinator, so you would use that whenever you don’t want to “fully commit” to a parse path just yet. The downside of using try, however, is that it may hurt performance a bit, and error messages emitted from your parser may become less clear, so the general advice is to just use it where necessary.

If that is exactly your goal, you can ignore this reply. If on the other hand you’re not married to Parsec specifically, you may want to have a look at the much simpler example of arithmetic parser done using grammatical-parsers. I’m the author of the library. A bit more advanced example in the examples directory demonstrates the use of finally tagless parsing style, which lets you assign semantics to the parse separately from the act of parsing. Floating numbers would then be implemented by adding another method float :: Double -> e to the class ArithmeticDomain e and a parse alternative that invokes the method.