Haskell Quiz/Numeric Maze/Solution Ninju

From HaskellWiki
Jump to navigation Jump to search
The printable version is no longer supported and may have rendering errors. Please update your browser bookmarks and please use the default browser print function instead.


I haven't yet added any optimization, because I wanted to keep the program as simple (and therefore readable) as possible, but I might add some later.

module Main where
import System.Environment
import Data.List

main :: IO ()
main = do args <- getArgs
          if length args == 2 
            then do let [a,b] = map read args
                    putStrLn $ show (solve a b)
            else putStrLn "Usage: solve START TARGET"
          return ()
    
data Operation = AddTwo Integer | Double Integer | Halve Integer

valid :: Operation -> Bool
valid (Halve x) = x `mod` 2 == 0
valid _         = True

apply :: Operation -> Integer
apply (AddTwo x) = x + 2 
apply (Double x) = x * 2 
apply (Halve x) = x `div` 2

solve :: Integer -> Integer -> [Integer]
solve a b = solve' [[a]] b
            where
            solve' paths target = case find ((== target) . last) paths of
                                    Just path -> path
                                    Nothing -> solve' (concatMap buildPathsFrom paths) target
            buildPathsFrom path = [ path ++ [apply (op (last path))] | op <- [AddTwo, Double, Halve], valid (op (last path)) ]