yx-0.0.4.3: Row-major coordinates

Safe HaskellSafe
LanguageHaskell2010

Data.Geometry.YX

Contents

Description

Bitmap-friendly XY coordinates.

We use YX rather than XY to allow natural row major order (first row sorts before the second, etc.). Note that rows are assumed to go down with y.

Synopsis

Coordinate type

data YX Source #

A 2D coordinate.

Constructors

YX 

Fields

  • y :: !Int

    Y-axis coordinate.

  • x :: !Int

    X-axis coordinate.

Instances
Eq YX Source # 
Instance details

Defined in Data.Geometry.YX

Methods

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

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

Num YX Source #

Integers are converted to their diagonal equivalent (for example 2 becomes YX 2 2).

Instance details

Defined in Data.Geometry.YX

Methods

(+) :: YX -> YX -> YX #

(-) :: YX -> YX -> YX #

(*) :: YX -> YX -> YX #

negate :: YX -> YX #

abs :: YX -> YX #

signum :: YX -> YX #

fromInteger :: Integer -> YX #

Ord YX Source # 
Instance details

Defined in Data.Geometry.YX

Methods

compare :: YX -> YX -> Ordering #

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

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

(>) :: YX -> YX -> Bool #

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

max :: YX -> YX -> YX #

min :: YX -> YX -> YX #

Show YX Source # 
Instance details

Defined in Data.Geometry.YX

Methods

showsPrec :: Int -> YX -> ShowS #

show :: YX -> String #

showList :: [YX] -> ShowS #

Ix YX Source # 
Instance details

Defined in Data.Geometry.YX

Methods

range :: (YX, YX) -> [YX] #

index :: (YX, YX) -> YX -> Int #

unsafeIndex :: (YX, YX) -> YX -> Int

inRange :: (YX, YX) -> YX -> Bool #

rangeSize :: (YX, YX) -> Int #

unsafeRangeSize :: (YX, YX) -> Int

Lattice YX Source # 
Instance details

Defined in Data.Geometry.YX

Methods

(\/) :: YX -> YX -> YX #

(/\) :: YX -> YX -> YX #

Basic steps

up :: YX Source #

Decrement y.

left :: YX Source #

Decrement x.

right :: YX Source #

Increment x.

down :: YX Source #

Increment y.

steps4 :: [YX] Source #

Ordered array of the 4 base steps.

steps8 :: [YX] Source #

Ordered array of the 8 steps (4 base and 4 diagonal).

Box

data Box Source #

A non-empty 2D box.

A box might have zero width or height but will always contain at least one point.

Instances
Eq Box Source # 
Instance details

Defined in Data.Geometry.YX

Methods

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

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

Show Box Source # 
Instance details

Defined in Data.Geometry.YX

Methods

showsPrec :: Int -> Box -> ShowS #

show :: Box -> String #

showList :: [Box] -> ShowS #

Semigroup Box Source #

Since: 0.0.4.1

Instance details

Defined in Data.Geometry.YX

Methods

(<>) :: Box -> Box -> Box #

sconcat :: NonEmpty Box -> Box #

stimes :: Integral b => b -> Box -> Box #

box Source #

Arguments

:: YX

Top-left point.

-> YX

Bottom-right point.

-> Maybe Box 

Constructs a box from its extremities, returning Nothing if the points are not ordered appropriately.

arrayBox :: IArray a e => a YX e -> Maybe Box Source #

Returns the box corresponding to an array, or Nothing if the array is empty.

boundingBox :: Foldable f => f YX -> Maybe Box Source #

Returns the smallest Box containing all input coordinates.

boxBounds :: Box -> (YX, YX) Source #

Returns the box' bounds, (topLeft, bottomRight).

Since: 0.0.4.1

topLeft :: Box -> YX Source #

Returns the top-left most point of the box (i.e. its lattice meet).

bottomRight :: Box -> YX Source #

Returns the bottom-right most point of the box (i.e. its lattice join).

boxHeight :: Box -> Int Source #

Returns the height of the box, always non-negative.

boxWidth :: Box -> Int Source #

Returns the width of the box, always non-negative.

inBox :: YX -> Box -> Bool Source #

Returns whether a given point is within a box.

boxDepth :: Box -> YX -> Maybe Int Source #

Returns the shortest distance of the point to the box' edge, or Nothing if the point is not within the box.

Since: 0.0.4.2

boxRange :: Box -> [YX] Source #

Returns all coordinates within the box, sorted.

boxRows :: Box -> [[YX]] Source #

Returns the box' coordinates, sorted and grouped by row.

boxIntersection :: Box -> Box -> Maybe Box Source #

Intersects two boxes.

boxNeighbors4 :: Box -> YX -> [YX] Source #

Returns 4 neighbors of YX filtered to members of the box.

Since: 0.0.4.0

boxNeighbors8 :: Box -> YX -> [YX] Source #

Returns 8 neighbors of YX filtered to members of the box.

Since: 0.0.4.0

Transformations

data Center Source #

The center of a rotation.

Valid rotations can have either an exact coordinate as center or the top left corner of a coordinate.

Instances
Eq Center Source # 
Instance details

Defined in Data.Geometry.YX

Methods

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

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

Ord Center Source # 
Instance details

Defined in Data.Geometry.YX

Show Center Source # 
Instance details

Defined in Data.Geometry.YX

rotate :: Direction -> Center -> YX -> YX Source #

Rotates a coordinate.

data Axis Source #

Symmetry axis.

Instances
Eq Axis Source # 
Instance details

Defined in Data.Geometry.YX

Methods

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

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

Ord Axis Source # 
Instance details

Defined in Data.Geometry.YX

Methods

compare :: Axis -> Axis -> Ordering #

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

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

(>) :: Axis -> Axis -> Bool #

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

max :: Axis -> Axis -> Axis #

min :: Axis -> Axis -> Axis #

Show Axis Source # 
Instance details

Defined in Data.Geometry.YX

Methods

showsPrec :: Int -> Axis -> ShowS #

show :: Axis -> String #

showList :: [Axis] -> ShowS #

mirror :: Axis -> YX -> YX Source #

Flips coordinates symmetrically on the given axis.

Serialization

byteStringToArray :: IArray a e => (Char -> Maybe e) -> ByteString -> Either String (a YX e) Source #

Parses a newline delimited bytestring into an array.

byteStringToArrayM :: (IArray a e, MonadError String m) => (YX -> Char -> m e) -> ByteString -> m (a YX e) Source #

Parses a newline delimited bytestring into an array in an effectful way.

Since: 0.0.4.0

arrayToByteString :: IArray a e => (e -> Char) -> a YX e -> ByteString Source #

Serializes an array into a bytestring. This function is the reverse of byteStringToArray.