{-# LANGUAGE BangPatterns #-} import Control.Monad (liftM, forM_) import qualified Data.Set as Set import Data.Char (isSpace) import Text.Printf type Tree = (Double, Branch) data Branch = Leaf | Branch String Tree Tree deriving (Show) eval :: Set.Set String -> Double -> Tree -> Double eval fs = go where go !p (p1, Leaf) = p*p1 go !p (p1, Branch f t1 t2) = go (p*p1) (if Set.member f fs then t1 else t2) tokenize :: String -> [String] tokenize s = case dropWhile isSpace s of [] -> [] '(':s -> "(" : tokenize s ')':s -> ")" : tokenize s s -> case span (\c -> not (isSpace c || c=='(' || c==')')) s of (t,s) -> t : tokenize s parseTree :: String -> Tree parseTree s = fst (tree (tokenize s)) where tree :: [String] -> (Tree, [String]) tree ("(":w:ts) = case branch ts of (b, ")":ts) -> ((read w, b), ts) branch :: [String] -> (Branch, [String]) branch ts@(")":_) = (Leaf, ts) branch (feature:ts) = case tree ts of (t1, ts) -> case tree ts of (t2, ts) -> (Branch feature t1 t2, ts) main :: IO () main = do n <- liftM read getLine forM_ [(1::Int)..n] $ \i -> do l <- liftM read getLine s <- liftM concat $ sequence $ replicate l getLine let t = parseTree s a <- liftM read getLine fss <- sequence $ replicate a $ liftM (drop 2 . words) getLine printf "Case #%d:\n" i forM_ fss $ \fs -> printf "%.7f\n" $ eval (Set.fromList fs) 1 t