Skip to content

Instantly share code, notes, and snippets.

@Lazersmoke
Created August 22, 2017 02:12
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 Lazersmoke/3a5e2e44ef1c395b4f404180e245d93c to your computer and use it in GitHub Desktop.
Save Lazersmoke/3a5e2e44ef1c395b4f404180e245d93c to your computer and use it in GitHub Desktop.
Code review of proofskiddie's boolean evaluator

Code review of proofskiddie's boolean evaluator

Original: https://hastebin.com/ucuqijegec.vbs

Mirror: https://pastebin.com/2ZKhTswH

I've camelCased all the functions, since that is the standard in Haskell.

cartprod

-- cartesian product of lists
cartprod :: [[a]] -> [[a]]
cartprod [] = [[]]
cartprod (xs : xss) = [ x : ys | x <- xs, ys <- yss]
    where yss = cartprod xss

cartprod is just sequence :: Monad m => t (m a) -> m (t a) (or sequenceA :: Applicative f => t (f a) -> f (t a)) for lists. The intuition behind this is that sequence traverses the outer list, "performing" each inner list as an action, and collecting the results. Performing a list as an action is performing a non-deterministic selection on the elements, returning every possible value from the list. This is why [(*3),(*2)] <*> [1,10] is [3,30,2,20]. In our case, we perform this selection for each input list, then collect the results in a list. Thus, we select each item from each list, and juxtapose it will each item from each other list, which is the definition of a cartesian product.

build

You don't need this where clause at all, better to just put it inline. Use Bool instead of 0 and 1. You should use a different name because build is taken by the function that cancels with the list optimization function.

Also: Always include a type signature!

This function is only used once (in totalState) so you should put it in a where binding there.

Original:

-- all possible truth values on n vars
build n = cartprod xs
    where xs = take n $ repeat [0,1]

Revised:

truthTable :: Int -> [[Bool]]
truthTable n = sequence . take n $ repeat [False,True]

Expr Data Type

-- datatype for boolean logic
data Expr =
    Var String 
  | And Expr Expr
  | Or Expr Expr
  | Imp Expr Expr
  | Not Expr
  | Equiv Expr Expr
  | T | F

You can (and should) factor your T and F constructors out into a Lit Bool (literal) constructor to avoid repeating yourself. You can do what jd95 suggested (using a functor fixpoint), but that is needlessly complex for now. Just change | T | F to | Lit Bool.

State Type Synonym

The name State is already taken by monad transformer and effects libraries, so you should use a more descriptive name, like VariableEnvironment. You are also using it as a map, so let's switch to using Data.Map since that is much faster for lookups (O(log n) vs O(n)) than a linked list. You will have to import qualified Data.Map as Map.

-- Map from variable names to values
type VariableEnvironment = Map.Map String Bool

eval

-- evaluate a boolean expression
eval :: Expr -> State -> Bool
eval exp state = case exp of
      Var str -> case lookup str state of
        Nothing -> error "variable not found"
        Just b  -> b
      And a b ->eval a state && eval b state
      Or  a b -> eval a state || eval b state
      Imp a b -> not (eval a state && (not $ eval b state))
      Not a   -> not $ eval a state
      Equiv a b -> eval a state== eval b state
      T -> True
      F -> False

This function is good except we need to update it to match the other changes, namely Lit case and using Map instead of a list for the environment. Notice how the Lit case is much more compact. error isn't exactly good practice, but proper error handling requires a lot of extra work for a toy evaluator.

-- evaluate a boolean expression
eval :: Expr -> VariableEnvironment -> Bool
eval exp state = case exp of
      Var str -> case Map.lookup str state of
        Nothing -> error "variable not found"
        Just b  -> b
      And a b -> eval a state && eval b state
      Or  a b -> eval a state || eval b state
      Imp a b -> not (eval a state && (not $ eval b state))
      Not a   -> not $ eval a state
      Equiv a b -> eval a state == eval b state
      Lit b -> b

Misc. functions

Type signature! Also, this is only used in makeState, so it should be moved to a where binding there.

-- possible names
alph :: [Char]
alph = ['a' .. 'z'] ++ ['A' .. 'Z']

makestate has to be updated to work with a Map. This just means adding Map.fromList at the end, to take our association list to a proper Map. This is relatively expensive to create, but the lookup is fast so it's OK. We can also drop the not $ y == 0 part because we made truthTable output Bools above.

Also, this function is only used once (in totalState), so you should move it to a where binding in that function (not shown here).

-- make state from a list of ints (uses as default left to right entries in alph)
makeState :: [Int] -> VariableEnvironment
makeState = Map.fromList . zipWith (\x y -> ([x], y)) alph

rmdup is just nub :: Eq a => [a] -> [a] from Data.List

-- remove duplicate strings from a list (used in getvars)
rmdup :: [String] -> [String]
rmdup [] = []
rmdup (x:xs) | elem x xs = rmdup xs
             | otherwise = x : rmdup xs

getvars must be updated to account for the Lit constructor. A fun exercise would be to parameterize Expr over the type of the parameter to Var, and make it foldable to make getvars = Data.Foldable.toList.

This function is only used once (in countVar), so it should be moved to a where binding under countVar or totalState.

-- return the Strings held by variables in an expression
getVars :: Expr -> [String]
getVars exp = case exp of
  Var str -> [str]
  And a b -> getvars a ++ getvars b
  Or a b  -> getvars a ++ getvars b
  Imp a b -> getvars a ++ getvars b
  Equiv a b -> getvars a ++ getvars b
  Not a   -> getvars a
  Lit _ -> []

countvar is only used once (in totalState), so you should move it to a where binding there.

-- count the number of distinct vars in an expression
countVar :: Expr -> Int
countVar = length . rmdup . getvars

totalstate can be made pointfree

-- create state of all possible vars in an expression
totalState :: Expr -> [VariableEnvironment]
totalState = map makeState . truthTable . countVar

totaleval looks good

-- eval expression under all possible states
totalEval :: Expr -> [Bool]
totalEval exp = map (eval exp) (totalState exp)

Examples look good.

a = Var "a"
b = Var "b"
c = Var "c"

ex_a = (Imp (Imp (Imp a b) b) b)
ex_b = (Imp (Imp (Imp a b) b) a)
ex_c = (Imp (Imp (Imp a b) a) a)
ex_d = (Imp (Imp (Imp b c) (Imp a b)) (Imp a b))
ex_e = (Imp (Or a (Not (And b c))) (Or (Equiv a c) b))
ex_f = (Imp a (Imp b (Imp b a)))
ex_g = (Imp (And a b) (Or a c))

-- example : totaleval ex_a = [True, True, True, True]
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment