fixed map
- map is now displayed correctly - camera is adjusted - created ProgramState as TVar for concurrent reading/writing
This commit is contained in:
@ -77,11 +77,11 @@ getTileVertices heights t = let p = (listArray (0,5) hexagon)
|
||||
]
|
||||
|
||||
getHeight :: PlayMap -> TileVertex -> Tile -> Float
|
||||
getHeight pm v t@(_,ty) =
|
||||
getHeight pm v t@(tx,_) =
|
||||
let
|
||||
h = heightLookup pm
|
||||
! tileheight = h t
|
||||
! y = if even ty then 1 else 0
|
||||
! y = if even tx then 0 else -1
|
||||
in
|
||||
case v of
|
||||
VertexNW -> let
|
||||
@ -110,7 +110,7 @@ getHeight pm v t@(_,ty) =
|
||||
in (sw + nw + tileheight) / 3.0
|
||||
|
||||
heightLookup :: PlayMap -> Tile -> Float
|
||||
heightLookup hs t@(x,y) = if inRange (bounds hs) t then h else 0
|
||||
heightLookup hs t = if inRange (bounds hs) t then h else 0
|
||||
where
|
||||
(h,_) = hs ! t
|
||||
|
||||
|
@ -1,9 +1,12 @@
|
||||
{-# LANGUAGE OverloadedStrings #-}
|
||||
module Map.Map
|
||||
|
||||
where
|
||||
|
||||
import System.Random
|
||||
import Data.Array.IArray
|
||||
import Data.Text as T
|
||||
import Prelude as P
|
||||
|
||||
data TileType =
|
||||
Grass
|
||||
@ -19,33 +22,36 @@ type MapEntry = (
|
||||
|
||||
type PlayMap = Array (Int, Int) MapEntry
|
||||
|
||||
testMapTemplate :: [[String]]
|
||||
testMapTemplate = [
|
||||
["~~~~~~~~~~"],
|
||||
["~~SSSSSS~~"],
|
||||
["~SSGGGGS~~"],
|
||||
["~SSGGMMS~~"],
|
||||
["~SGGMMS~~~"],
|
||||
["~SGMMMS~~~"],
|
||||
["~GGGGGGS~~"],
|
||||
["~SGGGGGS~~"],
|
||||
["~~SSSS~~~~"],
|
||||
["~~~~~~~~~~"]
|
||||
-- if writing in ASCII-Format transpose so i,j -> y,x
|
||||
-- row-minor -> row-major
|
||||
testMapTemplate :: [Text]
|
||||
testMapTemplate = T.transpose [
|
||||
"~~~~~~~~~~",
|
||||
"~~SSSSSS~~",
|
||||
"~SSGGGGS~~",
|
||||
"~SSGGMMS~~",
|
||||
"~SGGMMS~~~",
|
||||
"~SGMMMS~~~",
|
||||
"~GGGGGGS~~",
|
||||
"~SGGGGGS~~",
|
||||
"~~SSSS~~~~",
|
||||
"~~~~~~~~~~"
|
||||
]
|
||||
|
||||
testmap :: IO PlayMap
|
||||
testmap = do
|
||||
g <- getStdGen
|
||||
rawMap <- return $ map (parseTemplate (randoms g)) (concat $ concat testMapTemplate)
|
||||
rawMap <- return $ parseTemplate (randoms g) (T.concat testMapTemplate)
|
||||
return $ listArray ((0,0),(9,9)) rawMap
|
||||
|
||||
|
||||
parseTemplate :: [Int] -> Char -> MapEntry
|
||||
parseTemplate (r:_) t =
|
||||
case t of
|
||||
parseTemplate :: [Int] -> Text -> [MapEntry]
|
||||
parseTemplate (r:rs) t =
|
||||
(case T.head t of
|
||||
'~' -> (0, Water)
|
||||
'S' -> (0, Sand)
|
||||
'G' -> ((fromIntegral $ r `mod` 3)/3,Grass)
|
||||
'M' -> ((fromIntegral $ r `mod` 3 + 2)/3, Mountain)
|
||||
'G' -> (fromIntegral (r `mod` 3) / 3,Grass)
|
||||
'M' -> (fromIntegral (r `mod` 3 + 2) / 3, Mountain)
|
||||
_ -> error "invalid template format for map"
|
||||
parseTemplate [] _ = error "out of randoms..."
|
||||
):parseTemplate rs (T.tail t)
|
||||
parseTemplate [] _ = error "out of randoms.."
|
||||
|
Reference in New Issue
Block a user