{-# LANGUAGE BangPatterns #-} import Control.Monad (liftM, forM_) import Data.Array import qualified Data.IntMap as IM import qualified Data.IntSet as IS import qualified Data.Set as Set import qualified Data.Map as Map import System.IO (hFlush, stdout) import Text.Printf data Op = Plus | Minus deriving (Show, Eq, Ord) type Val = Int data Expr = I {-# UNPACK #-} !Val | Con Expr !Op {-# UNPACK #-} !Val deriving (Show, Eq, Ord) showExpr :: Expr -> String showExpr (I d) = show d showExpr (Con e op d) = showExpr e ++ (if op==Plus then "+" else "-") ++ show d type Pos = (Int,Int) type ASquare = Array Pos (Either Val Op) parse :: Int -> [String] -> ASquare parse w rows = array ((1,1),(w,w)) $ do (y,row) <- zip [1..] rows (x,c) <- zip [1..] row let v = case c of '+' -> Right Plus '-' -> Right Minus d -> Left $ read [d] return $ ((x,y), v) move :: ASquare -> (Val,Pos,Expr) -> [(Val,Pos,Expr)] move s (v,p,e) = do let b = bounds s neighbers :: (Int,Int) -> [(Int,Int)] neighbers (x,y) = filter (inRange b) [(x+1,y),(x-1,y),(x,y+1),(x,y-1)] p1 <- neighbers p let Right !op = s!p1 p2 <- neighbers p1 let Left !x = s!p2 return ((if op==Plus then (+) else (-)) v x, p2, Con e op x) solve :: ASquare -> IS.IntSet -> IM.IntMap Expr solve s xs = go xs IM.empty Set.empty (Map.fromList [((d,p), I d) | (p, Left d) <- assocs s]) where go :: IS.IntSet -> IM.IntMap Expr -> Set.Set (Val,Pos) -> Map.Map (Val,Pos) Expr -> IM.IntMap Expr go vs ans visited ts | IS.null vs = ans | otherwise = go (IS.difference vs (IM.keysSet matched)) (IM.union ans matched) (Set.union visited (Map.keysSet new)) (Map.fromListWith min [((v',p'),e') | ((v,p),e) <- Map.toList new, (v',p',e') <- move s (v,p,e)]) where new = Map.filterWithKey (\k _ -> Set.notMember k visited) ts matched = IM.fromAscListWith min [(v,e) | ((v,_),e) <- Map.toAscList new, IS.member v vs] main :: IO () main = do t <- liftM read getLine forM_ [(1::Int)..t] $ \i -> do [w,q] <- liftM (map read . words) getLine s <- liftM (parse w) $ sequence $ replicate w getLine xs <- liftM (take q . map read . words) getLine let ans = solve s (IS.fromList xs) printf "Case #%d:\n" i forM_ xs $ \x -> putStrLn (showExpr (ans IM.! x)) hFlush stdout