{-# LANGUAGE BangPatterns #-} import Control.Monad (liftM, forM_) import Data.Array import Data.List (sort) import Data.Maybe (maybeToList) import qualified Data.IntMap as IM import qualified Data.IntSet as IS import System.IO (hFlush, stdout) import Text.Printf data Op = Plus | Minus deriving (Show, Eq, Ord) data Expr = I {-# UNPACK #-} !Int | Con Expr !Op {-# UNPACK #-} !Int 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 ASquare = Array (Int,Int) (Either Int 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) type Table = Array (Int,Int) (IM.IntMap Expr) tables :: ASquare -> [Table] tables s = iterate g table1 where 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)] table1 :: Table table1 = accumArray (\_ x -> x) IM.empty b [(i, IM.singleton d (I d)) | (i, Left d) <- assocs s] g :: Table -> Table g table = accum f table xs where f :: IM.IntMap Expr -> (Int, Expr) -> IM.IntMap Expr f m (v,e) = case IM.lookup v m of Nothing -> IM.insert v e m Just e' -> if e' < e then m else IM.insert v e m xs :: [((Int,Int), (Int, Expr))] xs = do (i, m) <- assocs table (v, e) <- IM.toList m j <- neighbers i let Right !op = s!j k <- neighbers j let Left !x = s!k v' = (if op==Plus then (+) else (-)) v x e' = Con e op x seq v' $ return (k, (v',e')) f :: IS.IntSet -> IM.IntMap Expr -> [Table] -> IM.IntMap Expr f xs !ret (t:ts) | IS.null xs = ret | otherwise = f xs' ret' ts where m = IM.unionsWith min (elems t) xs' = IS.difference xs (IM.keysSet m) ret' = IM.union ret $ IM.fromAscList [(x,e) | x <- IS.toList xs, e <- maybeToList (IM.lookup x m)] 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 = f (IS.fromList xs) IM.empty (tables s) printf "Case #%d:\n" i forM_ xs $ \x -> putStrLn (showExpr (ans IM.! x)) hFlush stdout