Google Code Jam/Cheating a Boolean Tree

From HaskellWiki
Jump to navigation Jump to search

Problem

For this problem we will consider a type of binary tree that we will call a boolean tree. In this tree, every row is completely filled, except possibly the last (deepest) row, and the nodes in the last row are as far to the left as possible. Additionally, every node in the tree will either have 0 or 2 children.

What makes a boolean tree special is that each node has a boolean value associated with it, 1 or 0. In addition, each interior node has either an "AND" or an "OR" gate associated with it. The value of an "AND" gate node is given by the logical AND of its two children's values. The value of an "OR" gate likewise is given by the logical OR of its two children's values. The value of all of the leaf nodes will be given as input so that the value of all nodes can be calculated up the tree.

The root of the tree is of particular interest to us. We would really like for the root to have the value V, either 1 or 0. Unfortunately, this may not be the value the root actually has. Luckily for us, we can cheat and change the type of gate for some of the nodes; we can change an AND gate to an OR gate or an OR gate to an AND gate.

Given a description of a boolean tree and what gates can be changed, find the minimum number of gates that need to be changed to make the value of the root node V. If this is impossible, output "IMPOSSIBLE" (quotes for clarity).

Input

The first line of the input file contains the number of cases, N. N test cases follow.

Each case begins with M and V. M represents the number of nodes in the tree and will be odd to ensure all nodes have 0 or 2 children. V is the desired value for the root node, 0 or 1.

M lines follow describing each of the tree's nodes. The Xth line will describe node X, starting with node 1 on the first line.

The first (M−1)/2 lines describe the interior nodes. Each line contains G and C, each being either 0 or 1. If G is 1 then the gate for this node is an AND gate, otherwise it is an OR gate. If C is 1 then the gate for this node is changeable, otherwise it is not. Interior node X has nodes 2X and 2X+1 as children.

The next (M+1)/2 lines describe the leaf nodes. Each line contains one value I, 0 or 1, the value of the leaf node.

To help visualize, here is a picture of the tree in the first sample input.

GCJ2008CheatingTree.png

Output

For each test case, you should output:

Case #X: Y

where X is the number of the test case and Y is the minimum number of gates that must be changed to make the output of the root node V, or "IMPOSSIBLE" (quotes for clarity) if this is impossible.

Limits

1 < N ≤ 20

Small dataset

2 < M < 30

Large dataset

2 < M < 10000

Sample

Input

2
9 1
1 0
1 1
1 1
0 0
1
0
1
0
1
5 0
1 1
0 0
1
1
0

Output

Case #1: 1
Case #2: IMPOSSIBLE

Solution

All sets

import Control.Applicative
import Control.Arrow
import Control.Monad.State

data PNode = Gate Bool Type | Value Bool deriving Show
data Type = Or | And deriving Show
data Tree = Node Bool Type Tree Tree | Leaf Bool | Undefined deriving Show

node :: Tree -> State [PNode] Tree 
node (Node k g t1 t2) = liftM2 (Node k g) (node t1) (node t2) -- slip trough
node Undefined = do
	g:gs <- get
	put gs 
	return $ case g of
		Gate k g -> Node k g Undefined Undefined
		Value b  -> Leaf b
node l = return l -- state should be empty here, letting leaves through

tree :: [PNode] -> Tree
tree xs = fst . head . dropWhile (not.null.snd) . iterate (uncurry $ runState . node) $ (Undefined, xs)

both = uncurry $ liftM2 (+) --the price to pay to have both input with same value

best (Nothing, Nothing) = Nothing  -- minimum price to have at least one input of a value
best (Nothing, j) = j
best (j, Nothing) = j
best (Just j1, Just j2) = Just $ min j1 j2

value (Leaf False) = (Just 0, Nothing)
value (Leaf True) = (Nothing, Just 0)
value n@(Node _ _ t1 t2) = let
	ms v = both . (v.value *** v.value) 
	bs v = best . (v.value *** v.value) 
	[m0,m1,b0,b1] = map ($(t1,t2)) [ms fst, ms snd, bs fst, bs snd] in
	case n of
		Node False And _ _	-> (b0,m1)
		Node False Or  _ _ 	-> (m0,b1)
		Node True And  _ _ 	-> (b0,best (m1,((+1) <$> b1)))
		Node True Or   _ _ 	-> (best (m0,((+1) <$> b0)), b1)

main = enumFromTo (1::Int) <$> readLn >>= mapM_ doCase
  where doCase caseno = do
  		[m,v] <- map read . words <$> getLine
		ps <- replicateM (div (m - 1) 2) $ do
			[b1,b2] <- map read . words <$> getLine
			return $ [Gate False Or, Gate True Or,Gate False And, Gate True And] !! (b2 + 2* b1)
		ps' <- replicateM (div (m + 1) 2) $ ([Value False,Value True] !!) . read <$> getLine
  		putStrLn $ "Case #" ++ show caseno ++ ": " ++ (output v . value . tree $ ps ++ ps')
		where
			output n s = maybe "IMPOSSIBLE" show $ [fst,snd] !! n $ s