imj-base-0.1.0.2: Game engine with geometry, easing, animated text, delta rendering.

Safe HaskellNone
LanguageHaskell2010

Imj.Geo.Discrete

Contents

Synopsis

Discrete geometry types

Direction

data Direction Source #

Discrete directions.

Constructors

Up 
Down 
LEFT 
RIGHT 

Coordinates

data Coords a Source #

Two-dimensional discrete coordinates. We use phantom types Pos, Vel to distinguish positions from speeds.

Constructors

Coords 

Fields

Instances

Eq (Coords a) Source # 

Methods

(==) :: Coords a -> Coords a -> Bool #

(/=) :: Coords a -> Coords a -> Bool #

Ord (Coords a) Source # 

Methods

compare :: Coords a -> Coords a -> Ordering #

(<) :: Coords a -> Coords a -> Bool #

(<=) :: Coords a -> Coords a -> Bool #

(>) :: Coords a -> Coords a -> Bool #

(>=) :: Coords a -> Coords a -> Bool #

max :: Coords a -> Coords a -> Coords a #

min :: Coords a -> Coords a -> Coords a #

Show (Coords a) Source # 

Methods

showsPrec :: Int -> Coords a -> ShowS #

show :: Coords a -> String #

showList :: [Coords a] -> ShowS #

DiscreteDistance (Coords Pos) Source #

 Using bresenham 2d line algorithm.

DiscreteInterpolation (Coords Pos) Source #

 Using bresenham 2d line algorithm.

newtype Coord a Source #

Discrete coordinate.

Constructors

Coord Int 

Instances

Enum (Coord a) Source # 

Methods

succ :: Coord a -> Coord a #

pred :: Coord a -> Coord a #

toEnum :: Int -> Coord a #

fromEnum :: Coord a -> Int #

enumFrom :: Coord a -> [Coord a] #

enumFromThen :: Coord a -> Coord a -> [Coord a] #

enumFromTo :: Coord a -> Coord a -> [Coord a] #

enumFromThenTo :: Coord a -> Coord a -> Coord a -> [Coord a] #

Eq (Coord a) Source # 

Methods

(==) :: Coord a -> Coord a -> Bool #

(/=) :: Coord a -> Coord a -> Bool #

Integral (Coord a) Source # 

Methods

quot :: Coord a -> Coord a -> Coord a #

rem :: Coord a -> Coord a -> Coord a #

div :: Coord a -> Coord a -> Coord a #

mod :: Coord a -> Coord a -> Coord a #

quotRem :: Coord a -> Coord a -> (Coord a, Coord a) #

divMod :: Coord a -> Coord a -> (Coord a, Coord a) #

toInteger :: Coord a -> Integer #

Num (Coord a) Source # 

Methods

(+) :: Coord a -> Coord a -> Coord a #

(-) :: Coord a -> Coord a -> Coord a #

(*) :: Coord a -> Coord a -> Coord a #

negate :: Coord a -> Coord a #

abs :: Coord a -> Coord a #

signum :: Coord a -> Coord a #

fromInteger :: Integer -> Coord a #

Ord (Coord a) Source # 

Methods

compare :: Coord a -> Coord a -> Ordering #

(<) :: Coord a -> Coord a -> Bool #

(<=) :: Coord a -> Coord a -> Bool #

(>) :: Coord a -> Coord a -> Bool #

(>=) :: Coord a -> Coord a -> Bool #

max :: Coord a -> Coord a -> Coord a #

min :: Coord a -> Coord a -> Coord a #

Real (Coord a) Source # 

Methods

toRational :: Coord a -> Rational #

Show (Coord a) Source # 

Methods

showsPrec :: Int -> Coord a -> ShowS #

show :: Coord a -> String #

showList :: [Coord a] -> ShowS #

data Col Source #

Represents a column index (x)

data Row Source #

Represents a row index (y)

Size

data Size Source #

Represents a discrete size (width and height)

Constructors

Size 

Fields

Instances

Eq Size Source # 

Methods

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

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

Show Size Source # 

Methods

showsPrec :: Int -> Size -> ShowS #

show :: Size -> String #

showList :: [Size] -> ShowS #

newtype Length a Source #

Discrete length

Constructors

Length Int 

Instances

Enum (Length a) Source # 

