module Game.LambdaHack.Common.Level
  ( 
    LevelId, AbsDepth, Dungeon
  , ascendInBranch, whereTo
    
  , Level(..), ItemFloor, ActorMap, TileMap, SmellMap
    
  , at, findPoint, findPos, findPosTry, findPosTry2
  ) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Data.Binary
import qualified Data.EnumMap.Strict as EM
import Game.LambdaHack.Common.Actor
import Game.LambdaHack.Common.Item
import qualified Game.LambdaHack.Common.Kind as Kind
import qualified Game.LambdaHack.Common.KindOps as KindOps
import Game.LambdaHack.Common.Misc
import Game.LambdaHack.Common.Point
import qualified Game.LambdaHack.Common.PointArray as PointArray
import Game.LambdaHack.Common.Random
import Game.LambdaHack.Common.Time
import Game.LambdaHack.Content.ItemKind (ItemKind)
import Game.LambdaHack.Content.TileKind (TileKind)
type Dungeon = EM.EnumMap LevelId Level
ascendInBranch :: Dungeon -> Bool -> LevelId -> [LevelId]
ascendInBranch dungeon up lid =
  
  let (minD, maxD) =
        case (EM.minViewWithKey dungeon, EM.maxViewWithKey dungeon) of
          (Just ((s, _), _), Just ((e, _), _)) -> (s, e)
          _ -> error $ "null dungeon" `showFailure` dungeon
      ln = max minD $ min maxD $ toEnum $ fromEnum lid + if up then 1 else -1
  in case EM.lookup ln dungeon of
    Just _ | ln /= lid -> [ln]
    _ | ln == lid -> []
    _ -> ascendInBranch dungeon up ln  
whereTo :: LevelId    
        -> Point      
        -> Maybe Bool 
        -> Dungeon    
        -> (LevelId, Point)
                      
whereTo lid pos mup dungeon =
  let lvl = dungeon EM.! lid
      (up, i) = case elemIndex pos $ fst $ lstair lvl of
        Just ifst -> (True, ifst)
        Nothing -> case elemIndex pos $ snd $ lstair lvl of
          Just isnd -> (False, isnd)
          Nothing -> case mup of
            Just forcedUp -> (forcedUp, 0)  
            Nothing -> error $ "no stairs at" `showFailure` (lid, pos)
      !_A = assert (maybe True (== up) mup) ()
  in case ascendInBranch dungeon up lid of
    [] | isJust mup -> (lid, pos)  
    [] -> error $ "no dungeon level to go to" `showFailure` (lid, pos)
    ln : _ -> let lvlDest = dungeon EM.! ln
                  stairsDest = (if up then snd else fst) (lstair lvlDest)
              in if length stairsDest < i + 1
                 then error $ "no stairs at index" `showFailure` (lid, pos)
                 else (ln, stairsDest !! i)
type ItemFloor = EM.EnumMap Point ItemBag
type ActorMap = EM.EnumMap Point [ActorId]
type TileMap = PointArray.GArray Word16 (Kind.Id TileKind)
type SmellMap = EM.EnumMap Point Time
data Level = Level
  { ldepth      :: AbsDepth   
  , lfloor      :: ItemFloor  
  , lembed      :: ItemFloor  
  , lactor      :: ActorMap   
  , ltile       :: TileMap    
  , lxsize      :: X          
  , lysize      :: Y          
  , lsmell      :: SmellMap   
  , ldesc       :: Text       
  , lstair      :: ([Point], [Point])
                              
  , lseen       :: Int        
  , lexplorable :: Int        
  , ltime       :: Time       
  , lactorCoeff :: Int        
  , lactorFreq  :: Freqs ItemKind
                              
  , litemNum    :: Int        
  , litemFreq   :: Freqs ItemKind
                              
  , lescape     :: [Point]    
  , lnight      :: Bool
  }
  deriving (Show, Eq)
assertSparseItems :: ItemFloor -> ItemFloor
assertSparseItems m =
  assert (EM.null (EM.filter EM.null m)
          `blame` "null floors found" `swith` m) m
assertSparseActors :: ActorMap -> ActorMap
assertSparseActors m =
  assert (EM.null (EM.filter null m)
          `blame` "null actor lists found" `swith` m) m
at :: Level -> Point -> Kind.Id TileKind
{-# INLINE at #-}
at Level{ltile} p = ltile PointArray.! p
findPoint :: X -> Y -> (Point -> Maybe Point) -> Rnd Point
findPoint x y f =
  let search = do
        pxy <- randomR (0, (x - 1) * (y - 1))
        let pos = PointArray.punindex x pxy
        case f pos of
          Just p -> return p
          Nothing -> search
  in search
findPos :: TileMap -> (Point -> Kind.Id TileKind -> Bool) -> Rnd Point
findPos ltile p =
  let (x, y) = PointArray.sizeA ltile
      search = do
        pxy <- randomR (0, (x - 1) * (y - 1))
        let tile = KindOps.Id $ ltile `PointArray.accessI` pxy
            pos = PointArray.punindex x pxy
        if p pos tile
        then return $! pos
        else search
  in search
findPosTry :: Int                                  
           -> TileMap                              
           -> (Point -> Kind.Id TileKind -> Bool)  
           -> [Point -> Kind.Id TileKind -> Bool]  
           -> Rnd Point
{-# INLINE findPosTry #-}
findPosTry numTries ltile m = findPosTry2 numTries ltile m [] undefined
findPosTry2 :: Int                                  
            -> TileMap                              
            -> (Point -> Kind.Id TileKind -> Bool)  
            -> [Point -> Kind.Id TileKind -> Bool]  
            -> (Point -> Kind.Id TileKind -> Bool)  
            -> [Point -> Kind.Id TileKind -> Bool]  
            -> Rnd Point
findPosTry2 numTries ltile m0 l g r = assert (numTries > 0) $
  let (x, y) = PointArray.sizeA ltile
      accomodate fallback _ [] = fallback  
      accomodate fallback m (hd : tl) =
        let search 0 = accomodate fallback m tl
            search !k = do
              pxy <- randomR (0, (x - 1) * (y - 1))
              let tile = KindOps.Id $ ltile `PointArray.accessI` pxy
                  pos = PointArray.punindex x pxy
              if m pos tile && hd pos tile
              then return $! pos
              else search (k - 1)
        in search numTries
  in accomodate (accomodate (findPos ltile m0) m0 r)
                
                (\pos tile -> m0 pos tile && g pos tile)
                l
instance Binary Level where
  put Level{..} = do
    put ldepth
    put (assertSparseItems lfloor)
    put (assertSparseItems lembed)
    put (assertSparseActors lactor)
    put ltile
    put lxsize
    put lysize
    put lsmell
    put ldesc
    put lstair
    put lseen
    put lexplorable
    put ltime
    put lactorCoeff
    put lactorFreq
    put litemNum
    put litemFreq
    put lescape
    put lnight
  get = do
    ldepth <- get
    lfloor <- get
    lembed <- get
    lactor <- get
    ltile <- get
    lxsize <- get
    lysize <- get
    lsmell <- get
    ldesc <- get
    lstair <- get
    lseen <- get
    lexplorable <- get
    ltime <- get
    lactorCoeff <- get
    lactorFreq <- get
    litemNum <- get
    litemFreq <- get
    lescape <- get
    lnight <- get
    return $! Level{..}