interviews-in23/Main.hs

79 lines
2.3 KiB
Haskell

{-# LANGUAGE OverloadedStrings #-}
module Main where
import Control.Applicative ((<|>),empty)
import Data.Attoparsec.Text (Parser, parseOnly, decimal, choice, option, sepBy, endOfLine, endOfInput, many1)
import qualified Data.Maybe as M
import qualified Data.Text as T
import qualified Data.Text.IO as T
insuranceNetworkParser :: Parser InsuranceNetworkAST
insuranceNetworkParser = many1 line
where
-- <line> ::= <insurer-id> ":" <percent> <optional-exprs>
-- <optional-exprs> ::= "" | "if" <exprs>
line :: Parser INASTLine
line = do
id <- insurerId
": "
pc <- percent
oe <- option [] (" if " *> exprs)
endOfLine
pure $ INASTLine id pc oe
-- <exprs> ::= <expr> | <expr> "and" <exprs>
exprs :: Parser [ INASTExpr ]
exprs = expr `sepBy` " and "
-- <expr> ::= <lesser-than> | <greater-than> | <equals> | <insurer-id>
expr :: Parser INASTExpr
expr = choice [ INASTExprLt <$> lt
, INASTExprGt <$> gt
, INASTExprEq <$> eq
, INASTExprInsurerId <$> insurerId ]
-- <lesser-than> ::= "<" <integer>
lt :: Parser INASTLt
lt = "<" *> integer
-- <greater-than> ::= ">" <integer>
gt :: Parser INASTGt
gt = ">" *> integer
-- <equals> ::= "=" <integer>
eq :: Parser INASTEq
eq = "=" *> integer
-- <insurer-id> ::= "I" <integer>
insurerId :: Parser INASTInsurerId
insurerId = "I" *> integer
-- <percent> ::= <integer> "%"
percent :: Parser INASTPercent
percent = integer <* "%"
-- <integer> ::= <digit> | <non-zero-digit> <integer>
-- Overapproximation of the grammar
integer :: Parser Int
integer = decimal
type InsuranceNetworkAST = [INASTLine]
data INASTLine = INASTLine INASTInsurerId INASTPercent [INASTExpr]
deriving (Show)
data INASTExpr = INASTExprLt INASTLt
| INASTExprGt INASTGt
| INASTExprEq INASTEq
| INASTExprInsurerId INASTInsurerId
deriving (Show)
type INASTLt = Int
type INASTGt = Int
type INASTEq = Int
type INASTInsurerId = Int
type INASTPercent = Int
main :: IO ()
main = do
inputNetwork <- T.readFile "./input.network"
T.putStrLn "Using the following input network:"
T.putStrLn inputNetwork
T.putStrLn "Parsed AST:"
print (parseOnly insuranceNetworkParser inputNetwork)