Methods

succ :: Length a -> Length a #

pred :: Length a -> Length a #

toEnum :: Int -> Length a #

fromEnum :: Length a -> Int #

enumFrom :: Length a -> [Length a] #

enumFromThen :: Length a -> Length a -> [Length a] #

enumFromTo :: Length a -> Length a -> [Length a] #

enumFromThenTo :: Length a -> Length a -> Length a -> [Length a] #

Eq (Length a) Source # 

Methods

(==) :: Length a -> Length a -> Bool #

(/=) :: Length a -> Length a -> Bool #

Integral (Length a) Source # 

Methods

quot :: Length a -> Length a -> Length a #

rem :: Length a -> Length a -> Length a #

div :: Length a -> Length a -> Length a #

mod :: Length a -> Length a -> Length a #

quotRem :: Length a -> Length a -> (Length a, Length a) #

divMod :: Length a -> Length a -> (Length a, Length a) #

toInteger :: Length a -> Integer #

Num (Length a) Source # 

Methods

(+) :: Length a -> Length a -> Length a #

(-) :: Length a -> Length a -> Length a #

(*) :: Length a -> Length a -> Length a #

negate :: Length a -> Length a #

abs :: Length a -> Length a #

signum :: Length a -> Length a #

fromInteger :: Integer -> Length a #

Ord (Length a) Source # 

Methods

compare :: Length a -> Length a -> Ordering #

(<) :: Length a -> Length a -> Bool #

(<=) :: Length a -> Length a -> Bool #

(>) :: Length a -> Length a -> Bool #

(>=) :: Length a -> Length a -> Bool #

max :: Length a -> Length a -> Length a #

min :: Length a -> Length a -> Length a #

Real (Length a) Source # 

Methods

toRational :: Length a -> Rational #

Show (Length a) Source # 

Methods

showsPrec :: Int -> Length a -> ShowS #

show :: Length a -> String #

showList :: [Length a] -> ShowS #

data Width Source #

Phantom type for width

data Height Source #

Phantom type for height

toCoords :: Length Height -> Length Width -> Coords Pos Source #

Width and Height to Coords

maxLength :: Size -> Int Source #

Returns the bigger dimension (width or height)

onOuterBorder Source #

Arguments

:: Coords Pos

The coordinates to test

-> Size

The size

-> Maybe Direction

If the coordinates are on the border, returns a Direction pointing away from the region (at the given coordinates).

Tests if a Coords lies on the outer border of a region of a given size, containing (0,0) and positive coordinates.

containsWithOuterBorder :: Coords Pos -> Size -> Bool Source #

Tests if a Coords is contained or on the outer border of a region of a given size, containing (0,0) and positive coordinates.

Segment

data Segment Source #

A segment is a line betwen two discrete coordinates.

It can be materialized as a list of Coords using bresenham

Constructors

Horizontal !(Coord Row) !(Coord Col) !(Coord Col)

Horizontal segment

Vertical !(Coord Col) !(Coord Row) !(Coord Row)

Vertical segment

Oblique !(Coords Pos) !(Coords Pos)

Oblique segment

Instances

mkSegment Source #

Arguments

:: Coords Pos

Segment start

-> Coords Pos

Segment end

-> Segment 

Bresenham line algorithm

bresenhamLength :: Coords Pos -> Coords Pos -> Int Source #

Returns the bresenham 2d distance between two coordinates.

bresenham :: Segment -> [Coords Pos] Source #

Bresenham 2d algorithm, slightly optimized for horizontal and vertical lines.

Reexports

data Pos Source #

 Phantom type : position

Instances

data Vel Source #

Phantom type : velocity

Construct Segment

mkSegmentByExtendingWhile Source #

Arguments

:: Coords Pos

start of the segment

-> Direction

Direction in which to extend

-> (Coords Pos -> Bool)

Continue extension while this functions returns True.

-> Segment 

changeSegmentLength :: Int -> Segment -> Segment Source #

Modify the end of the segment to reach the given length

Use Segment

extremities :: Segment -> (Coords Pos, Coords Pos) Source #

Returns the start and end coordinates.

segmentContains Source #

Arguments

:: Coords Pos

The coordinates to test

-> Segment 
-> Maybe Int

