Skip to content

Instantly share code, notes, and snippets.

@hoheinzollern
Last active October 5, 2016 16:21
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 hoheinzollern/1d0b281d01d1cea65aa0b8c93f098f6b to your computer and use it in GitHub Desktop.
Save hoheinzollern/1d0b281d01d1cea65aa0b8c93f098f6b to your computer and use it in GitHub Desktop.
module Main where
import Data.List
import Control.Exception
instance Show Expr where
show (e@(Plus e1 e2)) = autoparl e e1 ++ " + " ++ autoparr e e2
show (e@(Minus e1 e2)) = autoparl e e1 ++ " - " ++ autoparr e e2
show (e@(Times e1 e2)) = autoparl e e1 ++ " * " ++ autoparr e e2
show (e@(Div e1 e2)) = autoparl e e1 ++ " / " ++ autoparr e e2
show (Const x) = show x
priority (Const x) = 5
priority (Times x y) = 4
priority (Div x y) = 4
priority (Plus x y) = 3
priority (Minus x y) = 3
autoparl e e1 = if priority e1 < priority e then "(" ++ show e1 ++ ")" else show e1
autoparr e e1 = if priority e1 <= priority e then "(" ++ show e1 ++ ")" else show e1
data Expr = Plus Expr Expr
| Minus Expr Expr
| Times Expr Expr
| Div Expr Expr
| Const Int
deriving (Eq)
eval :: Expr -> Maybe Int
eval (Const x) = do return x
eval (Plus x y) = do a <- eval x; b <- eval y; return (a + b)
eval (Minus x y) = do a <- eval x; b <- eval y; return (a - b)
eval (Times x y) = do a <- eval x; b <- eval y; return (a * b)
eval (Div x y) = do a <- eval x; b <- eval y; if b /= 0 then Just (a `div` b) else Nothing
nums = map Const [1,2,3,4,5,6,7,8,9]
goal = 1150
search [] = []
search [x] = case eval x of
Just y -> if y == goal then [x] else []
_ -> []
search forest = choose1 forest []
choose1 [] l2 = []
choose1 (x:xs) l2 =
choose2 x xs l2 ++ choose1 xs (x:l2)
choose2 x [] l2 = []
choose2 x (x':xs) l2 =
explore x x' (xs ++ l2) ++
choose2 x xs (x':l2)
explore x y l =
search (Plus x y : l) ++
search (Minus x y : l) ++
search (Minus y x : l) ++
search (Times x y : l) ++
search (Div x y : l) ++
search (Div y x : l)
main = do
mapM_ print $ take 100 $ search nums
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment