{-# LANGUAGE DeriveGeneric, GeneralizedNewtypeDeriving #-}
module Game.LambdaHack.Client.Bfs
( BfsDistance, MoveLegal(..), minKnownBfs, apartBfs, fillBfs
, AndPath(..), findPathBfs
, accessBfs
#ifdef EXPOSE_INTERNAL
#endif
) where
import Prelude ()
import Game.LambdaHack.Common.Prelude
import Control.Monad.ST.Strict
import Data.Binary
import Data.Bits (Bits, complement, (.&.), (.|.))
import qualified Data.Vector.Unboxed as U
import qualified Data.Vector.Unboxed.Mutable as VM
import GHC.Generics (Generic)
import Game.LambdaHack.Common.Point
import qualified Game.LambdaHack.Common.PointArray as PointArray
newtype BfsDistance = BfsDistance {bfsDistance :: Word8}
deriving (Show, Eq, Ord, Enum, Bounded, Bits)
data MoveLegal = MoveBlocked | MoveToOpen | MoveToClosed | MoveToUnknown
deriving Eq
minKnownBfs :: BfsDistance
minKnownBfs = toEnum $ (1 + fromEnum (maxBound :: BfsDistance)) `div` 2
apartBfs :: BfsDistance
apartBfs = pred minKnownBfs
abortedKnownBfs :: BfsDistance
abortedKnownBfs = pred maxBound
abortedUnknownBfs :: BfsDistance
abortedUnknownBfs = pred apartBfs
type PointI = Int
type VectorI = Int
fillBfs :: PointArray.Array Word8
-> Word8
-> Point
-> PointArray.Array BfsDistance
-> ()
{-# INLINE fillBfs #-}
fillBfs lalter alterSkill source arr@PointArray.Array{..} =
let vToI (x, y) = PointArray.pindex axsize (Point x y)
movesI :: [VectorI]
movesI = map vToI
[(-1, -1), (0, -1), (1, -1), (1, 0), (1, 1), (0, 1), (-1, 1), (-1, 0)]
unsafeWriteI :: Int -> BfsDistance -> ()
{-# INLINE unsafeWriteI #-}
unsafeWriteI p c = runST $ do
vThawed <- U.unsafeThaw avector
VM.unsafeWrite vThawed p (bfsDistance c)
void $ U.unsafeFreeze vThawed
bfs :: BfsDistance -> [PointI] -> ()
bfs !distance !predK =
let processKnown :: PointI -> [PointI] -> [PointI]
processKnown !pos !succK2 =
let fKnown :: [PointI] -> VectorI -> [PointI]
fKnown !l !move =
let !p = pos + move
visitedMove =
BfsDistance (arr `PointArray.accessI` p) /= apartBfs
in if visitedMove
then l
else let alter :: Word8
!alter = lalter `PointArray.accessI` p
in if | alterSkill < alter -> l
| alter == 1 ->
let distCompl =
distance .&. complement minKnownBfs
in unsafeWriteI p distCompl
`seq` l
| otherwise -> unsafeWriteI p distance
`seq` p : l
in foldl' fKnown succK2 movesI
succK4 = foldr processKnown [] predK
in if null succK4 || distance == abortedKnownBfs
then ()
else bfs (succ distance) succK4
in bfs (succ minKnownBfs) [PointArray.pindex axsize source]
data AndPath =
AndPath { pathList :: ![Point]
, pathGoal :: !Point
, pathLen :: !Int
}
| NoPath
deriving (Show, Generic)
instance Binary AndPath
findPathBfs :: PointArray.Array Word8 -> (Point -> Bool)
-> Point -> Point -> Int
-> PointArray.Array BfsDistance
-> AndPath
{-# INLINE findPathBfs #-}
findPathBfs lalter fovLit pathSource pathGoal sepsRaw
arr@PointArray.Array{..} =
let !pathGoalI = PointArray.pindex axsize pathGoal
!pathSourceI = PointArray.pindex axsize pathSource
eps = sepsRaw `mod` 4
(mc1, mc2) = splitAt eps [(0, -1), (1, 0), (0, 1), (-1, 0)]
(md1, md2) = splitAt eps [(-1, -1), (1, -1), (1, 1), (-1, 1)]
prefMoves = mc1 ++ reverse mc2 ++ md2 ++ reverse md1
vToI (x, y) = PointArray.pindex axsize (Point x y)
movesI :: [VectorI]
movesI = map vToI prefMoves
track :: PointI -> BfsDistance -> [Point] -> [Point]
track !pos !oldDist !suffix | oldDist == minKnownBfs =
assert (pos == pathSourceI) suffix
track pos oldDist suffix | oldDist == succ minKnownBfs =
let !posP = PointArray.punindex axsize pos
in posP : suffix
track pos oldDist suffix =
let !dist = pred oldDist
minChild !minP _ _ [] = minP
minChild minP maxDark minAlter (mv : mvs) =
let !p = pos + mv
backtrackingMove =
BfsDistance (arr `PointArray.accessI` p) /= dist
in if backtrackingMove
then minChild minP maxDark minAlter mvs
else let alter = lalter `PointArray.accessI` p
dark = not $ fovLit $ PointArray.punindex axsize p
in if | alter == 0 && dark -> p
| alter < minAlter -> minChild p dark alter mvs
| dark > maxDark && alter == minAlter ->
minChild p dark alter mvs
| otherwise -> minChild minP maxDark minAlter mvs
!newPos = minChild pos False maxBound movesI
#ifdef WITH_EXPENSIVE_ASSERTIONS
!_A = assert (newPos /= pos) ()
#endif
!posP = PointArray.punindex axsize pos
in track newPos dist (posP : suffix)
!goalDist = BfsDistance $ arr `PointArray.accessI` pathGoalI
pathLen = fromEnum $ goalDist .&. complement minKnownBfs
pathList = track pathGoalI (goalDist .|. minKnownBfs) []
andPath = AndPath{..}
in assert (BfsDistance (arr `PointArray.accessI` pathSourceI)
== minKnownBfs) $
if goalDist /= apartBfs && pathLen < 2 * chessDist pathSource pathGoal
then andPath
else let f :: (Point, Int, Int, Int) -> Point -> BfsDistance
-> (Point, Int, Int, Int)
f acc@(pAcc, dAcc, chessAcc, sumAcc) p d =
if d <= abortedUnknownBfs
|| d /= apartBfs && adjacent p pathGoal
then let dist = fromEnum $ d .&. complement minKnownBfs
chessNew = chessDist p pathGoal
sumNew = dist + 2 * chessNew
resNew = (p, dist, chessNew, sumNew)
in case compare sumNew sumAcc of
LT -> resNew
EQ -> case compare chessNew chessAcc of
LT -> resNew
EQ -> case compare dist dAcc of
LT -> resNew
EQ | euclidDistSq p pathGoal
< euclidDistSq pAcc pathGoal -> resNew
_ -> acc
_ -> acc
_ -> acc
else acc
initAcc = (originPoint, maxBound, maxBound, maxBound)
(pRes, dRes, _, sumRes) = PointArray.ifoldlA' f initAcc arr
in if sumRes == maxBound
|| goalDist /= apartBfs && pathLen < sumRes
then if goalDist /= apartBfs then andPath else NoPath
else let pathList2 = track (PointArray.pindex axsize pRes)
(toEnum dRes .|. minKnownBfs) []
in AndPath{pathList = pathList2, pathLen = sumRes, ..}
accessBfs :: PointArray.Array BfsDistance -> Point -> Maybe Int
accessBfs bfs p =
let dist = bfs PointArray.! p
in if dist == apartBfs
then Nothing
else Just $ fromEnum $ dist .&. complement minKnownBfs