Nothing if the coordinate is not contained, else Just the distance from segment start.

Returns the distance from segment start

Construct Coords

coordsForDirection :: Direction -> Coords a Source #

Returns the coordinates that correspond to one step in the given direction.

Use Coords

diffCoords Source #

Arguments

:: Coords a

a

-> Coords a

b

-> Coords a

a - b

Returns a - b

sumCoords Source #

Arguments

:: Coords a

a

-> Coords a

b

-> Coords a

a + b

Returns a + b

sumPosSpeed :: Coords Pos -> Coords Vel -> Coords Pos Source #

Assumes that we integrate over one game step.

Returns a + b

move Source #

Arguments

:: Int

Take that many steps

-> Direction

In that direction

-> Coords a

From these coordinates

-> Coords a 

translate' Source #

Arguments

:: Length Height

The height to add

-> Length Width

The width to add

-> Coords Pos 
-> Coords Pos 

Translate by a given height and width.

translateInDir :: Direction -> Coords a -> Coords a Source #

Translate of 1 step in a given direction.

Discrete algorithms

Bresenham

The 2d version, bresenham, allows to draw a line on a 2d grid.

The 3d version, bresenham3, allows to interpolate discrete colors in RGB space.

bla :: (Int, Int) -> (Int, Int) -> [(Int, Int)] Source #

Bresenham's line algorithm. Includes the first point and goes through the second to infinity.

bresenham3Length :: (Int, Int, Int) -> (Int, Int, Int) -> Int Source #

Returns the 3D bresenham length between two 3D coordinates.

bresenham3 :: (Int, Int, Int) -> (Int, Int, Int) -> [(Int, Int, Int)] Source #

3D version of the bresenham algorithm.

List resampling

Typically, resampleWithExtremities will be used on the result of bresenham to over-sample the produced line.

resampleWithExtremities Source #

Arguments

:: [a]

Input

-> Int

\( n \) : input length. It is expected that \( 0 <= n <= \) length input

-> Int

\( m \) : output length. It is expected that \( 0 <= m \).

-> [a]

Output :

  • when \( m < n \), it is a downsampled version of the input,
  • when \( m > n \), it is an upsampled version of the input.

Resamples a list, using the analogy where a list is seen as a uniform sampling of a geometrical segment.

With a uniform sampling strategy, for an input of length \( n \), and a desired output of length \( m \):

  • Regular samples are repeated \( r = \lfloor {m \over n} \rfloor \) times.
  • Over-represented samples are repeated \( r + 1 \) times.

If \( m' \) is the number of over-represented samples,

\[ \begin{alignedat}{2} m &= r*n + m' \\ \implies \quad m' &= m - r*n \end{alignedat} \]

We can chose over-represented samples in at least two different ways:

  • Even spread :

    • Given a partition of the input continuous interval \( [\,0, length]\, \) in \( m' \) equal-length intervals, the over-represented samples are located at the (floored) centers of these intervals.
    • More precisely, over-represented samples indexes are:

      \[ \biggl\{ a + \Bigl\lfloor {1 \over 2} + { n-1-a \over m-1 } * s \Bigl\rfloor \mid s \in [\,0\,..\,m'-1] \;,\; a = {1 \over 2} * {n \over m'} \biggl\} \]

    • Example : for a length 5 input, and 2 over-represented samples:
                 input samples:   -----
    
      over-represented samples:    - -
    
  • "Even with extremities" spread:

    • The first and last over-represented samples match with an input extremity. The rest of the over-represented samples are positionned "regularly" in-between the first and last. An exception is made when there is only one over-represented sample : in that case it is placed in the middle.
    • More precisely, over-represented samples indexes are:

      \[ if \; m' == 1 : \biggl\{ \Bigl\lfloor {n-1 \over 2} \Bigl\rfloor \biggl\} \]

      \[ otherwise : \biggl\{ \Bigl\lfloor {1 \over 2} + {n-1 \over m'-1}*s \Bigl\rfloor \mid s \in [\,0,m'-1]\, \biggl\} \]

    • Example : for a length 5 input, and 2 over-represented samples:
                 input samples:   -----
    
      over-represented samples:   -   -
    

    As its name suggests, this function uses the "even with extremities" spread.

    For clarity, the variable names used in the code match the ones in the documentation.