-- ================================== -- Module name: TestCourt -- Project: Foo -- Copyright (C) 2007 Bartosz Wójcik -- Created on: 01.10.2007 -- Last update: 28.11.2007 -- Version: % {- This program is free software: you can redistribute it and/or modify it under the terms of the GNU General Public License as published by the Free Software Foundation, either version 3 of the License, or (at your option) any later version. This program is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General Public License for more details. You should have received a copy of the GNU General Public License along with this program. If not, see . -} -- ================================== module Main where -- Test module. import Court import Foo import FooMove import FooField import FooState import qualified Data.Map as Map import Data.List main = court 8 8 (True,PreventingOpponent2) (True,Watch2Ahead2) 1 -- main = court 8 8 (True,PreventingOpponent) (True,Watch2Ahead) 1 -- main = court 8 8 (True,PreventingOpponent) (True,CheckDist1PlyHash2) 1 {- -- testField = Map.insert (5,4) (True,[(a,b) | a<-[4..6] , b<-[3..5],(a,b) /= (5,4)]) $ Map.insert (4,4) (True,[(a,b) | a<-[3..5] , b<-[3..5],(a,b) /= (4,4)]) $ Map.insert (5,5) (True,[(a,b) | a<-[4..6] , b<-[4..6],(a,b) /= (5,5)]) (field 8 8) testField = myFold activateVertex (field 8 8) [(5,4),(4,4),(5,5),(6,5),(6,4)] testField2 = myFold activateVertex (field 8 8) [(1,3),(1,4)] testField3 = myFold activateVertex (field 8 8) [(4,4),(4,3),(4,2),(4,1)] myFold f v [] = v myFold f v (l:ls) = myFold f (f v l) ls activateVertex :: Graph -> Vertex -> Graph activateVertex graph (x,y) = Map.insert (x,y) (True,[(a,b) | a<-[(x-1)..(x+1)] , b<-[(y-1)..(y+1)],(a,b) /= (x,y)]) graph size = sizeMove 0 $ nextMove True (4,5) testField 8 8 0 size1 = sizeMove 0 $ nextMove True (4,5) (field 8 8) 8 8 0 move2Vs (LastPass vs _ _ _ _ _ _) = vs testMove = nextMove True (4,5) testField 8 8 0 testMoveX = nextMoveX True (4,5) testField 8 8 0 testMove3X = nextMoveX True (4,5) testField3 8 8 0 testMove3 = nextMove True (4,5) testField3 8 8 0 testMove2X = nextMoveX True (1,4) testField2 8 8 0 testMove2 = nextMove True (1,4) testField2 8 8 0 testMove1 = nextMove True (4,5) (field 8 8) 8 8 0 listMove (Pass m) = map move2Vs m -- !! nextPassX :: Bool -> Move -> [Move] nextPassX d (NextPass vs g fL fW True n i [] m mV)| even i && noPass = [LostHalfGoal vs g] | noPass = [HalfGoal vs g] | otherwise = [NextPass (v':vs) (rmEdge v v' g) fL fW (active v' g) (n+1) i [] (Map.insert (markEdge fW v v') True m) (Map.insertWith (+) v' 1 mV) |v' <- vertices v g] -- Map.insertWith (+) where v = head vs noPass = vertices v g == [] nextPassX d (NextPass vs g fL fW False n i [] _ _) | y == 0 && d || y == fL + 2 && not d = [Goal vs] | y == 0 && not d || y == fL + 2 && d = [LostGoal vs] | otherwise = [LastPass vs g fL fW n i [nextMoveX d v g fL fW (i+1)]] where y = snd v v = head vs nextMoveX :: Bool -> Vertex -> Graph -> Int -> Int -> Int -> Move nextMoveX d v g fL fW i = Pass (nNextMoveX d [NextPass [v] g fL fW True 1 i [] (Map.empty) (Map.insert v 1 Map.empty)]) nextAllPassesX :: Bool -> [Move] -> [Move] nextAllPassesX d ls = (concat $ map (nextPassX d) ls) nNextMoveX :: Bool -> [Move] -> [Move] nNextMoveX _ [] = [] nNextMoveX d ls = newFinishedMoves ++ nNextMoveX d (movesNotToPruneX newNotFinishedMoves ++ pruneMoves (Map.empty) (movesPossiblyToPruneX newNotFinishedMoves)) where newMoves = nextAllPassesX d ls newFinishedMoves = [m | m <- newMoves, not $ isNextPass m] newNotFinishedMoves = [m | m <- newMoves, isNextPass m] movesPossiblyToPruneX :: [Move] -> [Move] movesPossiblyToPruneX ls = [m | m <- ls, cycleInLastPassX m] movesNotToPruneX :: [Move] -> [Move] movesNotToPruneX ls = [m | m <- ls, not $ cycleInLastPassX m] cycleInLastPassX :: Move -> Bool cycleInLastPassX (NextPass vs _ _ _ _ _ _ _ _ mV) = Map.findWithDefault 0 (head vs) mV > 1 -} gr = field 8 8 tI0 = [(3,0),(4,0),(5,0)] tI1 = inactVertConnectedTo tI0 [] gr tI2 = inactVertConnectedTo tI1 tI0 gr tI3 = inactVertConnectedTo tI2 (tI0 ++ tI1) gr tI4 = inactVertConnectedTo tI3 (tI0 ++ tI1 ++ tI2) gr tI21 = nub $ fst $ tI21X tI21X = inactVertConnectedTo2 tI0 gr tI22 = nub $ fst $ tI22X tI22X = inactVertConnectedTo2 tI21 (snd $ tI21X) tI23 = nub $ fst $ tI23X tI23X = inactVertConnectedTo2 tI22 (snd $ tI22X) tI24 = nub $ fst $ tI24X tI24X = inactVertConnectedTo2 tI23 (snd $ tI23X) tD1 = distanceMap 1 False 8 8 gr tD2 = distanceMap 2 False 8 8 gr tD3 = distanceMap 3 False 8 8 gr tD n = distanceMap n False 8 8 gr dOfV v = distanceOfVertex v 3 (Map.unions [snd tD3,snd tD2,snd tD1]) False 8 8 gr