Skip to content

Instantly share code, notes, and snippets.

@quickdudley
Forked from 5outh/DeMorgan.hs
Last active June 29, 2017 00:29
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 quickdudley/ce5f88f6b1988e096df42d3dcb6ba808 to your computer and use it in GitHub Desktop.
Save quickdudley/ce5f88f6b1988e096df42d3dcb6ba808 to your computer and use it in GitHub Desktop.
DeMorgan
{-# LANGUAGE NoMonomorphismRestriction #-}
import Text.ParserCombinators.Parsec
import Text.ParserCombinators.Parsec.Token hiding (parens)
import Text.ParserCombinators.Parsec.Expr
import Control.Applicative hiding ((<|>))
import Control.Monad
import Prelude hiding (not)
data Expr = Not Expr | And Expr Expr | Or Expr Expr | Var Char | SubExpr Expr deriving Eq
not :: Expr -> Expr
not (Not e) = e
not (And e1 e2) = Or (not e1) (not e2)
not (Or e1 e2) = And (not e1) (not e2)
not (Var c) = Not (Var c)
not (SubExpr e) = not e
instance Show Expr where
showsPrec p e = let
mb s = if p == 0
then s
else ('(':) . s . (')':)
in case e of
(Not e') -> mb $ ("NOT "++) . showsPrec 1 e'
(AND e1 e2) -> mb $ showsPrec 1 e1 . (" AND "++) . showsPrec 1 e2
(OR e1 e2) -> mb $ showsPrec 1 e1 . (" OR "++) . showsPrec 1 e2
(Var c) -> (c:)
(SubExpr e') -> showsPrec 1 e'
parseExpr :: String -> Either ParseError Expr
parseExpr = parse expr ""
where expr = buildExpressionParser operators term <?> "compound expression"
term = parens expr <|> variable <?> "full expression"
operators = [ [Prefix (string "NOT" >> spaces >> return Not)]
, [binary "AND" And]
, [binary "OR" Or] ]
where binary n c = Infix (string n *> spaces *> pure c) AssocLeft
variable = Var <$> (letter <* spaces) <?> "variable"
parens p = SubExpr <$> (char '(' *> spaces *> p <* char ')' <* spaces) <?> "parens"
main = mapM_ printNotExpr . lines =<< readFile "inputs.txt"
where printNotExpr e = case parseExpr e of
Right x -> print $ not x
Left e -> error $ show e
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment