Safe Haskell | None |
---|---|
Language | Haskell2010 |
DFOV (Digital Field of View) implemented according to specification at http://roguebasin.roguelikedevelopment.org/index.php?title=Digital_field_of_view_implementation. This fast version of the algorithm, based on PFOV, has AFAIK never been described nor implemented before.
The map is processed in depth-first-search manner, that is, as soon as we detect on obstacle we move away from the viewer up to the FOV radius and then restart on the other side of the obstacle. This has better cache behaviour than breadth-firsts-search, where we would process all tiles equally distant from the viewer in the same round, because then we'd need to keep the many convex hulls and edges, not just a single set, and we'd potentially traverse all of them each round.
Synopsis
- scan :: Distance -> (PointI -> Bool) -> (Bump -> PointI) -> [PointI]
- data Bump = B {}
- type Distance = Int
- type Progress = Int
- data LineOrdering
- data Line = Line Bump Bump
- data ConvexHull = ConvexHull Bump CHull
- data CHull
- type Edge = (Line, ConvexHull)
- type EdgeInterval = (Edge, Edge)
- steepestInHull :: LineOrdering -> Bump -> ConvexHull -> Bump
- foldlCHull' :: (a -> Bump -> a) -> a -> CHull -> a
- addToHull :: LineOrdering -> Bump -> ConvexHull -> ConvexHull
- addToHullGo :: LineOrdering -> Bump -> CHull -> CHull
- createLine :: Bump -> Bump -> Line
- steepness :: LineOrdering -> Bump -> Bump -> Bump -> Bool
- intersect :: Line -> Distance -> (Int, Int)
- _debugSteeper :: LineOrdering -> Bump -> Bump -> Bump -> Bool
- _debugLine :: Line -> (Bool, String)
Documentation
:: Distance | visiblity distance |
-> (PointI -> Bool) | visually clear position predicate |
-> (Bump -> PointI) | coordinate transformation |
-> [PointI] |
Calculates the list of tiles visible from (0, 0) within the given sight range.
Scanning coordinate system
Rotated and translated coordinates of 2D points, so that the points fit in a single quadrant area (e, g., quadrant I for Permissive FOV, hence both coordinates positive; adjacent diagonal halves of quadrant I and II for Digital FOV, hence y positive). The special coordinates are written using the standard mathematical coordinate setup, where quadrant I, with x and y positive, is on the upper right.
Assorted minor operations
Current scan parameters
Geometry in system Bump
data LineOrdering Source #
Two strict orderings of lines with a common point.
Straight line between points.
data ConvexHull Source #
Convex hull represented as a non-empty list of points.
Instances
Show ConvexHull Source # | |
Defined in Game.LambdaHack.Server.FovDigital showsPrec :: Int -> ConvexHull -> ShowS # show :: ConvexHull -> String # showList :: [ConvexHull] -> ShowS # |
type Edge = (Line, ConvexHull) Source #
An edge (comprising of a line and a convex hull) of the area to be scanned.
type EdgeInterval = (Edge, Edge) Source #
The contiguous area left to be scanned, delimited by edges.
Internal operations
steepestInHull :: LineOrdering -> Bump -> ConvexHull -> Bump Source #
Specialized implementation for speed in the inner loop. Not partial.
foldlCHull' :: (a -> Bump -> a) -> a -> CHull -> a Source #
Standard foldl'
over CHull
.
:: LineOrdering | the line ordering to use |
-> Bump | a new bump to consider |
-> ConvexHull | a convex hull of bumps represented as a list |
-> ConvexHull |
Extends a convex hull of bumps with a new bump. The new bump makes
some old bumps unnecessary, e.g. those that are joined with the new steep
bump with lines that are not shallower than any newer lines in the hull.
Removing such unnecessary bumps slightly speeds up computation
of steepestInHull
.
Recursion in addToHullGo
seems spurious, but it's called each time with
potentially different comparison predicate, so it's necessary.
addToHullGo :: LineOrdering -> Bump -> CHull -> CHull Source #
createLine :: Bump -> Bump -> Line Source #
Create a line from two points.
Debug: check if well-defined.
steepness :: LineOrdering -> Bump -> Bump -> Bump -> Bool Source #
Strictly compare steepness of lines (b1, bf)
and (b2, bf)
,
according to the LineOrdering
given. This is related to comparing
the slope (gradient, angle) of two lines, but simplified wrt signs
to work fast in this particular setup.
Debug: Verify that the results of 2 independent checks are equal.
intersect :: Line -> Distance -> (Int, Int) Source #
A pair (a, b)
such that a
divided by b
is the X coordinate
of the intersection of a given line and the horizontal line at distance
d
above the X axis.
Derivation of the formula:
The intersection point (xt, yt)
satisfies the following equalities:
yt = d (yt - y) (xf - x) = (xt - x) (yf - y)
hence
(yt - y) (xf - x) = (xt - x) (yf - y) (d - y) (xf - x) = (xt - x) (yf - y) (d - y) (xf - x) + x (yf - y) = xt (yf - y) xt = ((d - y) (xf - x) + x (yf - y)) / (yf - y)
General remarks: The FOV agrees with physical properties of tiles as diamonds and visibility from any point to any point. A diamond is denoted by the left corner of it's encompassing tile. Hero is at (0, 0). Order of processing in the first quadrant rotated by 45 degrees is
45678 123 @
so the first processed diamond is at (-1, 1). The order is similar as for the restrictive shadow casting algorithm and reversed wrt PFOV. The fast moving line when scanning is called the shallow line, and it's the one that delimits the view from the left, while the steep line is on the right, opposite to PFOV. We start scanning from the left.
The PointI
(Enum
representation of Point
) coordinates are cartesian.
The Bump
coordinates are cartesian, translated so that
the hero is at (0, 0) and rotated so that he always
looks at the first (rotated 45 degrees) quadrant. The (Progress
, Distance
)
cordinates coincide with the Bump
coordinates, unlike in PFOV.
Debug: check that the line fits in the upper half-plane.
_debugSteeper :: LineOrdering -> Bump -> Bump -> Bump -> Bool Source #
Debug functions for DFOV:
Debug: calculate steepness for DFOV in another way and compare results.