module Diplomacy.OrderResolution (
    Resolved
  , SomeResolved(..)
  , withSomeResolved
  , FailureReason(..)
  , Resolution
  , typicalResolution
  , retreatResolution
  , adjustResolution
  , typicalChange
  , ConvoyRoutes(..)
  , ConvoyRoute
  , convoyRoutes
  , successfulConvoyRoutes
  ) where
import Data.Typeable
import Data.Ord
import Data.List
import Data.Monoid
import Data.Either
import Data.Maybe
import Data.AtLeast
import Data.TypeNat.Nat
import Data.TypeNat.Vect
import Data.Functor.Identity
import Data.Traversable (sequenceA)
import qualified Data.Map as M
import qualified Data.Set as S
import Data.MapUtil
import Control.Monad
import Control.Applicative
import Diplomacy.GreatPower
import Diplomacy.Aligned
import Diplomacy.Unit
import Diplomacy.Phase
import Diplomacy.Subject
import Diplomacy.OrderType
import Diplomacy.OrderObject
import Diplomacy.Order
import Diplomacy.Province
import Diplomacy.Zone
import Diplomacy.Subject
type Resolution phase = M.Map Zone (Aligned Unit, SomeResolved OrderObject phase)
type TypicalResolutionInput
    = M.Map Zone (Aligned Unit, Either (SomeResolved OrderObject Typical) (SomeOrderObject Typical))
type TypicalResolutionOutput
    = M.Map Zone (Aligned Unit, Either (SomeResolved OrderObject Typical) (SomeResolved OrderObject Typical))
preserveAssumptions :: TypicalResolutionOutput -> TypicalResolutionInput
preserveAssumptions = M.map makeInput
  where
    makeInput (aunit, x) = case x of
        Left y -> (aunit, Left y)
        Right (SomeResolved (x, _)) -> (aunit, Right $ SomeOrderObject x)
dropAssumptionTags :: TypicalResolutionOutput -> Resolution Typical
dropAssumptionTags = M.map dropTag
  where
    dropTag (aunit, x) = case x of
        Left y -> (aunit, y)
        Right y -> (aunit, y)
typicalResolutionAssuming
    :: TypicalResolutionInput
    -> TypicalResolutionOutput
typicalResolutionAssuming input =
    let resolution = M.mapWithKey (resolveOne resolution) input
    in  resolution
  where
    resolveOne
        :: TypicalResolutionOutput
        -> Zone
        -> (Aligned Unit, Either (SomeResolved OrderObject Typical) (SomeOrderObject Typical))
        -> (Aligned Unit, Either (SomeResolved OrderObject Typical) (SomeResolved OrderObject Typical))
    resolveOne resolution zone (aunit, x) = case x of
        Left y -> (aunit, Left y)
        Right y -> (aunit, Right (resolveSomeOrderTypical resolution zone (aunit, y)))
assumeNoOrder
    :: Zone
    -> TypicalResolutionInput
    -> TypicalResolutionInput
assumeNoOrder = M.alter (const Nothing)
assumeSucceeds
    :: Zone
    -> TypicalResolutionInput
    -> TypicalResolutionInput
assumeSucceeds zone = M.adjust makeSucceeds zone
  where
    makeSucceeds
        :: (Aligned Unit, Either (SomeResolved OrderObject Typical) (SomeOrderObject Typical))
        -> (Aligned Unit, Either (SomeResolved OrderObject Typical) (SomeOrderObject Typical))
    makeSucceeds (aunit, x) = case x of
        Left (SomeResolved (x, _)) -> (aunit, Left (SomeResolved (x, Nothing)))
        Right (SomeOrderObject x) -> (aunit, Left (SomeResolved (x, Nothing)))
noAssumptions
    :: M.Map Zone (Aligned Unit, SomeOrderObject Typical)
    -> TypicalResolutionInput
noAssumptions = M.map (\(x, y) -> (x, Right y))
data RequiresConvoy
    = RequiresConvoy
    | DoesNotRequireConvoy
    deriving (Show)
type ConvoyRoute = [(Zone, Maybe (Aligned Subject))]
data ConvoyRoutes = ConvoyRoutes {
      convoyRoutesParadox :: [ConvoyRoute]
    , convoyRoutesNonParadox :: [ConvoyRoute]
    }
    deriving (Show)
moveRequiresConvoy :: ProvinceTarget -> ProvinceTarget -> Bool
moveRequiresConvoy ptFrom ptTo = not (isSameOrAdjacent movingTo movingFrom)
  where
    movingTo = ptProvince ptFrom
    movingFrom = ptProvince ptTo
isConvoyMoveWithNoConvoyRoute :: MoveClassification -> Bool
isConvoyMoveWithNoConvoyRoute thisClassification = case thisClassification of
    NotHold RequiresConvoy theseConvoyRoutes _ _ -> null (successfulConvoyRoutes theseConvoyRoutes)
    _ -> False
