| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Game.TCOD.Heightmap
- heightmapNew :: Int -> Int -> IO TCODHeightMap
- heightmapDelete :: TCODHeightMap -> IO ()
- heightmapGetValue :: TCODHeightMap -> Int -> Int -> IO Double
- heightmapGetInterpolatedValue :: TCODHeightMap -> Double -> Double -> IO Double
- heightmapSetValue :: TCODHeightMap -> Int -> Int -> Double -> IO ()
- heightmapGetSlope :: TCODHeightMap -> Int -> Int -> IO Double
- heightmapGetNormal :: TCODHeightMap -> Double -> Double -> Double -> IO (Double, Double, Double)
- heightmapCountCells :: TCODHeightMap -> Double -> Double -> IO Int
- heightmapHasLandOnBorder :: TCODHeightMap -> Double -> IO Bool
- heightmapGetMinMax :: TCODHeightMap -> IO (Double, Double)
- heightmapCopy :: TCODHeightMap -> TCODHeightMap -> IO ()
- heightmapAdd :: TCODHeightMap -> Double -> IO ()
- heightmapScale :: TCODHeightMap -> Double -> IO ()
- heightmapClamp :: TCODHeightMap -> Double -> Double -> IO ()
- heightmapNormalize :: TCODHeightMap -> Double -> Double -> IO ()
- heightmapClear :: TCODHeightMap -> IO ()
- heightmapLerp :: TCODHeightMap -> TCODHeightMap -> TCODHeightMap -> Double -> IO ()
- heightmapAddHm :: TCODHeightMap -> TCODHeightMap -> TCODHeightMap -> IO ()
- heightmapMultiplyHm :: TCODHeightMap -> TCODHeightMap -> TCODHeightMap -> IO ()
- heightmapAddHill :: TCODHeightMap -> Double -> Double -> Double -> Double -> IO ()
- heightmapDigHill :: TCODHeightMap -> Double -> Double -> Double -> Double -> IO ()
- data DigBezier = DigBezier {- bezierP1 :: (Int, Int)
- bezierP2 :: (Int, Int)
- bezierP3 :: (Int, Int)
- bezierP4 :: (Int, Int)
- bezierStartRadius :: !Double
- bezierStartDepth :: !Double
- bezierEndRadius :: !Double
- bezierEndDepth :: !Double
 
- heightmapDigBezier :: TCODHeightMap -> DigBezier -> IO ()
- heightmapRainErosion :: TCODHeightMap -> Int -> Double -> Double -> TCODRandom -> IO ()
- heightmapKernelTransform :: TCODHeightMap -> Int -> Vector Int -> Vector Int -> Vector Double -> Double -> Double -> IO ()
- heightmapAddVoronoi :: TCODHeightMap -> Int -> Vector Double -> TCODRandom -> IO ()
- heightmapMidPointDisplacement :: TCODHeightMap -> TCODRandom -> Double -> IO ()
- heightmapAddFbm :: TCODHeightMap -> TCODNoise -> Double -> Double -> Double -> Double -> Double -> Double -> Double -> IO ()
- heightmapScaleFbm :: TCODHeightMap -> TCODNoise -> Double -> Double -> Double -> Double -> Double -> Double -> Double -> IO ()
- heightmapIslandify :: TCODHeightMap -> Double -> TCODRandom -> IO ()
Documentation
heightmapNew :: Int -> Int -> IO TCODHeightMap Source #
Allocate new heightmap with given sizes
heightmapDelete :: TCODHeightMap -> IO () Source #
Destroy inner buffers of heightmap
heightmapGetValue :: TCODHeightMap -> Int -> Int -> IO Double Source #
Get value of heightmap at given point
heightmapGetInterpolatedValue :: TCODHeightMap -> Double -> Double -> IO Double Source #
This function returns the interpolated height at non integer coordinates.
heightmapSetValue :: TCODHeightMap -> Int -> Int -> Double -> IO () Source #
Once the heightmap has been created, you can do some basic operations on the values inside it.
heightmapGetSlope :: TCODHeightMap -> Int -> Int -> IO Double Source #
This function returns the slope between 0 and PI/2 at given coordinates.
Arguments
| :: TCODHeightMap | |
| -> Double | x | 
| -> Double | y | 
| -> Double | Water level (default 0). The map height is clamped at waterLevel so that the sea is flat. | 
| -> IO (Double, Double, Double) | 
This function returns the map normal at given coordinates.
Arguments
| :: TCODHeightMap | |
| -> Double | min | 
| -> Double | max | 
| -> IO Int | 
Count the map cells inside a height range
This function returns the number of map cells which value is between min and max.
heightmapHasLandOnBorder Source #
Arguments
| :: TCODHeightMap | |
| -> Double | Return true only if no border cell is > waterLevel. | 
| -> IO Bool | 
Check if the map is an island
This function checks if the cells on the map border are below a certain height.
heightmapGetMinMax :: TCODHeightMap -> IO (Double, Double) Source #
Get the map min and max values
heightmapCopy :: TCODHeightMap -> TCODHeightMap -> IO () Source #
Copy contents of heightmap from one to another
heightmapAdd :: TCODHeightMap -> Double -> IO () Source #
Adding a float value to all cells
heightmapScale :: TCODHeightMap -> Double -> IO () Source #
Clamping all values
heightmapClamp :: TCODHeightMap -> Double -> Double -> IO () Source #
Clamping all values
heightmapNormalize :: TCODHeightMap -> Double -> Double -> IO () Source #
The whole heightmap is translated and scaled so that the lowest cell value becomes min and the highest cell value becomes max
heightmapClear :: TCODHeightMap -> IO () Source #
Resetting all values to 0.0
Arguments
| :: TCODHeightMap | First heightmap in the lerp operation. | 
| -> TCODHeightMap | Second heightmap in the lerp operation. | 
| -> TCODHeightMap | Where to store result | 
| -> Double | coef lerp coefficient. For each cell in the destination map, value = a.value + (b.value - a.value) * coef | 
| -> IO () | 
Doing a lerp operation between two heightmaps
Arguments
| :: TCODHeightMap | First heightmap in the addition operation. | 
| -> TCODHeightMap | Second heightmap in the addition operation. | 
| -> TCODHeightMap | Where to store result | 
| -> IO () | 
Adding two heightmaps
Arguments
| :: TCODHeightMap | First heightmap in the addition operation. | 
| -> TCODHeightMap | Second heightmap in the addition operation. | 
| -> TCODHeightMap | Where to store result | 
| -> IO () | 
Multiplying values of two heightmaps
Add hills
This function adds a hill (a half spheroid) at given position.
Digg hills
This function digs a hill (a half spheroid) at given position.
Helper struct for heightmapDigBezier
heightmapDigBezier :: TCODHeightMap -> DigBezier -> IO () Source #
Digg hills
This function digs a hill (a half spheroid) at given position.
Arguments
| :: TCODHeightMap | |
| -> Int | number of drops. Number of rain drops to simulate. Should be at least width * height. | 
| -> Double | erosion coeff. Amount of ground eroded on the drop's path. | 
| -> Double | sedimantation coeff. Amount of ground deposited when the drops stops to flow | 
| -> TCODRandom | RNG to use, NULL for default generator. | 
| -> IO () | 
Simulate rain erosion
This function simulates the effect of rain drops on the terrain, resulting in erosion patterns.
heightmapKernelTransform Source #
Arguments
| :: TCODHeightMap | |
| -> Int | Kernel size. Number of neighbour cells involved. dx, dy and weights should be the exact same size of the value. | 
| -> Vector Int | dx. Array of kernelSize cells coordinates. The coordinates are relative to the current cell (0,0) is current cell, (-1,0) is west cell, (0,-1) is north cell, (1,0) is east cell, (0,1) is south cell, ... | 
| -> Vector Int | dy | 
| -> Vector Double | weights. Array of kernelSize cells weight. The value of each neighbour cell is scaled by its corresponding weight | 
| -> Double | min level. The transformation is only applied to cells which value is >= minLevel. | 
| -> Double | max level. The transformation is only applied to cells which value is <= maxLevel. | 
| -> IO () | 
Do a generic transformation
This function allows you to apply a generic transformation on the map, so that each resulting cell value is the weighted sum of several neighbour cells. This can be used to smooth/sharpen the map. See examples below for a simple horizontal smoothing kernel : replace value(x,y) with 0.33*value(x-1,y) + 0.33*value(x,y) + 0.33*value(x+1,y).
To do this, you need a kernel of size 3 (the sum involves 3 surrounding cells).
Arguments
| :: TCODHeightMap | |
| -> Int | Number of Voronoi sites. | 
| -> Vector Double | coeff The distance to each site is scaled by the corresponding coef. Closest site : coef[0], second closest site : coef[1], ... | 
| -> TCODRandom | RNG to use, NULL for default generator. | 
| -> IO () | 
Add a Voronoi diagram
This function adds values from a Voronoi diagram to the map.
heightmapMidPointDisplacement Source #
Arguments
| :: TCODHeightMap | |
| -> TCODRandom | Random number generation to use, or NULL/0 to use the default one. | 
| -> Double | roughness | 
| -> IO () | 
Generate a map with mid-point displacement
This algorithm generates a realistic fractal heightmap using the href="http://en.wikipedia.org/wiki/Diamond-square_algorithm"diamond-square/a (or random midpoint displacement) algorithm. The roughness range should be comprised between 0.4 and 0.6. The image below show the same map with roughness varying from 0.4 to 0.6. src="midpoint.png" / It's also a good habit to normalize the map after using this algorithm to avoid unexpected heights.
Arguments
| :: TCODHeightMap | |
| -> TCODNoise | The 2D noise to use. | 
| -> Double | mult x. mulx, muly addx, addy The noise coordinate for map cell (x,y) are (x + addx)*mulx width , (y + addy)*muly / height. Those values allow you to scale and translate the noise function over the heightmap. | 
| -> Double | mult y | 
| -> Double | add x | 
| -> Double | add y | 
| -> Double | octaves. Number of octaves in the fbm sum. | 
| -> Double | delta. The value added to the heightmap is delta + noise * scale. | 
| -> Double | scale is between -1.0 and 1.0 | 
| -> IO () | 
This function adds values from a simplex fbm function to the map.
Arguments
| :: TCODHeightMap | |
| -> TCODNoise | The 2D noise to use. | 
| -> Double | mult x. mulx, muly addx, addy The noise coordinate for map cell (x,y) are (x + addx)*mulx width , (y + addy)*muly / height. Those values allow you to scale and translate the noise function over the heightmap. | 
| -> Double | mult y | 
| -> Double | add x | 
| -> Double | add y | 
| -> Double | octaves. Number of octaves in the fbm sum. | 
| -> Double | delta. The value added to the heightmap is delta + noise * scale. | 
| -> Double | scale is between -1.0 and 1.0 | 
| -> IO () | 
This function adds values from a simplex fbm function to the map.
Arguments
| :: TCODHeightMap | |
| -> Double | sea level | 
| -> TCODRandom | Random number generation to use, or NULL/0 to use the default one. | 
| -> IO () | 
Lowers the terrain near the heightmap borders