2
\$\begingroup\$

I recently started to learn Haskell in order to write some small tools for me. Currently I'm working on a program which calculates how much steam a (railcraft) boiler of a given size outputs per tick.

In the console the user inputs a string of the following format: S | L | BL-Size | BH-Size, example BH-3x3x4

I then use ParserCombinators from the Text.ParserCombinators.ReadP library to parse this string into a custom type. However I think my parser is overly complicated. Any suggestions how to simplify the following code?

module Boilers (Boiler(..), Tank(..)) where
data Boiler = Hobbyist | Locomotive | Boiler (Int, Int, Int) Tank deriving (Show)
data Tank = HighPressure | LowPressure deriving (Eq, Show)
module BoilerParser where
import Data.Char
import Text.ParserCombinators.ReadP
import Control.Applicative
import Boilers
import Data.Maybe
boiler :: ReadP Boiler
boiler = do
 b <- standard <++ hobbyist <++ locomotive
 maybe pfail return b
standard :: ReadP (Maybe Boiler)
standard = do
 satisfy (\c -> toUpper c == 'B')
 t <- fmap (\t -> case toUpper t of
 'H' -> Just HighPressure
 'L' -> Just LowPressure
 _ -> Nothing) get
 satisfy (== '-')
 s <- BoilerParser.size
 case t of
 Nothing -> pfail
 (Just a) -> return (Just (Boiler s a))
hobbyist :: ReadP (Maybe Boiler)
hobbyist = fmap (\c -> if toUpper c == 'H' then Just Hobbyist else Nothing) get
locomotive :: ReadP (Maybe Boiler)
locomotive = fmap (\c -> if toUpper c == 'L' then Just Locomotive else Nothing) get
size :: ReadP (Int, Int, Int)
size = do
 x <- size' 1
 satisfy (== 'x')
 y <- size' 1
 satisfy (== 'x')
 z <- size' 1
 return (x,y,z)
size':: Int -> ReadP Int
size' ds = fmap read (count ds (satisfy isDigit))
asked Aug 22, 2016 at 17:13
\$\endgroup\$

1 Answer 1

2
\$\begingroup\$
boiler :: ReadP Boiler
boiler
 = Hobbyist <$ char 'H'
 <|> Locomotive <$ char 'L'
 <|> flip Boiler <$ char 'B'
 <*> (HighPressure <$ char 'H' <|> LowPressure <$ char 'L')
 <*> ((,,) <$ char '-'
 <*> (read <$> munch1 isDigit) <* char 'x'
 <*> (read <$> munch1 isDigit) <* char 'x'
 <*> (read <$> munch1 isDigit))

By changing the internal definition of Boiler you can clean up that flip.

By also changing the user interface you can use the Read instance deriver:

data Boiler = H | L | BL Int Int Int | BH Int Int Int deriving (Read, Show)

Your example would then look like BH 3 3 4.

By the way, whereever you're using the Eq instance of Tank, consider pattern matching instead.

answered Aug 23, 2016 at 11:30
\$\endgroup\$
4
  • \$\begingroup\$ Tanks for the answer. I'll look into changing the definitions.But I'm a bit puzzled about the <$ operator ? What does it do? Is it simply a left biased $ or does it do something else? \$\endgroup\$ Commented Aug 23, 2016 at 16:28
  • \$\begingroup\$ It is the thing with the characteristic property of having the type signature Functor f => a -> f b -> f a :P. a <$ b = fmap (const a) b. Note the existence of hayoo.fh-wedel.de . \$\endgroup\$ Commented Aug 23, 2016 at 17:22
  • \$\begingroup\$ Yeah, I searched Hoogle, but found nothing the first time. Second time it was there. Anyway: Additional question: You said I can change my data so I can use the Read instance deriver. Care to elaborate? I'm not sure how to do it. \$\endgroup\$ Commented Aug 23, 2016 at 21:02
  • \$\begingroup\$ Using data Boiler = H | L | BL Int Int Int | BH Int Int Int deriving (Read, Show) instead of your definitions of Boiler and Tank will give you access to, for example, readLn :: IO Boiler, which turns an input line like "BH 3 3 4" into a Boiler value. \$\endgroup\$ Commented Aug 23, 2016 at 22:16

Your Answer

Draft saved
Draft discarded

Sign up or log in

Sign up using Google
Sign up using Email and Password

Post as a guest

Required, but never shown

Post as a guest

Required, but never shown

By clicking "Post Your Answer", you agree to our terms of service and acknowledge you have read our privacy policy.

Start asking to get answers

Find the answer to your question by asking.

Ask question

Explore related questions

See similar questions with these tags.