type Supports = [Aligned Subject]
support :: TypicalResolutionOutput -> Subject -> ProvinceTarget -> Supports
support resolution subject goingTo = M.foldWithKey selector [] (dropAssumptionTags resolution)
  where
    selector
        :: Zone
        -> (Aligned Unit, SomeResolved OrderObject Typical)
        -> [Aligned Subject]
        -> [Aligned Subject]
    selector zone (aunit, SomeResolved (object, thisResolution)) b = case object of
        SupportObject supportSubject supportTo ->
            if    supportSubject /= subject
               || supportTo /= goingTo
            then b
            else case thisResolution of
                Nothing -> align (alignedThing aunit, zoneProvinceTarget zone) (alignedGreatPower aunit) : b
                _ -> b
        _ -> b
foreignSupport
    :: TypicalResolutionOutput
    -> GreatPower
    -> Subject
    -> ProvinceTarget
    -> Supports
foreignSupport resolution power subject goingTo =
    filter isForeignSupport (support resolution subject goingTo)
  where
    isForeignSupport asubj = alignedGreatPower asubj /= power
isMoveDislodgedFromAttackedZone
    :: TypicalResolutionOutput
    -> Zone
    -> (Aligned Unit, OrderObject Typical Move)
    -> Bool
isMoveDislodgedFromAttackedZone resolution zoneFrom (aunit, object) = case thisClassification of
    Hold _ -> False
    NotHold _ _ _ thisIncumbant -> case thisIncumbant of
        
        
        
        
        
        
        
        
        ComplementaryMove WouldSucceed asubj target ->
            let opposingSupports = foreignSupport resolution (alignedGreatPower aunit) (alignedThing asubj) target
                thisSupports = support resolution (alignedThing aunit, zoneProvinceTarget zoneFrom) (zoneProvinceTarget zoneTo)
            in     alignedGreatPower aunit /= alignedGreatPower asubj
                && length opposingSupports > length thisSupports
        _ -> False
  where
    thisClassification = classify resolution zoneFrom (aunit, object)
    zoneTo = Zone (moveTarget object)
type CompetingMoves = [(Aligned Subject, ProvinceTarget)]
competingMoves
    :: TypicalResolutionOutput
    -> Zone
    -> Zone
    -> CompetingMoves
