Google Code Jam/Train Timetable

From HaskellWiki
Jump to navigation Jump to search

Problem

A train line has two stations on it, A and B. Trains can take trips from A to B or from B to A multiple times during a day. When a train arrives at B from A (or arrives at A from B), it needs a certain amount of time before it is ready to take the return journey - this is the turnaround time. For example, if a train arrives at 12:00 and the turnaround time is 0 minutes, it can leave immediately, at 12:00.

A train timetable specifies departure and arrival time of all trips between A and B. The train company needs to know how many trains have to start the day at A and B in order to make the timetable work: whenever a train is supposed to leave A or B, there must actually be one there ready to go. There are passing sections on the track, so trains don't necessarily arrive in the same order that they leave. Trains may not travel on trips that do not appear on the schedule.

Input

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

Each case contains a number of lines. The first line is the turnaround time, T, in minutes. The next line has two numbers on it, NA and NB. NA is the number of trips from A to B, and NB is the number of trips from B to A. Then there are NA lines giving the details of the trips from A to B.

Each line contains two fields, giving the HH:MM departure and arrival time for that trip. The departure time for each trip will be earlier than the arrival time. All arrivals and departures occur on the same day. The trips may appear in any order - they are not necessarily sorted by time. The hour and minute values are both two digits, zero-padded, and are on a 24-hour clock (00:00 through 23:59).

After these NA lines, there are NB lines giving the departure and arrival times for the trips from B to A.

Output

For each test case, output one line containing "Case #x: " followed by the number of trains that must start at A and the number of trains that must start at B.

Limits

1 ≤ N ≤ 100

Small dataset

0 ≤ NA, NB ≤ 20

0 ≤ T ≤ 5

Large dataset

0 ≤ NA, NB ≤ 100

0 ≤ T ≤ 60

Sample

Input

2
5
3 2
09:00 12:00
10:00 13:00
11:00 12:30
12:02 15:00
09:00 10:30
2
2 0
09:00 09:01
12:00 12:02

Output

Case #1: 2 2
Case #2: 2 0


Solutions

Strategy

The program produces a list of trains. A train is added whenever there is no train ready to run, in the right place for a journey. When there is a suitable train it is used. The journeys are pooled and sorted by ascending starting time. The trains are stateful and carry around the next place they will be ready to leave with the minimum time. Minimum leaving time is last arrival time plus turning time. Journeys are examinated one by one and used trains updated.

Code

import Data.List

data City = A | B deriving (Eq,Ord,Show)

type Time = Int

-- | A point in time and space
data TP   = TP   {at :: Time , pos :: City} deriving (Ord,Eq)
data Tratta = Tratta { from :: TP, to :: TP} deriving (Ord,Eq)
-- | the name of the city the train started at beginning and the TP it will be ready next
data Train  = Train  {started :: City , doing ::TP} deriving Eq

-- | test for a Train if it can do a Tratta
ready :: Tratta -> Train -> Bool
ready (Tratta from _) (Train _ doing) = pos from == pos doing && at doing <= at from

-- | update a list of Train , a new train is added if no other can be used
busy :: [Train] -> Tratta -> [Train]
busy ts x = case find (ready x) ts of 
		Nothing -> Train (pos . from $ x) (to x)  : ts
		Just t 	-> Train (started t) (to x)       : delete t ts

-- | creates the trains from a list of Tratta to be done
trains :: [Tratta] -> [Train]
trains = foldl' busy []

type Versus = (City,City)

parseTratta :: Int  -> Versus -> String -> Tratta
parseTratta ta (a,b) x = let 
	[t1,t2] = map toMinute . words $ x
	toMinute (h1:h2:':':m1:[m2]) = read [h1,h2] * 60 + read [m1,m2]
	in Tratta (TP t1 a) (TP (t2 + ta) b)

parseCase [] = Nothing
parseCase (ta:m:xs) = let 
	[t1,t2] = map read . words $ m
	(das,xs') = splitAt t1 xs
	(dbs,xs'') = splitAt t2 xs'
	pta = parseTratta (read ta)
	in Just (sort $ map (pta (A,B)) das ++ map (pta (B,A)) dbs,xs'')

parseCases :: String -> [[Tratta]]
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) -> do
		putStr $ "Case #" ++ show i ++ ": "
		let (as,bs) = partition ((==A). started) $ trains ns 
		putStrLn $ (show (length as) ++ " " ++ show (length bs))