Guidelines
When solving the homework, strive to create not just code that works, but code that is readable and concise. Try to write small functions which perform just a single task, and then combine those smaller pieces to create more complex functions.
Don’t repeat yourself: write one function for each logical task, and reuse functions as necessary.
Don't be afraid to introduce new functions where you see fit.
Each task has corresponding source file in src directory where you should implement the solution.
All solutions should compile without warnings with following command:
stack buildYou can and should run automated tests before pushing solution to GitHub via
stack test --test-arguments "-p TaskX"where X in TaskX should be number of corresponding Task to be tested.
So to run all test for the first task you should use following command:
stack test --test-arguments "-p Task1"You can also run tests for all tasks with just
stack testFor debugging you should use GHCi via stack:
stack ghciYou can then load your solution for particular task using :load TaskX command.
Here is how to load Task1 in GHCi:
$ stack ghci
ghci> :load Task1
[1 of 1] Compiling Task1 ( .../src/Task1.hs, interpreted )
Ok, one module loaded.Note: if you updated solution, it can be quickly reloaded in the same GHCi session with
:reloadcommandghci> :reload
In this assignment you will implement generalized representation for arbitrary expressions.
It is recommended for tasks to be implemented in order.
Before attempting to generalize anything, you should always first write something simple and concrete as a prototype, and then see what can be abstracted and generalized.
Your first task is to implement representation for integer arithmetic expressions with just two binary operations: addition and multiplication.
In fact the representation for this task is already provided in src/Task1.hs:
-- | Representation of integer arithmetic expressions comprising
-- - Literals of type 'a'
-- - Binary operations 'Add' and 'Mul'
data IExpr =
Lit Integer
| Add IExpr IExpr
| Mul IExpr IExpr
deriving ShowYour goal will be to implement evaluation of these expressions and parsing from string representation in Reverse Polish Notation.
In src/Task1.hs you will find following definition for integer arithmetic expressions:
data IExpr =
Lit Integer
| Add IExpr IExpr
| Mul IExpr IExpr
deriving ShowFeel free to derive any other type classes like
Eqif necessary.
Using provided representation implement function evalIExpr
which fully evaluates given expression.
evalIExpr :: IExpr -> IntegerExample:
>>> evalIExpr (Lit 2)
2
>>> evalIExpr (Add (Lit 2) (Lit 3))
5
>>> evalIExpr (Add (Mul (Lit 3) (Lit 2)) (Lit 3))
9Next you need to implement parsing of IExpr from
Reverse Polish Notation
(RPN).
Since RPN is just one of many possible string representations
for arithmetic expressions, it makes sense to abstract
parsing into a dedicated type class (like Read from Prelude).
However, instead of using built-in type class Read you should
use a much simpler type class Parse provided in src/Task1.hs.
-- | Class of parseable types
class Parse a where
-- | Parses value 'a' from given string
-- wrapped in 'Maybe' with 'Nothing' indicating failure to parse
parse :: String -> Maybe aDefine an instance of Parse for IExpr which will parse
arithmetic expression in RPN with symbols + and *
representing addition and multiplication respectively.
instance Parse IExpr where
parse = ...Tip
For simple parsing like in this assignment you can use standard function
words
from Prelude to split given string by spaces into a list of words.
Example:
>>> parse "2" :: Maybe IExpr
Just (Lit 2)
>>> parse "2 3 +" :: Maybe IExpr
Just (Add (Lit 2) (Lit 3))
>>> parse "3 2 * 3 +" :: Maybe IExpr
Just (Add (Mul (Lit 3) (Lit 2)) (Lit 3))
>>> parse "2 +" :: Maybe IExpr
Nothing
>>> parse "2 3" :: Maybe IExpr
NothingFinally, combine both evaluation and parsing into
single function evaluateIExpr, which parses RPN
and immediately evaluates it.
evaluateIExpr :: String -> Maybe IntegerExample:
>>> evaluateIExpr "2"
Just 2
>>> evaluateIExpr "2 3 +"
Just 5
>>> evaluateIExpr "3 2 * 3 +"
Just 9
>>> evaluateIExpr "2 +"
Nothing
>>> evaluateIExpr "2 3"
NothingNote that result is wrapped into
MaybewithNothingindicating that given expression could not be parsed as RPN.
Now that you have a prototype for Integer expressions
with couple of operations, it is time to extend its functionality
in a more general representation.
In particular, new representation should
- support expressions with variables (like
x 2 +) - support arbitrary domain type (not only
Integer) - support different binary operations for different domain types
Based on outlined requirements, prototype from first task needs to be
extended with additional constructor Var String and become parameterized
with domain type a and type of binary operations (enumeration) op.
Again, this new representation is already provided in src/Task2.hs:
-- | Generalized representation of expressions comprising
-- - Literals of type 'a'
-- - Variables with arbitrary 'String' names
-- - Binary operations of type 'op'
data Expr a op =
Lit a
| Var String
| BinOp op (Expr a op) (Expr a op)
deriving ShowAlso provided is enumeration of integer binary operations, this time with subtraction:
-- | Integer binary operations
data IntOp = Add | Mul | Sub
deriving ShowDefine an instance of Parse for Expr that parses expression from RPN.
Note that because Expr is parameterized with types a and op, you will need to
require these types to be instances of Parse as well:
instance (Parse a, Parse op) => Parse (Expr a op) where
parse = ...Example:
>>> parse "2" :: Maybe (Expr Integer IntOp)
Just (Lit 2)
>>> parse "2 3 -" :: Maybe (Expr Integer IntOp)
Just (BinOp Sub (Lit 2) (Lit 3))
>>> parse "3 2 * 3 +" :: Maybe (Expr Integer IntOp)
Just (BinOp Add (BinOp Mul (Lit 3) (Lit 2)) (Lit 3))
>>> parse "2 +" :: Maybe (Expr Integer IntOp)
Nothing
>>> parse "2 3" :: Maybe (Expr Integer IntOp)
NothingEvaluating these generalized expressions is not as simple as it was in first task,
because semantics of the same binary operation may be different depending on domain type
(e.g. addition operation must be evaluated completely differently in Integer expressions
and in Float expressions).
In order to solve this problem we can introduce yet another type class Eval a op,
parameterized with both the domain type a and binary operations op, allowing us
to define separate implementations for operations in different contexts:
-- | Class of evaluatable types
class Eval a op where
-- | Evaluates given binary operation with provided arguments
evalBinOp :: op -> a -> a -> aImplement instance of Eval for Integer with IntOp operations.
Note
Haskell 2010 prohibits type classes with multiple parameters. However, this restriction can be lifted with following pragma
{-# LANGUAGE MultiParamTypeClasses #-}In modern Haskell versions (GHC2021 and GHC2024) this pragma is enabled by default.
Next, implement function evalExpr which evaluates given expression
using given association list of variable values:
evalExpr :: (Eval a op) => [(String, a)] -> Expr a op -> Maybe aReturns
Nothingin case appropriate variable value is missing.
Example:
>>> evalExpr [] (Lit 2 :: Expr Integer IntOp)
Just 2
>>> evalExpr [("x", 3)] (BinOp Add (Lit 2) (Var "x")) :: Maybe Integer
Just 5
>>> evalExpr [("x", 3)] (BinOp Add (Lit 2) (Var "y")) :: Maybe Integer
NothingFinally, we need to combine both generalized evaluation and parsing into single function.
In fact, this function is already provided in src/Task2.hs:
evaluate :: (Eval a op, Parse a, Parse op) => Reify a op -> [(String, a)] -> String -> Maybe a
evaluate reify m s = case parse s of
Just e -> evalExpr m (reify e)
Nothing -> NothingCheck out the explanation below to understand why this generic function is the way it is.
So your job is to only implement the Integer-specific version in evaluateInteger
using this predefined function evaluate:
evaluateInteger :: [(String, Integer)] -> String -> Maybe IntegerExample:
>>> evaluateInteger [] "2"
Just 2
>>> evaluateInteger [("x", 3)] "2 x -"
Just (-1)
>>> evaluateInteger [("x", 3)] "2 y -"
Nothing
>>> evaluateInteger [] "3 2 * 3 +"
Just 9
>>> evaluateInteger [] "2 +"
Nothing
>>> evaluateInteger [] "2 3"
NothingImportant
Ideally we would have the following function that will use parse and evalExpr
in its definition:
evaluate :: (Eval a op, Parse a, Parse op) => [(String, a)] -> String -> Maybe a
evaluate m s = case parse s of
Just e -> evalExpr m e
Nothing -> NothingHowever, if you try to implement it as shown, the compiler will start complaining:
• Could not deduce (Parse op0) arising from a use of ‘parse’
from the context: (Eval a op, Parse a, Parse op)
...
• Could not deduce (Eval a op0) arising from a use of ‘evalExpr’
from the context: (Eval a op, Parse a, Parse op)
...
We accidentally defined way too general function,
such that compiler cannot prove that the expression e
has type Expr a op with the same a and op which are used in constraints.
Even specifying explicit type as e :: Expr a op will not work,
because a and op in this type signature have no relation
to a and op in constraints. In this case they are just some random
names for generic type parameters (we might as well have specified it
as e :: Expr foo bar to the same result).
There is no way to reference generic type parameter names from inside of function definition, only in function signature itself.
So to workaround this problem we pass explicit "conversion" in form of Reify
function to reconcile generic type of intermediate e :: Expr foo bar
with concrete type Expr a op implied by constraints:
type Reify a op = Expr a op -> Expr a opIn reality this is just identity function specialized for concrete pair of a and op:
reifyInteger :: Reify Integer IntOp
reifyInteger = idAlthough this is kind of ugly, it at least resolves the problem, allowing GHC to infer correct
type of intermediate expression Expr, which is not present anywhere in signature of evaluate.
The last task is to implement brute force SAT solver
using representation Expr (from previous task) for Boolean formulas in Reverse Polish Notation.
In computer science and formal methods, a SAT solver is a computer program which aims to solve the Boolean satisfiability problem (SAT). On input a formula over Boolean variables, such as "(x or y) and (x or not y)", a SAT solver outputs whether the formula is satisfiable, meaning that there are possible values of x and y which make the formula true, or unsatisfiable, meaning that there are no such values of x and y. In this case, the formula is satisfiable when x is true, so the solver should return "satisfiable".
You should implement function solveSAT which parses given Boolean formula in Reverse Polish Notation
and returns whether this formula is satisfiable wrapped into Maybe with Nothing indicating
parsing failure:
solveSAT :: String -> Maybe BoolInput formula will consist of variables and following binary operations:
andorxor
Example:
>>> solveSAT "x y and"
Just True
>>> solveSAT "x y xor x y and and"
Just False
>>> solveSAT "x y xor x y and or"
Just True
>>> solveSAT "x xor"
NothingTip
When implementing enumeration of all possible variable mappings it might be helpful to use list comprehensions in some way.
Here is example of generating all pairs, where first element is from list [1,2,3] and second from ['a','b']:
>>> [(x, y) | x <- [1,2,3], y <- "ab"]
[(1,'a'),(1,'b'),(2,'a'),(2,'b'),(3,'a'),(3,'b')]