competingMoves resolution zoneFrom zoneTo = M.foldWithKey selector [] (dropAssumptionTags resolution')
  where
    
    
    
    
    
    
    
    
    
    
    
    
    resolution' = M.delete zoneFrom resolution
    selector
        :: Zone
        -> (Aligned Unit, SomeResolved OrderObject Typical)
        -> CompetingMoves
        -> CompetingMoves
    selector zone (aunit, SomeResolved (object, _)) b = case object of
        MoveObject movingTo ->
            if    zone == zoneFrom
               || Zone movingTo /= zoneTo
               || isConvoyMoveWithNoConvoyRoute thisClassification
               
               
               || isMoveDislodgedFromAttackedZone resolution' zone (aunit, object)
            then b
            else let subject = (alignedThing aunit, zoneProvinceTarget zone)
                     asubject = align subject (alignedGreatPower aunit)
                 in  (asubject, movingTo) : b
          where
            thisClassification = classify resolution' zone (aunit, object)
        _ -> b
data WouldSucceed
    = WouldSucceed
    | WouldNotSucceed
    deriving (Show)
data Incumbant
    = ComplementaryMove WouldSucceed (Aligned Subject) ProvinceTarget
    
    
    
    
    
    
    
    
    
    
    
    | ReturningMove (Aligned Subject) ProvinceTarget
    
    | Stationary (Aligned Subject)
    
    
    
    
    
    
    
    | NoIncumbant
    deriving (Show)
incumbant
    :: TypicalResolutionOutput
    -> Zone
    -> Zone
    -> Incumbant
incumbant resolution zoneFrom zoneTo = case lookupWithKey zoneTo resolution' of
    
    
    
    Just (zoneTo', (aunit, SomeResolved (object, res))) -> case object of
        MoveObject pt ->
            if Zone pt == zoneTo
            then Stationary (align (alignedThing aunit, zoneProvinceTarget zoneTo') (alignedGreatPower aunit))
            else if Zone pt == zoneFrom
            
            
            
            
            then case res of
                Nothing -> ComplementaryMove WouldSucceed (align (alignedThing aunit, zoneProvinceTarget zoneTo') (alignedGreatPower aunit)) pt
                Just _ -> ComplementaryMove WouldNotSucceed (align (alignedThing aunit, zoneProvinceTarget zoneTo') (alignedGreatPower aunit)) pt
            else case res of
                Nothing -> NoIncumbant
                Just _ -> ReturningMove (align (alignedThing aunit, pt) (alignedGreatPower aunit)) (zoneProvinceTarget zoneTo')
        _ -> Stationary (align (alignedThing aunit, zoneProvinceTarget zoneTo') (alignedGreatPower aunit))
    _ -> NoIncumbant
  where
    resolutionThisSucceeds = typicalResolutionAssuming (assumeSucceeds zoneFrom (preserveAssumptions resolution))
    resolution' = dropAssumptionTags resolutionThisSucceeds
data MoveClassification
    = Hold CompetingMoves
    | NotHold RequiresConvoy ConvoyRoutes CompetingMoves Incumbant
    deriving (Show)
classify
    :: TypicalResolutionOutput
    -> Zone
    -> (Aligned Unit, OrderObject Typical Move)
    -> MoveClassification
classify resolution zone (aunit, MoveObject movingTo) =
    if zone == Zone movingTo
    then Hold (holdCompetingMoves resolution zone (Zone movingTo))
    else let power = alignedGreatPower aunit
             unit = alignedThing aunit
             pt = zoneProvinceTarget zone
             asubject = align (unit, pt) power
         in  classifyNonHold resolution asubject movingTo
  where
    
    
    
    
    
    holdCompetingMoves
        :: TypicalResolutionOutput
        -> Zone
        -> Zone
        -> CompetingMoves
    holdCompetingMoves resolution zoneFrom zoneTo = theseCompetingMoves
      where
        theseCompetingMoves = competingMoves resolution zoneFrom zoneTo
    classifyNonHold
        :: TypicalResolutionOutput
        -> Aligned Subject
        -> ProvinceTarget
        -> MoveClassification
    classifyNonHold resolution asubject pt =
        NotHold thisRequiresConvoy theseConvoyRoutes theseCompetingMoves thisIncumbant
      where
        thisRequiresConvoy =
            if moveRequiresConvoy (zoneProvinceTarget zoneFrom) (zoneProvinceTarget zoneTo)
            then RequiresConvoy
            else DoesNotRequireConvoy
        theseConvoyRoutes = convoyRoutes (dropAssumptionTags resolution) (alignedThing asubject) pt 
        
        
        
        
        
        
        theseCompetingMoves = competingMoves resolution zoneFrom zoneTo
        thisIncumbant = incumbant resolution zoneFrom zoneTo
        zoneFrom = Zone (subjectProvinceTarget (alignedThing asubject))
        zoneTo = Zone pt
rawConvoyRoutes
    :: Resolution Typical
    -> Subject
    -> ProvinceTarget
    -> [ConvoyRoute]
rawConvoyRoutes resolution (unit, ptFrom) ptTo =
    (fmap . fmap) tagWithChange routes
  where
    
    
    
    routes :: [[Province]]
    routes = fmap (\(_, y, ys) -> y : init ys) discoveredPaths
    discoveredPaths :: [((), Province, [Province])]
    discoveredPaths = paths ((flip S.member) viableConvoyProvinces) (\p -> if p == ptProvince ptTo then Just () else Nothing) [ptProvince ptFrom]
    tagWithChange :: Province -> (Zone, Maybe (Aligned Subject))
    tagWithChange pr = (Zone (Normal pr), typicalChange resolution (Zone (Normal pr)))
    viableConvoyProvinces :: S.Set Province
    viableConvoyProvinces = S.fromList (fmap (ptProvince . zoneProvinceTarget) (M.keys (M.filter isViableConvoy resolution)))
    isViableConvoy
        :: (Aligned Unit, SomeResolved OrderObject Typical)
        -> Bool
    isViableConvoy (aunit, SomeResolved (object, _)) = case object of
        ConvoyObject (unit', convoyingFrom) convoyingTo ->
               unit == unit'
            && ptFrom == convoyingFrom
            && ptTo == convoyingTo
        _ -> False
convoyRoutes
    :: Resolution Typical
    -> Subject
    -> ProvinceTarget
    -> ConvoyRoutes
convoyRoutes resolution subject pt =
    let routes = rawConvoyRoutes resolution subject pt
        (paradox, nonParadox) = partition (isParadoxRoute resolution pt . fmap fst) routes
    in  ConvoyRoutes paradox nonParadox
isVoidConvoy
    :: Resolution Typical
    -> Subject
    -> ProvinceTarget
    -> Bool
isVoidConvoy resolution subject convoyingTo = case M.lookup convoyingFrom resolution of
    Nothing -> True
    Just (aunit, SomeResolved (MoveObject movingTo, _)) ->
           convoyingUnit /= alignedThing aunit
        || convoyingTo /= movingTo
  where
    convoyingFrom :: Zone
    convoyingFrom = Zone (snd subject)
    convoyingUnit :: Unit
    convoyingUnit = fst subject
isParadoxRoute
    :: Resolution Typical
    -> ProvinceTarget 
    -> [Zone] 
    -> Bool
isParadoxRoute resolution destination convoyZones = case M.lookup (Zone destination) resolution of
    
    
    
    
    Just (_, SomeResolved (SupportObject _ supportTarget, _)) ->
        if any ((==) (Zone supportTarget)) convoyZones
        
        
        then True
        
        
        
        
        
        else case M.lookup (Zone supportTarget) resolution of
            
            
            
            
            
            
            Just (_, SomeResolved (ConvoyObject convoySubject convoyTarget, _)) ->
                let nextRoutes = rawConvoyRoutes resolution convoySubject convoyTarget
                    (maybeParadoxical, others) = partition (any ((==) (Zone supportTarget)) . fmap fst) nextRoutes
                    successfulOthers = filter isSuccessfulConvoyRoute others
                in    not (isVoidConvoy resolution convoySubject convoyTarget)
                   && null successfulOthers
                   
                   
                   && isParadoxRoute (M.delete (Zone destination) resolution) convoyTarget convoyZones
            _ -> False
    _ -> False
paradoxInducingSupport
    :: TypicalResolutionOutput
    -> Zone 
    -> Maybe (OrderObject Typical Support)
paradoxInducingSupport resolution zone =
    case M.lookup zone (dropAssumptionTags resolution) of
        Just (aunit, SomeResolved (s@(SupportObject _ _), _)) -> Just s
        _ -> Nothing
paradoxInducingConvoyZone
    :: TypicalResolutionOutput
    -> Zone 
    -> Maybe Zone
paradoxInducingConvoyZone resolution =
    fmap (Zone . supportTarget) . paradoxInducingSupport resolution
successfulConvoyRoutes :: ConvoyRoutes -> [ConvoyRoute]
successfulConvoyRoutes = filter isSuccessfulConvoyRoute . convoyRoutesNonParadox
isSuccessfulConvoyRoute :: ConvoyRoute -> Bool
isSuccessfulConvoyRoute = all (isNothing . snd)
resolveSomeOrderTypical
    :: TypicalResolutionOutput
    -> Zone
    -> (Aligned Unit, SomeOrderObject Typical)
    -> SomeResolved OrderObject Typical
resolveSomeOrderTypical resolution zone (aunit, SomeOrderObject object) =
    let thisResolution :: SomeResolved OrderObject Typical
        thisResolution = case object of
            MoveObject _ -> SomeResolved (object, resolveMove object)
            SupportObject _ _ -> SomeResolved (object, resolveSupport object)
            ConvoyObject _ _ -> SomeResolved (object, resolveConvoy object)
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        resolveMove :: OrderObject Typical Move -> Maybe (FailureReason Typical Move)
        resolveMove moveObject = case classify resolution zone (aunit, moveObject) of
            
            
            Hold theseCompetingMoves -> case dominator of
                Nothing -> Nothing
                Just (x, ss) ->
                    if length ss <= length thisSupports
                    then Nothing
                    
                    else Just (MoveOverpowered (AtLeast (VCons x VNil) []))
              where
                dominator = case sortedOpposingSupports of
                    [] -> Nothing
                    [x] -> Just x
                    x : y : _ -> if length (snd x) > length (snd y)
                                 then Just x
                                 else Nothing
                sortedOpposingSupports = sortBy comparator opposingSupports
                comparator :: (Aligned Subject, Supports) -> (Aligned Subject, Supports) -> Ordering
                comparator (_, xs) (_, ys) = Down (length xs) `compare` Down (length ys)
                opposingSupports :: [(Aligned Subject, Supports)]
                opposingSupports = fmap (\x -> (fst x, calculateOpposingSupports x)) foreignCompetingMoves
                calculateOpposingSupports :: (Aligned Subject, ProvinceTarget) -> Supports
                calculateOpposingSupports (asubj, pt) = foreignSupport resolution (alignedGreatPower aunit) (alignedThing asubj) pt
                foreignCompetingMoves :: CompetingMoves
                foreignCompetingMoves = filter (\(asubj, _) -> alignedGreatPower asubj /= alignedGreatPower aunit) theseCompetingMoves
                thisSupports :: Supports
                thisSupports = support resolution (alignedThing aunit, zoneProvinceTarget zone) (zoneProvinceTarget zone)
            
            
            
            
            
            NotHold requiresConvoy theseConvoyRoutes theseCompetingMoves thisIncumbant ->
                case (checkConvoy, checkCompeting, checkIncumbant) of
                    
                    
                    (Nothing, x@(Just (MoveBounced _)), y@(Just (MoveOverpowered _))) -> y
                    (Nothing, x@(Just (MoveBounced _)), y@(Just (MoveBounced _))) -> y
                    (Nothing, x@(Just (MoveOverpowered _)), y@(Just (MoveBounced _))) -> x
                    (Nothing, x@(Just (MoveOverpowered _)), y@(Just (MoveOverpowered _))) -> y
                    (x, y, z) -> x <|> y <|> z
              where
                checkConvoy = case requiresConvoy of
                    RequiresConvoy ->
                        if    null (successfulConvoyRoutes theseConvoyRoutes)
                        then if null (convoyRoutesParadox theseConvoyRoutes)
                             then Just MoveNoConvoy
                             else Just MoveConvoyParadox
                        else Nothing
                    _ -> Nothing
                
                
                checkCompeting = case sortedOpposingSupports of
                    [] -> Nothing
                    ((x, ss) : xs) ->
                        if length ss == length thisSupports
                        then Just (MoveBounced (AtLeast (VCons x VNil) equallySupported))
                        else if length ss > length thisSupports
                        then Just (MoveOverpowered (AtLeast (VCons x VNil) equallySupported))
                        else Nothing
                      where
                        equallySupported = fmap fst (filter (\(x, ss') -> length ss' == length ss) xs)
                  where
                    sortedOpposingSupports = sortBy comparator opposingSupports
                    comparator :: (Aligned Subject, Supports) -> (Aligned Subject, Supports) -> Ordering
                    comparator (_, xs) (_, ys) = Down (length xs) `compare` Down (length ys)
                    opposingSupports :: [(Aligned Subject, Supports)]
                    opposingSupports = fmap (\x -> (fst x, calculateOpposingSupports x)) theseCompetingMoves
                    calculateOpposingSupports :: (Aligned Subject, ProvinceTarget) -> Supports
                    calculateOpposingSupports (asubj, pt) = support resolution (alignedThing asubj) pt
                    thisSupports :: Supports
                    thisSupports = support resolution (alignedThing aunit, zoneProvinceTarget zone) (moveTarget moveObject)
                checkIncumbant = case thisIncumbant of
                    NoIncumbant -> Nothing
                    
                    
                    
                    
                    
                    Stationary asubj -> case sortedOpposingSupports of
                        [] -> Nothing 
                        ((x, ss) : xs) ->
                            if length ss == length thisSupports
                            then Just (MoveBounced (AtLeast (VCons x VNil) equallySupported))
                            else if length ss > length thisSupports
                            then Just (MoveOverpowered (AtLeast (VCons x VNil) equallySupported))
                            else if opposingPower == thisPower
                            then Just (MoveFriendlyDislodge (alignedThing aunit))
                            else Nothing
                          where
                            equallySupported = fmap fst (filter (\(x, ss') -> length ss' == length ss) xs)
                      where
                        thisSupports :: Supports
                        thisSupports = foreignSupport resolution opposingPower (alignedThing aunit, zoneProvinceTarget zone) (moveTarget moveObject)
                        sortedOpposingSupports = sortBy comparator opposingSupports
                        comparator :: (Aligned Subject, Supports) -> (Aligned Subject, Supports) -> Ordering
                        comparator (_, xs) (_, ys) = Down (length xs) `compare` Down (length ys)
                        opposingSupports :: [(Aligned Subject, Supports)]
                        opposingSupports = fmap (\x -> (fst x, calculateOpposingSupports x)) theseCompetingMovesWithStationary
                        calculateOpposingSupports :: (Aligned Subject, ProvinceTarget) -> Supports
                        calculateOpposingSupports (asubj, pt) = support resolution (alignedThing asubj) pt
                        theseCompetingMovesWithStationary = (asubj, subjectProvinceTarget thisSubject) : theseCompetingMoves
                        opposingSubject = alignedThing asubj
                        opposingPower = alignedGreatPower asubj
                        thisPower = alignedGreatPower aunit
                        thisSubject = alignedThing asubj
                    
                    
                    
                    
                    
                    ReturningMove asubj pt -> case sortedOpposingSupports of
                        [] -> Nothing 
                        ((x, ss) : xs) ->
                            if length ss == length thisSupports
                            then Just (MoveBounced (AtLeast (VCons x VNil) equallySupported))
                            else if length ss > length thisSupports
                            then Just (MoveOverpowered (AtLeast (VCons x VNil) equallySupported))
                            else if opposingPower == thisPower
                            then Just (MoveFriendlyDislodge (subjectUnit (alignedThing asubj)))
                            else Nothing
                          where
                            equallySupported = fmap fst (filter (\(x, ss') -> length ss' == length ss) xs)
                      where
                        thisSupports :: Supports
                        thisSupports = foreignSupport resolution (alignedGreatPower asubj) (alignedThing aunit, zoneProvinceTarget zone) (moveTarget moveObject)
                        
                        
                        
                        
                        sortedOpposingSupports = sortBy comparator ((align (opposingUnit, pt) opposingPower, []) : opposingSupports)
                        comparator :: (Aligned Subject, Supports) -> (Aligned Subject, Supports) -> Ordering
                        comparator (_, xs) (_, ys) = Down (length xs) `compare` Down (length ys)
                        opposingSupports :: [(Aligned Subject, Supports)]
                        opposingSupports = fmap (\x -> (fst x, calculateOpposingSupports x)) theseCompetingMoves
                        calculateOpposingSupports :: (Aligned Subject, ProvinceTarget) -> Supports
                        calculateOpposingSupports (asubj, pt) = support resolution (alignedThing asubj) pt
                        opposingSubject = alignedThing asubj
                        opposingUnit = subjectUnit opposingSubject
                        opposingPower = alignedGreatPower asubj
                        thisPower = alignedGreatPower aunit
                    
                    
                    
                    
                    ComplementaryMove WouldNotSucceed asubj target -> case sortedOpposingSupports of
                        [] -> Nothing 
                        ((x, ss) : xs) ->
                            if length ss > length thisSupports && opposingPower /= thisPower
                            then Just (MoveOverpowered (AtLeast (VCons x VNil) equallySupported))
                            else if length thisSupports > length ss && opposingPower == thisPower
                            then Just (MoveFriendlyDislodge opposingUnit)
                            else if length ss == length thisSupports
                            then Just (MoveBounced (AtLeast (VCons x VNil) equallySupported))
                            else Nothing
                          where
                            equallySupported = fmap fst (filter (\(x, ss') -> length ss' == length ss) xs)
                      where
                        sortedOpposingSupports = sortBy comparator ((asubj, complementarySupports) : opposingSupports)
                        comparator :: (Aligned Subject, Supports) -> (Aligned Subject, Supports) -> Ordering
                        comparator (_, xs) (_, ys) = Down (length xs) `compare` Down (length ys)
                        opposingSupports :: [(Aligned Subject, Supports)]
                        opposingSupports = fmap (\x -> (fst x, calculateOpposingSupports x)) theseCompetingMoves
                        calculateOpposingSupports :: (Aligned Subject, ProvinceTarget) -> Supports
                        calculateOpposingSupports (asubj, pt) = support resolution (alignedThing asubj) pt
                        complementarySupports :: Supports
                        complementarySupports = foreignSupport resolution thisPower opposingSubject target
                        thisSupports :: Supports
                        thisSupports = foreignSupport resolution opposingPower (alignedThing aunit, zoneProvinceTarget zone) (moveTarget moveObject)
                        opposingPower = alignedGreatPower asubj
                        opposingSubject = alignedThing asubj
                        opposingUnit = subjectUnit opposingSubject
                        thisPower = alignedGreatPower aunit
                    
                    
                    
                    
                    ComplementaryMove WouldSucceed asubj target ->
                        if     not (null opposingSuccessfulConvoyRoutes)
                            || not (null thisSuccessfulConvoyRoutes)
                        then Nothing
                        else case sortedOpposingSupports of
                            [] -> Nothing 
                            ((x, ss) : xs) ->
                                if length ss > length thisSupports && opposingPower /= thisPower
                                then Just (MoveOverpowered (AtLeast (VCons x VNil) equallySupported))
                                else if length thisSupports > length ss && opposingPower == thisPower
                                then Just (MoveFriendlyDislodge opposingUnit)
                                else if    length ss == length thisSupports
                                then Just (MoveBounced (AtLeast (VCons x VNil) equallySupported))
                                else Nothing
                              where
                                equallySupported = fmap fst (filter (\(x, ss') -> length ss' == length ss) xs)
                      where
                        sortedOpposingSupports = sortBy comparator ((asubj, complementarySupports) : opposingSupports)
                        comparator :: (Aligned Subject, Supports) -> (Aligned Subject, Supports) -> Ordering
                        comparator (_, xs) (_, ys) = Down (length xs) `compare` Down (length ys)
                        opposingSupports :: [(Aligned Subject, Supports)]
                        opposingSupports = fmap (\x -> (fst x, calculateOpposingSupports x)) theseCompetingMoves
                        calculateOpposingSupports :: (Aligned Subject, ProvinceTarget) -> Supports
                        calculateOpposingSupports (asubj, pt) = support resolution (alignedThing asubj) pt
                        complementarySupports :: Supports
                        complementarySupports = foreignSupport resolution thisPower opposingSubject target
                        thisSupports :: Supports
                        thisSupports = foreignSupport resolution opposingPower (alignedThing aunit, zoneProvinceTarget zone) (moveTarget moveObject)
                        opposingSuccessfulConvoyRoutes :: [ConvoyRoute]
                        opposingSuccessfulConvoyRoutes = successfulConvoyRoutes opposingConvoyRoutes
                        thisSuccessfulConvoyRoutes :: [ConvoyRoute]
                        thisSuccessfulConvoyRoutes = successfulConvoyRoutes theseConvoyRoutes
                        opposingConvoyRoutes :: ConvoyRoutes
                        opposingConvoyRoutes = convoyRoutes (dropAssumptionTags resolution) opposingSubject target
                        opposingPower = alignedGreatPower asubj
                        opposingSubject = alignedThing asubj
                        opposingUnit = subjectUnit opposingSubject
                        thisPower = alignedGreatPower aunit
        
        
        
        
        
        
        
        
        
        
        
        resolveSupport
            :: OrderObject Typical Support
            -> Maybe (FailureReason Typical Support)
        resolveSupport supportObject =
                supportVoid supportObject
            <|> supportCut supportObject
            <|> supportDislodged supportObject
        
        supportVoid
            :: OrderObject Typical Support
            -> Maybe (FailureReason Typical Support)
        supportVoid (SupportObject supportingSubject supportingTo) =
            case M.lookup supportingFrom (dropAssumptionTags resolution) of
                Nothing -> Just SupportVoid
                Just (aunit, SomeResolved (object, _)) ->
                    if    supportingUnit == alignedThing aunit
                       && supportingTo == destination
                    then Nothing
                    else Just SupportVoid
                  where
                    destination = case object of
                        MoveObject pt -> pt
                        _ -> zoneProvinceTarget supportingFrom
          where
            supportingFrom :: Zone
            supportingFrom = Zone (snd supportingSubject)
            supportingUnit :: Unit
            supportingUnit = fst supportingSubject
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        supportCut
            :: OrderObject Typical Support
            -> Maybe (FailureReason Typical Support)
        supportCut (SupportObject supportingSubject supportingTo) =
            case filter issuedByOtherGreatPower offendingMoves of
                [] -> Nothing
                x : xs -> Just (SupportCut (AtLeast (VCons x VNil) xs))
          where
            issuedByOtherGreatPower :: Aligned Subject -> Bool
            issuedByOtherGreatPower x = alignedGreatPower aunit /= alignedGreatPower x
            supportingFrom :: Zone
            supportingFrom = zone
            offendingMoves :: [Aligned Subject]
            offendingMoves = M.elems (M.mapMaybeWithKey pickOffendingMove (dropAssumptionTags resolution))
            pickOffendingMove
                :: Zone
                -> (Aligned Unit, SomeResolved OrderObject Typical)
                -> Maybe (Aligned Subject)
            pickOffendingMove zone (aunit', SomeResolved (object, _)) =
                case object of
                    MoveObject movingTo ->
                        if    Zone movingTo == supportingFrom
                           && Zone supportingTo /= zone
                           && not (isConvoyMoveWithNoConvoyRoute thisClassification)
                        then Just $ align (alignedThing aunit', zoneProvinceTarget zone) (alignedGreatPower aunit')
                        else Nothing
                      where
                        thisClassification = classify resolution zone (aunit', object)
                    _ -> Nothing
        
        
        supportDislodged
            :: OrderObject Typical Support
            -> Maybe (FailureReason Typical Support)
        supportDislodged _ = case typicalChange (dropAssumptionTags resolution) zone of
            Nothing -> Nothing
            Just dislodger -> Just (SupportDislodged dislodger)
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        
        resolveConvoy
            :: OrderObject Typical Convoy
            -> Maybe (FailureReason Typical Convoy)
        resolveConvoy convoyObject =
                convoyVoid convoyObject
            <|> convoyNoRoute convoyObject
        convoyVoid
            :: OrderObject Typical Convoy
            -> Maybe (FailureReason Typical Convoy)
        convoyVoid (ConvoyObject subject target) =
            if isVoidConvoy (dropAssumptionTags resolution) subject target
            then Just ConvoyVoid
            else Nothing
        
        
        convoyNoRoute
            :: OrderObject Typical Convoy
            -> Maybe (FailureReason Typical Convoy)
        convoyNoRoute (ConvoyObject convoyingSubject convoyingTo) =
            case routesParticipatedIn of
                [] -> Just ConvoyNoRoute
                _ -> fmap ConvoyRouteCut cuttingSet
          where
            routes :: [[(Zone, Maybe (Aligned Subject))]]
            routes = rawConvoyRoutes (dropAssumptionTags resolution) convoyingSubject convoyingTo
            routesParticipatedIn :: [[(Zone, Maybe (Aligned Subject))]]
            routesParticipatedIn = filter participates routes
              where
                participates = any (\(z, _) -> z == zone)
            cuttingSet :: Maybe [(Zone, Aligned Subject)]
            cuttingSet | length cutRoutes == length routesParticipatedIn = Just (nub (concat cutRoutes))
                       | otherwise = Nothing
            cutRoutes :: [[(Zone, Aligned Subject)]]
            cutRoutes = filter (not . null) (fmap cutRoute routesParticipatedIn)
            cutRoute
                :: [(Zone, Maybe (Aligned Subject))]
                -> [(Zone, Aligned Subject)]
            cutRoute = mapMaybe pickCutRoute
            pickCutRoute
                :: (Zone, Maybe (Aligned Subject))
                -> Maybe (Zone, Aligned Subject)
            pickCutRoute (z, m) = fmap ((,) z) m
    in  thisResolution
typicalChange :: Resolution Typical -> Zone -> Maybe (Aligned Subject)
typicalChange res zone = M.foldWithKey folder Nothing res
  where
    folder
        :: Zone
        -> (Aligned Unit, SomeResolved OrderObject Typical)
        -> Maybe (Aligned Subject)
        -> Maybe (Aligned Subject)
    folder zone' (aunit, SomeResolved (object, resolution)) b = case object of
        MoveObject movingTo ->
            
            
            if    Zone movingTo /= zone
               || Zone movingTo == zone'
            then b
            else case resolution of
                     Nothing -> let power = alignedGreatPower aunit
                                    unit = alignedThing aunit
                                    subj = align (unit, zoneProvinceTarget zone') power
                                in  Just subj
                     _ -> b
        _ -> b
typicalResolution
    :: M.Map Zone (Aligned Unit, SomeOrderObject Typical)
    -> Resolution Typical
typicalResolution = dropAssumptionTags . typicalResolutionAssuming . noAssumptions
retreatResolution
    :: M.Map Zone (Aligned Unit, SomeOrderObject Retreat)
    -> Resolution Retreat
retreatResolution zonedOrders = M.mapWithKey (resolveRetreat zonedWithdraws) zonedOrders
  where
    
    
    zonedWithdraws :: M.Map Zone [Aligned Subject]
    zonedWithdraws = M.foldWithKey folder M.empty zonedOrders
      where
        folder
            :: Zone
            -> (Aligned Unit, SomeOrderObject Retreat)
            -> M.Map Zone [Aligned Subject]
            -> M.Map Zone [Aligned Subject]
        folder zone (aunit, SomeOrderObject object) b = case object of
            WithdrawObject withdrawingTo -> M.alter alteration (Zone withdrawingTo) b
              where
                subject = align (alignedThing aunit, zoneProvinceTarget zone) (alignedGreatPower aunit)
                alteration x = case x of
                    Nothing -> Just [subject]
                    Just ys -> Just (subject : ys)
            _ -> b
    resolveRetreat
        :: M.Map Zone [Aligned Subject]
        -> Zone
        -> (Aligned Unit, SomeOrderObject Retreat)
        -> (Aligned Unit, SomeResolved OrderObject Retreat)
    resolveRetreat zonedWithdraws zone (aunit, SomeOrderObject object) = case object of
        SurrenderObject -> (aunit, SomeResolved (object, Nothing))
        WithdrawObject _ -> (aunit, SomeResolved (object, resolution))
          where
            resolution :: Maybe (FailureReason Retreat Withdraw)
            resolution = case fmap (filter (/= thisSubject)) (M.lookup (Zone (withdrawTarget object)) zonedWithdraws) of
                Just [] -> Nothing
                Just (x : xs) -> Just (WithdrawCollision (AtLeast (VCons x VNil) xs))
                _ -> Nothing
      where
        thisSubject = align (alignedThing aunit, zoneProvinceTarget zone) (alignedGreatPower aunit)
adjustResolution
    :: M.Map Zone (Aligned Unit, SomeOrderObject Adjust)
    -> Resolution Adjust
adjustResolution = M.map (\(aunit, SomeOrderObject object) -> (aunit, SomeResolved (object, Nothing)))
type Resolved (k :: Phase -> OrderType -> *) (phase :: Phase) (order :: OrderType) =
    (k phase order, Maybe (FailureReason phase order))
data SomeResolved (k :: Phase -> OrderType -> *) phase where
    SomeResolved :: Resolved k phase order -> SomeResolved k phase
deriving instance Show (SomeResolved OrderObject phase)
deriving instance Show (SomeResolved Order phase)
instance Eq (SomeResolved OrderObject phase) where
    SomeResolved (object1, res1) == SomeResolved (object2, res2) =
           object1 `orderObjectEqual` object2
        && case (res1, res2) of
               (Just r1, Just r2) -> failureReasonEqual r1 r2
               (Nothing, Nothing) -> True
               _ -> False
withSomeResolved
  :: (forall order . Resolved k phase order -> t) -> SomeResolved k phase -> t
withSomeResolved f term = case term of
    SomeResolved x -> f x
data FailureReason (phase :: Phase) (order :: OrderType) where
    MoveOverpowered :: AtLeast One (Aligned Subject) -> FailureReason Typical Move
    MoveBounced :: AtLeast One (Aligned Subject) -> FailureReason Typical Move
    
    
    
    
    MoveFriendlyDislodge :: Unit -> FailureReason Typical Move
    MoveNoConvoy :: FailureReason Typical Move
    MoveConvoyParadox :: FailureReason Typical Move
    
    
    SupportVoid :: FailureReason Typical Support
    
    
    SupportCut :: AtLeast One (Aligned Subject) -> FailureReason Typical Support
    
    
    SupportDislodged :: Aligned Subject -> FailureReason Typical Support
    ConvoyVoid :: FailureReason Typical Convoy
    ConvoyNoRoute :: FailureReason Typical Convoy
    ConvoyRouteCut :: [(Zone, Aligned Subject)] ->  FailureReason Typical Convoy
    
    WithdrawCollision :: AtLeast One (Aligned Subject) -> FailureReason Retreat Withdraw
    
    
deriving instance Show (FailureReason phase order)
deriving instance Eq (FailureReason phase order)
failureReasonEqual
    :: FailureReason phase order
    -> FailureReason phase' order'
    -> Bool
failureReasonEqual r1 r2 = case (r1, r2) of
    (MoveOverpowered x, MoveOverpowered y) -> x == y
    (MoveBounced x, MoveBounced y) -> x == y
    (MoveFriendlyDislodge x, MoveFriendlyDislodge y) -> x == y
    (MoveNoConvoy, MoveNoConvoy) -> True
    (MoveConvoyParadox, MoveConvoyParadox) -> True
    (SupportVoid, SupportVoid) -> True
    (SupportCut x, SupportCut y) -> x == y
    (SupportDislodged x, SupportDislodged y) -> x == y
    (ConvoyVoid, ConvoyVoid) -> True
    (ConvoyNoRoute, ConvoyNoRoute) -> True
    (ConvoyRouteCut x, ConvoyRouteCut y) -> x == y
    (WithdrawCollision x, WithdrawCollision y) -> x == y
    _ -> False