module Game.Mastermind (
   Eval(Eval),
   evaluate,
   matching,
   matchingSimple,
   randomizedAttempt,
   mixedRandomizedAttempt,
   scanningRandomizedAttempt,
   separatingRandomizedAttempt,
   partitionSizes,
   mainSimple,
   mainRandom,
   main,
   propBestSeparatingCode,
   ) where
import qualified Game.Mastermind.CodeSet.Tree as CodeSetTree
import qualified Game.Mastermind.CodeSet as CodeSet
import qualified Game.Mastermind.NonEmptyEnumSet as NonEmptySet
import Game.Mastermind.CodeSet
   (intersection, (*&), (#*&), unit, empty, union, unions, cube, )
import Game.Utility
   (Choice(Choice), mergeChoice, noChoice, randomSelect, histogram)
import qualified Data.EnumMap as EnumMap
import qualified Data.EnumSet as EnumSet
import qualified Data.Map as Map
import qualified Data.Set as Set
import Data.EnumMap (EnumMap)
import Data.EnumSet (EnumSet)
import qualified Data.NonEmpty as NonEmpty
import qualified Data.List as List
import Data.NonEmpty ((!:))
import Data.List.HT (partition, )
import Data.Tuple.HT (mapPair, )
import Data.Maybe.HT (toMaybe, )
import Data.Maybe (listToMaybe, fromMaybe)
import Data.Ord.HT (comparing)
import Data.Eq.HT (equating)
import qualified Control.Monad.Trans.State as MS
import Control.Monad.IO.Class (liftIO)
import Control.Monad (guard, when, replicateM, liftM2, )
import qualified System.Random as Rnd
import qualified System.IO as IO
data Eval = Eval Int Int
   deriving (Eq, Ord, Show)
evaluate :: (Enum a) => [a] -> [a] -> Eval
evaluate code attempt =
   uncurry Eval $
   mapPair
      (length,
       sum . EnumMap.elems .
       uncurry (EnumMap.intersectionWith min) .
       mapPair (bagFromList,bagFromList) . unzip) $
   partition (uncurry $ equating fromEnum) $
   zip code attempt
bagFromList :: (Enum a) => [a] -> EnumMap a Int
bagFromList = EnumMap.fromListWith (+) . map (\a -> (a,1))
selectFromBag, _selectFromBag ::
   (Enum a) => EnumMap a Int -> [(a, EnumMap a Int)]
selectFromBag hist =
   map (\a -> (a, EnumMap.update (\n -> toMaybe (n>1) (pred n)) a hist)) $
   EnumMap.keys hist
_selectFromBag hist =
   EnumMap.toList $
   EnumMap.mapWithKey
      (\a _ -> EnumMap.update (\n -> toMaybe (n>1) (pred n)) a hist) hist
matchingSimple :: Enum a => EnumSet a -> [a] -> Int -> [[EnumSet a]]
matchingSimple alphabet code rightPlaces =
   map
      (zipWith
         (\symbol right ->
            if right
              then EnumSet.singleton symbol
              else EnumSet.delete symbol alphabet)
         code) $
   possibleRightPlaces (length code) rightPlaces
possibleRightPlaces :: Int -> Int -> [[Bool]]
possibleRightPlaces n rightPlaces =
   if n < rightPlaces
     then []
     else
       if n==0
         then [[]]
         else
            (guard (rightPlaces>0) >>
               (map (True:) $
                possibleRightPlaces (n-1) (rightPlaces-1)))
            ++
            (map (False:) $
             possibleRightPlaces (n-1) rightPlaces)
matching :: (CodeSet.C set, Enum a) => EnumSet a -> [a] -> Eval -> set a
matching alphabet =
   let findCodes =
          foldr
             (\(fixed,c) go rightSymbols floating0 ->
                if fixed
                  then c #*& go rightSymbols floating0
                  else
                    (unions $ do
                        guard (rightSymbols > 0)
                        (src, floating1) <- selectFromBag floating0
                        guard (not $ equating fromEnum c src)
                        return $ src #*& go (rightSymbols-1) floating1)
                    `union`
                    (EnumSet.difference
                        (EnumSet.delete c alphabet)
                        (EnumMap.keysSet floating0) *&
                     go rightSymbols floating0))
             (\rightSymbols _floating ->
                if rightSymbols>0
                  then empty
                  else unit)
   in \code (Eval rightPlaces rightSymbols) ->
       unions $
       map
          (\pattern ->
             let patternCode = zip pattern code
             in  findCodes patternCode rightSymbols $
                 bagFromList $ map snd $ filter (not . fst) patternCode) $
       possibleRightPlaces (length code) rightPlaces
partitionSizes :: (Enum a) => EnumSet a -> [a] -> [(Eval, Integer)]
partitionSizes alphabet code =
   map (\eval -> (eval, CodeSetTree.size $ matching alphabet code eval)) $
   possibleEvaluations (length code)
possibleEvaluations :: Int -> [Eval]
possibleEvaluations n = do
   rightPlaces <- [0..n]
   rightSymbols <- [0..n-rightPlaces]
   return $ Eval rightPlaces rightSymbols
interaction ::
   (CodeSetTree.T Char -> MS.State state (Maybe [Char])) ->
   state -> NonEmptySet.T Char -> Int -> IO ()
interaction select initial alphabet n =
   let go set = do
          newGuess <- MS.state $ MS.runState $ select set
          case newGuess of
             Nothing -> liftIO $ putStrLn "contradicting evaluations"
             Just attempt -> do
                liftIO $ do
                   putStr $
                      show attempt ++ " " ++
                      show (CodeSet.size set, CodeSet.representationSize set,
                            EnumSet.size (CodeSet.symbols set)) ++ " "
                   IO.hFlush IO.stdout
                eval <- liftIO getLine
                let getEval =
                      fmap (fromMaybe 0) . MS.state .
                      EnumMap.updateLookupWithKey (\_ _ -> Nothing)
                let ((rightPlaces,rightSymbols), ignored) =
                      MS.runState (liftM2 (,) (getEval 'x') (getEval 'o')) $
                      bagFromList eval
                when (not $ EnumMap.null ignored) $
                   liftIO $ putStrLn $ "ignoring: " ++ EnumMap.keys ignored
                if rightPlaces >= n
                  then liftIO $ putStrLn "I won!"
                  else go $ intersection set $
                       matching (NonEmptySet.flatten alphabet) attempt $
                       Eval rightPlaces rightSymbols
   in MS.evalStateT (go (cube alphabet n)) initial
mainSimple :: NonEmptySet.T Char -> Int -> IO ()
mainSimple = interaction (return . listToMaybe . CodeSet.flatten) ()
minimax :: (Ord b) => (a -> [b]) -> NonEmpty.T [] a -> a
minimax f (NonEmpty.Cons a0 rest) =
   fst $
   foldl
      (\old@(_minA, minB) a ->
         let (ltMinB, geMinB) = partition (<minB) $ f a
         in if null geMinB then (a, maximum ltMinB) else old)
      (a0, maximum $ f a0) rest
reduceAlphabet :: (CodeSet.C set, Enum a) => set a -> EnumSet a -> EnumSet a
reduceAlphabet set alphabet =
   let symbols = CodeSet.symbols set
   in  EnumSet.union symbols $ EnumSet.fromList $ take 1 $ EnumSet.toList $
       EnumSet.difference alphabet symbols
bestSeparatingCode ::
   (CodeSet.C set, Enum a) => Int -> set a -> NonEmpty.T [] [a] -> [a]
bestSeparatingCode n set =
   let alphabet = CodeSet.symbols set
   in minimax $ \attempt ->
         map (CodeSet.size . intersection set . matching alphabet attempt) $
         possibleEvaluations n
bestSeparatingCodeHistogram ::
   (CodeSet.C set, Enum a) => set a -> NonEmpty.T [] [a] -> [a]
bestSeparatingCodeHistogram set =
   minimax $ \attempt ->
      Map.elems $ histogram $ map (evaluate attempt) $ CodeSet.flatten set
propBestSeparatingCode ::
   (CodeSet.C set, Enum a) => Int -> set a -> NonEmpty.T [] [a] -> Bool
propBestSeparatingCode n set attempts =
   equating (map fromEnum)
      (bestSeparatingCode n set attempts)
      (bestSeparatingCodeHistogram set attempts)
randomizedAttempt ::
   (CodeSet.C set, Rnd.RandomGen g, Enum a) =>
   Int -> set a -> MS.State g (Maybe [a])
randomizedAttempt n set = do
   let symbolSet = CodeSet.symbols set
   let randomCode = replicateM n $ randomSelect $ EnumSet.toList symbolSet
   randomAttempts <- liftM2 (!:) randomCode $ replicateM 9 randomCode
   let somePossible =
          
          let size = CodeSet.size set
              num = 10
          in  map (CodeSet.select set) $
              Set.toList $ Set.fromList $
              take num $
              map (flip div (fromIntegral num)) $
              iterate (size+) 0
   return $
      toMaybe (not $ CodeSet.null set) $
      bestSeparatingCode n set $
      NonEmpty.appendLeft somePossible randomAttempts
withNonEmptyCodeSet ::
   (Monad m, CodeSet.C set, Enum a) =>
   set a ->
   (NonEmpty.T [] [a] -> m (Maybe [a])) ->
   m (Maybe [a])
withNonEmptyCodeSet set f =
   case CodeSet.flatten set of
      [] -> return Nothing
      x:[] -> return $ Just x
      x:_:[] -> return $ Just x
      x:xs -> f $ x!:xs
separatingRandomizedAttempt ::
   (CodeSet.C set, Rnd.RandomGen g, Enum a) =>
   Int -> EnumSet a -> set a -> MS.State g (Maybe [a])
separatingRandomizedAttempt n alphabet0 set =
   withNonEmptyCodeSet set $ \flattenedSet ->
      let size = CodeSet.size set
          alphabet = reduceAlphabet set alphabet0
          alphabetSize = EnumSet.size alphabet
      in if size * (size + toInteger alphabetSize ^ n) <= 1000000
            then return $ Just $ bestSeparatingCodeHistogram set $
                 NonEmpty.appendRight flattenedSet $
                 replicateM n (EnumSet.toList alphabet)
            else randomizedAttempt n set
mixedRandomizedAttempt ::
   (CodeSet.C set, Rnd.RandomGen g, Enum a) =>
   Int -> set a -> MS.State g (Maybe [a])
mixedRandomizedAttempt n set =
   withNonEmptyCodeSet set $ \ _flattenedSet ->
      let size = CodeSet.size set
      in if size <= 100
           then randomizedAttempt n set
           else fmap (Just . CodeSet.select set) $
                MS.state $ Rnd.randomR (0, size-1)
scanningRandomizedAttempt ::
   (CodeSet.C set, Rnd.RandomGen g, Enum a) =>
   Int -> EnumSet a -> [([a], Eval)] -> set a -> MS.State g (Maybe [a])
scanningRandomizedAttempt n alphabet oldGuesses set = do
   let sumEval (Eval correctPlaces correctSymbols) =
         correctPlaces + correctSymbols
   let (Choice totalBag count) =
         foldl mergeChoice noChoice $
         map (uncurry Choice . mapPair (bagFromList, sumEval)) oldGuesses
   let unusedSymbols = EnumSet.difference alphabet $ EnumMap.keysSet totalBag
   if count>=n
      then randomizedAttempt n set
      else
         if EnumSet.size unusedSymbols <= n
            then mixedRandomizedAttempt n set
            else do
               let nextSymbols = EnumSet.toList unusedSymbols
               keys <-
                  mapM
                     (const $ MS.state $ Rnd.randomR (0,1::Double))
                     nextSymbols
               return $ Just $ map snd $ take n $
                  List.sortBy (comparing fst) $ zip keys nextSymbols
mainRandom :: NonEmptySet.T Char -> Int -> IO ()
mainRandom alphabet n = do
   g <- Rnd.getStdGen
   interaction
      (separatingRandomizedAttempt n (NonEmptySet.flatten alphabet))
      g alphabet n
main :: IO ()
main =
   let alphabet = NonEmptySet.fromList ('a'!:['b'..'z'])
   in  if True
         then mainRandom alphabet 5
         else mainSimple alphabet 7