about summary refs log tree commit diff
path: root/src/Xanthous/Generators.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Xanthous/Generators.hs')
-rw-r--r--src/Xanthous/Generators.hs30
1 files changed, 23 insertions, 7 deletions
diff --git a/src/Xanthous/Generators.hs b/src/Xanthous/Generators.hs
index c266742b05..740b39c5f0 100644
--- a/src/Xanthous/Generators.hs
+++ b/src/Xanthous/Generators.hs
@@ -1,14 +1,19 @@
 {-# LANGUAGE GADTs #-}
-
+--------------------------------------------------------------------------------
 module Xanthous.Generators where
-
-import Xanthous.Prelude
-import Data.Array.Unboxed
-import System.Random (RandomGen)
+--------------------------------------------------------------------------------
+import           Xanthous.Prelude
+import           Data.Array.Unboxed
+import           System.Random (RandomGen)
 import qualified Options.Applicative as Opt
-
+--------------------------------------------------------------------------------
 import qualified Xanthous.Generators.CaveAutomata as CaveAutomata
-import Xanthous.Data (Dimensions)
+import           Xanthous.Generators.Util
+import           Xanthous.Data (Dimensions, Position(Position))
+import           Xanthous.Data.EntityMap (EntityMap)
+import qualified Xanthous.Data.EntityMap as EntityMap
+import           Xanthous.Entities.Environment
+--------------------------------------------------------------------------------
 
 data Generator = CaveAutomata
   deriving stock (Show, Eq)
@@ -52,3 +57,14 @@ showCells arr =
       row r = foldMap (showCell . (, r)) [minX..maxX]
       rows = row <$> [minY..maxY]
   in intercalate "\n" rows
+
+cellsToWalls :: UArray (Word, Word) Bool -> EntityMap Wall
+cellsToWalls cells = foldl' maybeInsertWall mempty . assocs $ cells
+  where
+    maybeInsertWall em (pos@(x, y), True)
+      | not (surroundedOnAllSides pos) =
+        let x' = fromIntegral x
+            y' = fromIntegral y
+        in EntityMap.insertAt (Position x' y') Wall em
+    maybeInsertWall em _ = em
+    surroundedOnAllSides pos = numAliveNeighbors cells pos == 8