Google Code Jam/Saving The Universe

From HaskellWiki
< Google Code Jam
Revision as of 17:54, 31 July 2008 by Paolino (talk | contribs) (Text added)
(diff) ← Older revision | Latest revision (diff) | Newer revision → (diff)
Jump to navigation Jump to search

Problem

The urban legend goes that if you go to the Google homepage and search for "Google", the universe will implode. We have a secret to share... It is true! Please don't try it, or tell anyone. All right, maybe not. We are just kidding.

The same is not true for a universe far far away. In that universe, if you search on any search engine for that search engine's name, the universe does implode!

To combat this, people came up with an interesting solution. All queries are pooled together. They are passed to a central system that decides which query goes to which search engine. The central system sends a series of queries to one search engine, and can switch to another at any time. Queries must be processed in the order they're received. The central system must never send a query to a search engine whose name matches the query. In order to reduce costs, the number of switches should be minimized.

Your task is to tell us how many times the central system will have to switch between search engines, assuming that we program it optimally.

Input

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

Each case starts with the number S -- the number of search engines. The next S lines each contain the name of a search engine. Each search engine name is no more than one hundred characters long and contains only uppercase letters, lowercase letters, spaces, and numbers. There will not be two search engines with the same name.

The following line contains a number Q -- the number of incoming queries. The next Q lines will each contain a query. Each query will be the name of a search engine in the case.

Output

For each input case, you should output:

Case #X: Y

where X is the number of the test case and Y is the number of search engine switches. Do not count the initial choice of a search engine as a switch.

Limits

0 < N ≤ 20

Small dataset

2 ≤ S ≤ 10
0 ≤ Q ≤ 100

Large dataset

2 ≤ S ≤ 100
0 ≤ Q ≤ 1000

Sample

Input

2
5
Yeehaw
NSM
Dont Ask
B9
Googol
10
Yeehaw
Yeehaw
Googol
B9
Googol
NSM
B9
NSM
Dont Ask
Googol
5
Yeehaw
NSM
Dont Ask
B9
Googol
7
Googol
Dont Ask
NSM
NSM
Yeehaw
Yeehaw
Googol

Output

Case #1: 1
Case #2: 0

In the first case, one possible solution is to start by using Dont Ask, and switch to NSM after query number 8. For the second case, you can use B9, and not need to make any switches.


Solutions

Strategy

We can solve it in one run through the list of queries, threading a list of servers with the run. The list of servers is updated deleting them as they appear in the query list. Whenever we find ourself with only one server we drop all the queries that are still possible. If we are left no queries that was the last server used , so we mark no changes, otherwise we keep processing the rest of the list with a fresh list of servers. To be noted, there are two base cases for the recursion. I hope someone can recode this.

Code

import Data.List

rcount :: Eq a => [a] -> [a] -> Integer
rcount names qs = count names qs where
	count _ [] = 0
	count [n] qs = let qs' = dropWhile (/= n) qs in
		if null qs' then 0 else 1 + count names qs'
	count ns (q:qs) = count (delete q ns) qs

parseCase [] = Nothing
parseCase (n:xs) = let 
	(ns,q:rs) = splitAt (read n) xs
	(qs,rs') = splitAt (read q) rs
	in Just ((ns,qs),rs')

type Names = [String]
type Queries = [String]

parseCases :: String -> [(Names,Queries)]
parseCases x = let (n:ts) = lines x in take (read n) . unfoldr parseCase $ ts

main = do
	ts <- parseCases `fmap` getContents
	flip mapM_ (zip [1..] ts) $ \(i,(ns,qs)) -> do
		putStr $ "Case #" ++ show i ++ ": "
		print $ rcount ns qs