Skip to content

Instantly share code, notes, and snippets.

@ondrap
Last active June 26, 2018 18:38
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save ondrap/69fa2162bc2516469642e5380b379f5c to your computer and use it in GitHub Desktop.
Save ondrap/69fa2162bc2516469642e5380b379f5c to your computer and use it in GitHub Desktop.
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GADTs #-}
{-# LANGUAGE OverloadedStrings #-}
-- | Jednoducha kalkulacka, na vstupu ocekava vyrazy
-- 1 + 3
-- 1 - -3
-- atd.
module Main where
import Control.Monad (forever)
import qualified Data.ByteString as BS
import Data.Functor.Foldable (Fix (..), cata)
import Data.Scientific (toRealFloat)
import Data.Void
import Text.Megaparsec
import qualified Text.Megaparsec.Byte as M
import qualified Text.Megaparsec.Byte.Lexer as L
data ExprF a =
Num Double
| Op (Double -> Double -> Double) a a
deriving (Functor)
type Expr = Fix ExprF
type Parser = Parsec Void BS.ByteString
parser :: Parser Expr
parser = do
M.space
tnum >>= go
where
go n1 =
(do
op <- operator
n2 <- tnum
go (Fix (Op op n1 n2))
) <|> (eof >> return n1)
tnum = Fix . Num . toRealFloat <$> L.lexeme M.space (L.signed (return ()) L.scientific)
operator = oper (+) "+" <|> oper (-) "-" <|> oper (*) "*" <|> oper (/) "/"
where
oper f c = const f <$> L.symbol M.space c
compute :: Expr -> Double
compute = cata go
where
go (Num n) = n
go (Op op a1 a2) = op a1 a2
main :: IO ()
main =
forever $ do
line <- BS.getLine
case parse parser "input" line of
Right expr -> putStrLn ("Vysledek: " ++ show (compute expr))
Left err -> putStrLn ("Chyba parsingu: " ++ show err)
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment