LambdaHack-0.11.0.0: A game engine library for tactical squad ASCII roguelike dungeon crawlers
Safe HaskellNone
LanguageHaskell2010

Game.LambdaHack.Common.Point

Description

Basic operations on 2D points represented as linear offsets.

Synopsis

Documentation

data Point Source #

2D points in cartesian representation. Coordinates grow to the right and down, so that the (0, 0) point is in the top-left corner of the screen. Coordinates are never negative (unlike for Vector) and the X coordinate never reaches the screen width as read from speedupHackXSize.

Constructors

Point 

Fields

Instances

Instances details
Enum Point Source # 
Instance details

Defined in Game.LambdaHack.Common.Point

Eq Point Source # 
Instance details

Defined in Game.LambdaHack.Common.Point

Methods

(==) :: Point -> Point -> Bool #

(/=) :: Point -> Point -> Bool #

Ord Point Source # 
Instance details

Defined in Game.LambdaHack.Common.Point

Methods

compare :: Point -> Point -> Ordering #

(<) :: Point -> Point -> Bool #

(<=) :: Point -> Point -> Bool #

(>) :: Point -> Point -> Bool #

(>=) :: Point -> Point -> Bool #

max :: Point -> Point -> Point #

min :: Point -> Point -> Point #

Show Point Source # 
Instance details

Defined in Game.LambdaHack.Common.Point

Methods

showsPrec :: Int -> Point -> ShowS #

show :: Point -> String #

showList :: [Point] -> ShowS #

Generic Point Source # 
Instance details

Defined in Game.LambdaHack.Common.Point

Associated Types

type Rep Point :: Type -> Type #

Methods

from :: Point -> Rep Point x #

to :: Rep Point x -> Point #

Arbitrary Point Source # 
Instance details

Defined in Game.LambdaHack.Common.Point

Methods

arbitrary :: Gen Point #

shrink :: Point -> [Point] #

Binary Point Source # 
Instance details

Defined in Game.LambdaHack.Common.Point

Methods

put :: Point -> Put #

get :: Get Point #

putList :: [Point] -> Put #

type Rep Point Source # 
Instance details

Defined in Game.LambdaHack.Common.Point

type Rep Point = D1 ('MetaData "Point" "Game.LambdaHack.Common.Point" "LambdaHack-0.11.0.0-inplace" 'False) (C1 ('MetaCons "Point" 'PrefixI 'True) (S1 ('MetaSel ('Just "px") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 X) :*: S1 ('MetaSel ('Just "py") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedStrict) (Rec0 Y)))

type PointI = Int Source #

Enumeration representation of Point.

chessDist :: Point -> Point -> Int Source #

The distance between two points in the chessboard metric.

>>> chessDist (Point 0 0) (Point 0 0)
0
>>> chessDist (Point (-1) 0) (Point 0 0)
1
>>> chessDist (Point (-1) 0) (Point (-1) 1)
1
>>> chessDist (Point (-1) 0) (Point 0 1)
1
>>> chessDist (Point (-1) 0) (Point 1 1)
2
chessDist p1 p2 >= 0
chessDist p1 p2 ^ (2 :: Int) <= euclidDistSq p1 p2

euclidDistSq :: Point -> Point -> Int Source #

Squared euclidean distance between two points.

adjacent :: Point -> Point -> Bool Source #

Checks whether two points are adjacent on the map (horizontally, vertically or diagonally).

bresenhamsLineAlgorithm :: Int -> Point -> Point -> Maybe [Point] Source #

Bresenham's line algorithm generalized to arbitrary starting eps (eps value of 0 gives the standard BLA). Skips the source point and goes through the second point to infinity. Gives Nothing if the points are equal. The target is given as Point, not PointI, to permit aiming out of the level, e.g., to get uniform distributions of directions for explosions close to the edge of the level.

>>> bresenhamsLineAlgorithm 0 (Point 0 0) (Point 0 0)
Nothing
>>> take 3 $ fromJust $ bresenhamsLineAlgorithm 0 (Point 0 0) (Point 1 0)
[(1,0),(2,0),(3,0)]
>>> take 3 $ fromJust $ bresenhamsLineAlgorithm 0 (Point 0 0) (Point 0 1)
[(0,1),(0,2),(0,3)]
>>> take 3 $ fromJust $ bresenhamsLineAlgorithm 0 (Point 0 0) (Point 1 1)
[(1,1),(2,2),(3,3)]

fromTo :: Point -> Point -> [Point] Source #

A list of all points on a straight vertical or straight horizontal line between two points. Fails if no such line exists.

>>> fromTo (Point 0 0) (Point 2 0)
[(0,0),(1,0),(2,0)]

insideP :: (X, Y, X, Y) -> Point -> Bool Source #

Checks that a point belongs to an area.

speedupHackXSize :: PrimArray X Source #

This is a hack to pass the X size of the dungeon, defined in game content, to the Enum instances of Point and Vector. This is already slower and has higher allocation than hardcoding the value, so passing the value explicitly to a generalization of the Enum conversions is out of the question. Perhaps this can be done cleanly and efficiently at link-time via Backpack, but it's probably not supported yet by GHCJS (not verified). For now, we need to be careful never to modify this array, except for setting it at program start before it's used for the first time. Which is easy, because Point is never mentioned in content definitions. The PrimArray has much smaller overhead than IORef and reading from it looks cleaner, hence its use.

Internal operations

bresenhamsLineAlgorithmBegin :: Int -> Point -> Point -> [Point] Source #

Bresenham's line algorithm generalized to arbitrary starting eps (eps value of 0 gives the standard BLA). Includes the source point and goes through the target point to infinity.

>>> take 4 $ bresenhamsLineAlgorithmBegin 0 (Point 0 0) (Point 2 0)
[(0,0),(1,0),(2,0),(3,0)]