Wednesday, August 27, 2008

Ten = 1+2+3+4

Daniel Lyons on his blog, showed us how to how to arith our way to 10 in Prolog using the operations of addition, subtraction, multiplication, and division and the numbers 1, 2, 3, and 4. A straightforward logic program, which I was hoping to duplicate the feel of in Haskell. Here's my go at it.
> module Ten where

> import Control.Monad
> import Data.List
> import Smullyan


I suppose the standard way people going about enumerating the arithmetic operations is to encode it in the following way ...
> {-
> data BinaryOp = Plus | Minus | Div | Times deriving Eq

> op :: BinaryOpIntIntMaybe Int
> op Plus b a = Just $ a + b
> op Minus b a = Just $ a - b
> op Times b a = Just $ a * b
> op Div b a = if b ≡ 0 ∨ a `rem` b ≠ 0
> then Nothing
> else Just (a `div` b)

> instance Show BinaryOp where
> show Plus = "+"
> show Minus = "-"
> show Div = "/"
> show Times = "x"
> -}


... but I shied away from that approach for two reasons: first and foremost, we have a disjoint type with enumerated values, but later we are going to choose from those enumerated values from a list of all those values. It seems to me to be wastefully redundant to enumerate the values of the type in its declaration, and then be required to enumerate those values again in their use. Wastefully redundant and dangerous — the type guarantees that I will not use values outside the type, but how can I guarantee that I've used all the values of the type in the program? I'm mean, of course, besides full coverage using a dependently typed system, that is.

So instead of the above commented out code, I chose the following type definition:
> data BinaryOp = Op (IntIntInt) String


This type has the advantage that the arithmetic operation is embedded in the type itself, as well as showing and equality:
> instance Eq BinaryOp where
> (Op _ a) ≡ (Op _ b) = a ≡ b

> instance Show BinaryOp where
> show (Op _ s) = s

> op :: BinaryOpIntIntMaybe Int
> op (Op f s) b a | s ≡ "/" = if b ≡ 0 ∨ a `rem` b ≠ 0
> then Nothing
> else Just (a `div` b)
> | otherwise = Just $ f a b


I know that some of you are going to be raising your eyebrows in disbelief: I've forsaken a pure and dependable, or compile-time, way to distinguish operations with a very weak string, or runtime, representation. The former is "just the way it makes sense" for most; the latter, my "sensible" compromise, sacrificing type safety for a more declarative representation. Again, if we had dependent types, I think there would be a type-safe way to represent arithmetic operators as comparable (distinct) and showable types ... dependent types for Haskell', anyone?

Okay, now we need to write permute, because this isn't C++ or Java. *sigh* That's correct, you heard it here first: Java and C++ are way better programming languages because they have permute in their standard libraries, and Haskell does not.
> permute :: Eq a ⇒ [a] → [[a]]
> permute list@(h:t) = [x:rest | x ∈ list,
> rest ∈ permute (list \\ [x])]
> permute [] = [[]]


And from that the solver simply follows: it's the permutation of the row of numbers matched with any arbitrary (ambiguous) arithmetic operation. This has the flavor of the days when I was writing code in MMSForth, push the numbers on the stack and then call the operators. Oh, JOY! (I'll stop now.)
> solver = [twiner perms [op1, op2, op3] |
> perms@[a,b,c,d] ∈ permute [1..4],
> op1 ∈ amb, op2 ∈ amb, op3 ∈ amb,
> ((op op1 b a >>= op op2 c >>= op op3 d)
> ≡ Just 10)]

> amb = [Op (+) "+", Op (*) "x", Op div "/", Op (-) "-"]


So, all we need is the display mechanic (twiner) to intersperse the arithmetic operators between the provided numbers. I had started down this path ...
> stringIt :: BinaryOpIntStringString
> stringIt op num acc = "(" ++ acc ++ show op ++ show num ++ ")"

> twiner :: [Int] → [BinaryOp] → String
> {-
> twiner args ops = doTwine args ops True ""
> where doTwine args ops binary acc | binary =
> let (arg1, rest) = (head args, tail args)
> (arg2, done) = (head rest, tail rest)
> in doTwine done (tail ops) False
> (stringIt (head ops) arg2 (show arg1))
> | ops == [] = acc
> | otherwise =
> doTwine (tail args) (tail ops) False
> (stringIt (head ops) (head args) acc)
> -}


... looking longingly at intersperse in the Data.List module (why, oh, why! can't they have intersperse take a state-function argument? Oh, because I would be the only person using it?), but, I figured, as I have already reinvented takeWhile, I had better not reinvent zipWith here:
> twiner (h:r) ops = foldl t (show h) (doTwine r)
> where doTwine args = zipWith (c stringIt) args ops


... *ahem* dependent types would guarantee that twiner is never called with an empty list of arguments.

I'd say my Haskell version follows in the spirit of the Prolog version in that it uses nondeterminism (of the Maybe and list MonadPlus types) to select the true equations. Weighing in at 18 lines of type declarations and code (with 4 additional lines for the module declaration and the imports), it is also about the same size as the Prolog version as well.

Goodness! Typeful logic programming in Haskell, with all the functional frosting on the cake applied for free, costs no more than developing a Prolog program, and along with the type-safety, it also carries with it the flavor and the feel of logic programming in Prolog as well.

3 comments:

Anonymous said...

Looks like you got all the "((a `op1` b) `op2` c) `op3` d" solutions but missed the "(a `op1` b) `op2` (c `op3` d)" ones...

meteficha said...
This comment has been removed by the author.
Unknown said...

http://haskell.org/ghc/docs/7.0-latest/html/libraries/base-4.3.1.0/Data-List.html#v:permutations