-- ================================== -- Module name: Foo -- Project: Foo -- Copyright (C) 2007 Bartosz Wójcik -- Created on: 01.10.2007 -- Last update: 07.04.2008 -- 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 Foo where import Data.List import Data.Bits import FooField import FooMove -- FooState has been developed as a brilliant idea, that unfortunatelly hasn't worked like expected. -- import FooState -- The program is supposed to play Pencil Soccer against human. -- The fileld is defined as a graph. The graph has edges everywhere there where there is a possibility to do a move. -- Once move is done, this affects directly the field - appropriate edge is removed -- (the idea is taken from Einstein - the space is not constant but changes affected by object and their moves). -- AlphaBeta extention helps to prune lot of moves without validatig them. Is useless in case moves are pruned in the way it has been finaly done here. -- #define AlphaBeta -- Playing machine constists of: -- playing algorithm -- Bool - direction, whether played towards goal (_,0) -- space of possible moves data PlayingMachine = Play PlayingAlgorithm Bool Move | MinValue -- Min value to use function max | MaxValue -- Max value to use function min -- List of algorithm can be completed. To do this you have to do 3 actions: -- 1. Add algorithm name to the typedefinition -- 2. Complete instance Ord for new algorithm (define how moves will be examined) -- 3. Describe algorithm in the documentation. data PlayingAlgorithm = GoAhead | GoBackWatchOpponent | GoAheadWatchOpponent | PreventingOpponent40 | PreventingOpponent50 | Watch2Ahead | Watch3Ahead deriving (Eq,Ord,Enum,Read,Show) moveOfMachine :: PlayingMachine -> Move moveOfMachine (Play _ _ m) = m -- Selects the best move out of given list of moves. bestMove :: [PlayingMachine] -> Move bestMove m = moveOfMachine $ foldr max MinValue m -- Selects the best move out of given list of moves. bestMoveWrapped :: [PlayingMachine] -> PlayingMachine bestMoveWrapped m = foldr max MinValue m -- Selects the worst move of the give tree of moves. This is in order to examine possible opponent moves. worstMove :: [PlayingMachine] -> PlayingMachine worstMove m = foldr min MaxValue m -- ============= #ifdef AlphaBeta -- ============= bestMoveAlphaBeta :: PlayingMachine -> [PlayingMachine] -> PlayingMachine bestMoveAlphaBeta alpha m = foldr (maxOrBetterThan alpha) MinValue m worstMoveAlphaBeta :: PlayingMachine -> [PlayingMachine] -> PlayingMachine worstMoveAlphaBeta alpha m = foldr (minOrWorseThan alpha) MaxValue m minOrWorseThan :: (Ord a) => a -> a -> a -> a minOrWorseThan alpha x y | alpha > y = y | otherwise = min x y maxOrBetterThan :: (Ord a) => a -> a -> a -> a maxOrBetterThan alpha x y | alpha < y = y | otherwise = max x y -- ====== #endif -- ====== instance Eq (PlayingMachine) where MinValue == MinValue = True MaxValue == MaxValue = True _ == _ = False -- ================================================= -- Instance of compare function is playing engine. -- Max over all defined moves gives the chosen move. -- ================================================= -- ================================ instance Ord (PlayingMachine) where -- ================================ -- There are compared moves of same generations (depths,plies). Generation doesn't access information about own predescor. -- If algorithm requires this information this has to be done in tricky way, not directly. -- Full description of MinValue and MaxValue constructors. -- -- =============================================================================================== -- compare MinValue _ = LT compare _ MinValue = GT compare MaxValue _ = GT compare _ MaxValue = LT -- =============================================================================================== -- -- Full description of UnfinishedMove constructor. -- -- It has been so described that such a move will never be selected. -- =============================================================================================== -- compare (Play _ _ (UnfinishedMove _ _)) (Play _ _ (UnfinishedMove _ _)) = EQ compare (Play _ _ (UnfinishedMove _ i)) (Play _ _ _) | odd i = GT | otherwise = LT compare (Play _ _ _) (Play _ _ (UnfinishedMove _ i)) | odd i = LT | otherwise = GT -- =============================================================================================== -- -- Full description of Goal constructor. -- -- =============================================================================================== -- compare (Play _ _ (Goal _)) (Play _ _ (Goal _)) = EQ compare (Play _ _ (Goal _)) (Play _ _ _) = GT compare (Play _ _ _) (Play _ _ (Goal _)) = LT -- =============================================================================================== -- -- Full description of HalfGoal constructor. -- -- =============================================================================================== -- compare (Play _ _ (HalfGoal _ _)) (Play _ _ (HalfGoal _ _)) = EQ compare (Play _ _ (HalfGoal _ _)) (Play _ _ _) = GT compare (Play _ _ _) (Play _ _ (HalfGoal _ _)) = LT -- =============================================================================================== -- -- Full description of LostGoal constructor. -- -- =============================================================================================== -- compare (Play _ d (LostGoal ((x,y):vs))) (Play _ _ (LostGoal ((x',y'):vs'))) = EQ compare (Play _ _ _) (Play _ _ (LostGoal _)) = GT compare (Play _ _ (LostGoal _)) (Play _ _ _) = LT -- =============================================================================================== -- -- Specialization for GoAheadWatchOpponent algorithm.-- -- =============================================================================================== -- compare p@(Play GoAheadWatchOpponent _ (LastPass _ _ _ _ _ 0 _)) p' = compareWatchingOpponent p p' compare p p'@(Play GoAheadWatchOpponent _ (LastPass _ _ _ _ _ 0 _)) = compareWatchingOpponent p p' -- =============================================================================================== -- -- =============================================================================================== -- compare p@(Play GoBackWatchOpponent _ (LastPass _ _ _ _ _ 0 _)) p' = compareWatchingOpponent p p' compare p p'@(Play GoBackWatchOpponent _ (LastPass _ _ _ _ _ 0 _)) = compareWatchingOpponent p p' -- =============================================================================================== -- -- Specialization for PreventingOpponent40 algorithm.-- -- =============================================================================================== -- compare (Play PreventingOpponent40 d m@(LastPass v g l w n i _)) p@(Play PreventingOpponent40 _ (LostHalfGoal _ _)) #ifdef AlphaBeta | i == 0 = compare (worstMoveAlphaBeta p $ mapMove (Play PreventingOpponent40 d ) $ nextMove d (head v) g l w 1) p #else | i == 0 = compare (worstMove $ mapSelectedMove (Play PreventingOpponent40 d ) PreventingOpponent40 $ nextMove d (head v) g l w 1) p #endif | otherwise = GT -- ================== -- compare p@(Play PreventingOpponent40 _ (LostHalfGoal _ _)) (Play PreventingOpponent40 d m@(LastPass v g l w n i _)) | i == 0 = compare p (worstMove $ mapSelectedMove (Play PreventingOpponent40 d ) PreventingOpponent40 $ nextMove d (head v) g l w 1) | otherwise = LT -- ================== -- compare (Play PreventingOpponent40 d (LastPass ((x,y):vs) g l w n i _)) (Play PreventingOpponent40 _ (LastPass ((x',y'):vs') g' _ _ n' i' _)) #ifdef AlphaBeta | i == 0 = compare (worstMoveAlphaBeta alpha $ mapMove (Play PreventingOpponent40 d ) $ nextMove d (x,y) g l w 1) (alpha) #else | i == 0 = compare (worstMove $ mapSelectedMove (Play PreventingOpponent40 d ) PreventingOpponent40 $ nextMove d (x,y) g l w 1) (worstMove $ mapSelectedMove (Play PreventingOpponent40 d ) PreventingOpponent40 $ nextMove d (x',y') g' l w 1) #endif | y > y' && not d = GT | y > y' && d = LT | y < y' && not d = LT | y < y' && d = GT | y == y' && cTM < cTM' = GT | y == y' && cTM > cTM' = LT | otherwise = EQ where cTM | yY < l' / 2 && d || yY >= l' / 2 && not d = abs $ fromIntegral w / 2 - fromIntegral x | yY >= l' / 2 && d || yY < l' / 2 && not d = fromIntegral w / 2 - abs (fromIntegral w / 2 - fromIntegral x) cTM' | yY' < l' / 2 && d || yY' >= l' / 2 && not d = abs $ fromIntegral w / 2 - fromIntegral x' | yY' >= l' / 2 && d || yY' < l' / 2 && not d = fromIntegral w / 2 - abs (fromIntegral w / 2 - fromIntegral x') l' = fromIntegral l yY' = fromIntegral y' yY = fromIntegral y #ifdef AlphaBeta alpha = worstMove $ mapMove (Play PreventingOpponent40 d ) $ nextMove d (x',y') g' l w 1 #endif -- =============================================================================================== -- -- Specialization for PreventingOpponent50 algorithm.-- -- =============================================================================================== -- compare (Play PreventingOpponent50 d m@(LastPass v g l w n i _)) p@(Play PreventingOpponent50 _ (LostHalfGoal _ _)) #ifndef AlphaBeta | i == 0 = compare (worstMove $ mapSelectedMove (Play PreventingOpponent50 d ) PreventingOpponent50 $ nextMove d (head v) g l w 1) p #endif | otherwise = GT -- ================== -- compare p@(Play PreventingOpponent50 _ (LostHalfGoal _ _)) (Play PreventingOpponent50 d m@(LastPass v g l w n i _)) | i == 0 = compare p (worstMove $ mapSelectedMove (Play PreventingOpponent50 d ) PreventingOpponent50 $ nextMove d (head v) g l w 1) | otherwise = LT -- ================== -- compare (Play PreventingOpponent50 d (LastPass ((x,y):vs) g l w n i _)) (Play PreventingOpponent50 _ (LastPass ((x',y'):vs') g' _ _ n' i' _)) #ifndef AlphaBeta | i == 0 = compare (worstMove $ mapSelectedMove (Play PreventingOpponent50 d ) PreventingOpponent50 $ nextMove d (x,y) g l w 1) (worstMove $ mapSelectedMove (Play PreventingOpponent50 d ) PreventingOpponent50 $ nextMove d (x',y') g' l w 1) #endif | y > y' && not d = GT | y > y' && d = LT | y < y' && not d = LT | y < y' && d = GT | y == y' && cTM < cTM' = GT | y == y' && cTM > cTM' = LT | otherwise = EQ where cTM | yY < l' / 2 && d || yY >= l' / 2 && not d = abs $ fromIntegral w / 2 - fromIntegral x | yY >= l' / 2 && d || yY < l' / 2 && not d = fromIntegral w / 2 - abs (fromIntegral w / 2 - fromIntegral x) cTM' | yY' < l' / 2 && d || yY' >= l' / 2 && not d = abs $ fromIntegral w / 2 - fromIntegral x' | yY' >= l' / 2 && d || yY' < l' / 2 && not d = fromIntegral w / 2 - abs (fromIntegral w / 2 - fromIntegral x') l' = fromIntegral l yY' = fromIntegral y' yY = fromIntegral y -- =============================================================================================== -- {- -- Specialization for GoBackLookForward algorithm.-- -- =============================================================================================== -- compare (Play GoBackLookForward d m@(LastPass v g l w n i _)) p@(Play GoBackLookForward _ (LostHalfGoal _ _)) | i == 0 = compare (worstMove $ mapMove (Play GoBackLookForward d ) $ nextMove d (head v) g l w 1) p | otherwise = GT -- ================== -- compare p@(Play GoBackLookForward _ (LostHalfGoal _ _)) (Play GoBackLookForward d m@(LastPass v g l w n i _)) | i == 0 = compare p (worstMove $ mapMove (Play GoBackLookForward d ) $ nextMove d (head v) g l w 1) | otherwise = LT -- ================== -- compare (Play GoBackLookForward d (LastPass ((x,y):vs) g l w n i _)) (Play GoBackLookForward _ (LastPass ((x',y'):vs') g' _ _ n' i' _)) | i == 0 = compare (worstMove $ mapMove (Play GoBackLookForward d ) $ nextMove d (x,y) g l w 1) (worstMove $ mapMove (Play GoBackLookForward d ) $ nextMove d (x',y') g' l w 1) | y > y' && not d = LT | y > y' && d = GT | y < y' && not d = GT | y < y' && d = LT | y == y' && cTM < cTM' = GT | y == y' && cTM > cTM' = LT | otherwise = EQ where cTM | yY < l' / 2 && d || yY >= l' / 2 && not d = abs $ fromIntegral w / 2 - fromIntegral x | yY >= l' / 2 && d || yY < l' / 2 && not d = fromIntegral w / 2 - abs (fromIntegral w / 2 - fromIntegral x) cTM' | yY' < l' / 2 && d || yY' >= l' / 2 && not d = abs $ fromIntegral w / 2 - fromIntegral x' | yY' >= l' / 2 && d || yY' < l' / 2 && not d = fromIntegral w / 2 - abs (fromIntegral w / 2 - fromIntegral x') l' = fromIntegral l yY' = fromIntegral y' yY = fromIntegral y -- =============================================================================================== -- -} -- Specialization for Watch2Ahead algorithm.-- -- =============================================================================================== -- compare (Play Watch2Ahead d m@(LastPass v g l w n i _)) p@(Play Watch2Ahead _ (LostHalfGoal _ _)) #ifdef AlphaBeta | i == 0 = compare (worstMoveAlphaBeta p $ mapMove (Play Watch2Ahead d ) $ nextMove d (head v) g l w 1) p | i == 1 = compare (bestMoveAlphaBeta p $ mapMove (Play Watch2Ahead d ) $ nextMove d (head v) g l w 2) p #else | i == 0 = compare (worstMove $ mapSelectedMove (Play Watch2Ahead d ) Watch2Ahead $ nextMove d (head v) g l w 1) p | i == 1 = compare (bestMoveWrapped $ mapSelectedMove (Play Watch2Ahead d ) Watch2Ahead $ nextMove d (head v) g l w 2) p #endif | otherwise = GT -- ================== -- compare p@(Play Watch2Ahead _ (LostHalfGoal _ _)) (Play Watch2Ahead d m@(LastPass v g l w n i _)) | i == 0 = compare p (worstMove $ mapSelectedMove (Play Watch2Ahead d ) Watch2Ahead $ nextMove d (head v) g l w 1) | i == 1 = compare p (bestMoveWrapped $ mapSelectedMove (Play Watch2Ahead d ) Watch2Ahead $ nextMove d (head v) g l w 2) | otherwise = LT -- ================== -- compare (Play Watch2Ahead d (LastPass ((x,y):vs) g l w n i _)) (Play Watch2Ahead _ (LastPass ((x',y'):vs') g' _ _ n' i' _)) #ifdef AlphaBeta | i == 0 = compare (worstMoveAlphaBeta alpha $ mapMove (Play Watch2Ahead d ) $ nextMove d (x,y) g l w 1) (alpha) | i == 1 = compare (bestMoveAlphaBeta beta $ mapMove (Play Watch2Ahead d ) $ nextMove d (x,y) g l w 2) (beta) #else | i == 0 = compare (worstMove $ mapSelectedMove (Play Watch2Ahead d ) Watch2Ahead $ nextMove d (x,y) g l w 1) (worstMove $ mapSelectedMove (Play Watch2Ahead d ) Watch2Ahead $ nextMove d (x',y') g' l w 1) | i == 1 = compare (bestMoveWrapped $ mapSelectedMove (Play Watch2Ahead d ) Watch2Ahead $ nextMove d (x,y) g l w 2) (bestMoveWrapped $ mapSelectedMove (Play Watch2Ahead d ) Watch2Ahead $ nextMove d (x',y') g' l w 2) #endif | y > y' && not d = GT | y > y' && d = LT | y < y' && not d = LT | y < y' && d = GT | y == y' && cTM < cTM' = GT | y == y' && cTM > cTM' = LT | otherwise = EQ where cTM | yY < l' / 2 && d || yY >= l' / 2 && not d = abs $ fromIntegral w / 2 - fromIntegral x | yY >= l' / 2 && d || yY < l' / 2 && not d = fromIntegral w / 2 - abs (fromIntegral w / 2 - fromIntegral x) cTM' | yY' < l' / 2 && d || yY' >= l' / 2 && not d = abs $ fromIntegral w / 2 - fromIntegral x' | yY' >= l' / 2 && d || yY' < l' / 2 && not d = fromIntegral w / 2 - abs (fromIntegral w / 2 - fromIntegral x') l' = fromIntegral l yY' = fromIntegral y' yY = fromIntegral y #ifdef AlphaBeta alpha = worstMove $ mapMove (Play Watch2Ahead d ) $ nextMove d (x',y') g' l w 1 beta = bestMoveWrapped $ mapMove (Play Watch2Ahead d ) $ nextMove d (x',y') g' l w 2 #endif -- =============================================================================================== -- -- Specialization for Watch3Ahead algorithm.-- -- =============================================================================================== -- compare (Play Watch3Ahead d m@(LastPass v g l w n i _)) p@(Play Watch3Ahead _ (LostHalfGoal _ _)) #ifndef AlphaBeta | i == 0 = compare (worstMove $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (head v) g l w 1) p | i == 1 = compare (bestMoveWrapped $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (head v) g l w 2) p | i == 2 = compare (worstMove $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (head v) g l w 3) p #endif | otherwise = GT -- ================== -- compare p@(Play Watch3Ahead _ (LostHalfGoal _ _)) (Play Watch3Ahead d m@(LastPass v g l w n i _)) | i == 0 = compare p (worstMove $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (head v) g l w 1) | i == 1 = compare p (bestMoveWrapped $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (head v) g l w 2) | i == 2 = compare p (worstMove $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (head v) g l w 3) | otherwise = LT -- ================== -- compare (Play Watch3Ahead d (LastPass ((x,y):vs) g l w n i _)) (Play Watch3Ahead _ (LastPass ((x',y'):vs') g' _ _ n' i' _)) #ifndef AlphaBeta | i == 0 = compare (worstMove $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (x,y) g l w 1) (worstMove $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (x',y') g' l w 1) | i == 1 = compare (bestMoveWrapped $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (x,y) g l w 2) (bestMoveWrapped $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (x',y') g' l w 2) | i == 2 = compare (worstMove $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (x,y) g l w 3) (worstMove $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (x',y') g' l w 3) #endif | y > y' && not d = GT | y > y' && d = LT | y < y' && not d = LT | y < y' && d = GT | y == y' && cTM < cTM' = GT | y == y' && cTM > cTM' = LT | otherwise = EQ where cTM | yY < l' / 2 && d || yY >= l' / 2 && not d = abs $ fromIntegral w / 2 - fromIntegral x | yY >= l' / 2 && d || yY < l' / 2 && not d = fromIntegral w / 2 - abs (fromIntegral w / 2 - fromIntegral x) cTM' | yY' < l' / 2 && d || yY' >= l' / 2 && not d = abs $ fromIntegral w / 2 - fromIntegral x' | yY' >= l' / 2 && d || yY' < l' / 2 && not d = fromIntegral w / 2 - abs (fromIntegral w / 2 - fromIntegral x') l' = fromIntegral l yY' = fromIntegral y' yY = fromIntegral y #ifdef AlphaBeta alpha = worstMove $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (x',y') g' l w 1 beta = bestMoveWrapped $ mapSelectedMove (Play Watch3Ahead d ) Watch3Ahead $ nextMove d (x',y') g' l w 2 #endif -- =============================================================================================== -- -- Basic description of LostHalfGoal constructor. -- -- =============================================================================================== -- compare (Play _ _ (LostHalfGoal _ _)) (Play _ _ (LostHalfGoal _ _)) = EQ compare (Play _ _ (LastPass _ _ _ _ _ i _)) (Play _ _ (LostHalfGoal _ _)) = GT compare (Play _ _ (LostHalfGoal _ _)) (Play _ _ (LastPass _ _ _ _ _ i' _)) = LT -- =============================================================================================== -- compare (Play a d (LastPass ((x,y):vs) g l w n i m)) (Play a' d' (LastPass ((x',y'):vs') g' l' w' n' i' m')) | y > y' && not d = GT | y > y' && d = LT | y < y' && not d = LT | y < y' && d = GT | y == y' && cTM < cTM' = GT | y == y' && cTM > cTM' = LT | y == y' && cTM == cTM' && n > n' = GT | y == y' && cTM == cTM' && n < n' = LT | y == y' && cTM == cTM' && n == n' = EQ where cTM = abs $ fromIntegral w / 2 - fromIntegral x cTM' = abs $ fromIntegral w / 2 - fromIntegral x' compare _ _ = EQ -- just in case -- ==================================== -- end of instance Ord (PlayingMachine) -- ==================================== -- ---------------------------------------------------------------------- -- Idea is following. -- If opponent can score a goal after current move this move is value 0. -- If move is LostHalfGoal its value is 1. -- If move is Goal, its value is VERY BIG. -- Otherwise value of the move is algorithm dependent; higher, closer to opponent goal move finishes. -- Then compare moves. compareWatchingOpponent :: PlayingMachine -> PlayingMachine -> Ordering compareWatchingOpponent p1 p2 | p1' == 0 = LT | p2' == 0 = GT | otherwise = compare (valueOfMove p1) (valueOfMove p2) where p1' = valueOfMove $ nextWorstMove p1 p2' = valueOfMove $ nextWorstMove p2 -- Select worst (for us) opponent answer. nextWorstMove :: PlayingMachine -> PlayingMachine nextWorstMove (Play a d (LastPass ((x,y):vs) g l w _ i _)) = worstMove $ mapMove (Play a d ) $ nextMove d (x,y) g l w (i + 1) nextWorstMove p = p -- Give value of the move. valueOfMove :: PlayingMachine -> Int -- Different algorithms use different ways of scoring. valueOfMove (Play GoBackWatchOpponent d (LastPass ((x,y):vs) _ l w n _ _)) | d = y*l + w - (round $ abs $ fromIntegral w / 2 - fromIntegral x) + n | otherwise = (l-y)*l + w - (round $ abs $ fromIntegral w / 2 - fromIntegral x) + n valueOfMove (Play _ d (LastPass ((x,y):vs) _ l w n _ _)) | d = (l-y)*l + w - (round $ abs $ fromIntegral w / 2 - fromIntegral x) + n | otherwise = y*l + w - (round $ abs $ fromIntegral w / 2 - fromIntegral x) + n valueOfMove (Play _ _ (LostGoal _)) = 0 valueOfMove (Play _ _ (LostHalfGoal _ _)) = 1 valueOfMove (Play _ _ (HalfGoal _ _)) = 1000 valueOfMove _ = 0 -- Maps given function on selected leaves of tree of moves. -- It select moves that finish match and given number of the others. -- This function has very important meaning for the efficiency and speed of playing machines. -- It is a main hash function. It bases on observations, that: -- Longer moves diminish space of moves, so selecting longer moves leads to faster playing machines -- When many moves finish in the same vetrex, longer ones are usually not worse than shorter. -- Short moves shoudn't be pruned if they are Goal, LostGoal, HalfGoal nad LostHalfGoal. Otherwise they might be omitted by plaiyng machine. -- Balance between speed when not much moves are selected to next ply and risk that some important moves will be omitted has been selected on experimental way. -- It is not ensured that all possible end vertices are represented by at least 1 move. This would be strong improvement of this function -- although would lead to additional costs that then would need to be checed if they are acceptable. mapSelectedMove f PreventingOpponent40 m = takeLastMove 40 0 $ mapMove f m mapSelectedMove f PreventingOpponent50 m = takeLastMove 50 0 $ mapMove f m mapSelectedMove f Watch2Ahead m = takeLastMove 30 0 $ mapMove f m mapSelectedMove f Watch3Ahead m = takeLastMove 18 0 $ mapMove f m mapSelectedMove f _ m = takeLastMove 1000 0 $ mapMove f m -- Takes from the list of moves (wrapped into PlayingMachine) one move each type that finishes match (assuming they are always firsts elements of the list) -- and 'n' next elements (they are supposed to be LastPass) takeLastMove :: Int -> Int -> [PlayingMachine] -> [PlayingMachine] takeLastMove n bits lp@((Play _ _ (LastPass _ _ _ _ _ _ _)):ls) = take n lp takeLastMove n bits (p@(Play _ _ (Goal _)):lp) | testBit bits 0 = takeLastMove n bits lp | otherwise = p : takeLastMove n (setBit bits 0) lp takeLastMove n bits (p@(Play _ _ (HalfGoal _ _)):lp) | testBit bits 1 = takeLastMove n bits lp | otherwise = p : takeLastMove n (setBit bits 1) lp takeLastMove n bits (p@(Play _ _ (LostGoal _)):lp) | testBit bits 2 = takeLastMove n bits lp | otherwise = p : takeLastMove n (setBit bits 2) lp takeLastMove n bits (p@(Play _ _ (LostHalfGoal _ _)):lp) | testBit bits 3 = takeLastMove n bits lp | otherwise = p : takeLastMove n (setBit bits 3) lp takeLastMove n bits (p:lp) = p : takeLastMove n bits lp takeLastMove n _ [] = []