about summary refs log tree commit diff
path: root/src/Xanthous/Generators/CaveAutomata.hs
diff options
context:
space:
mode:
authorGriffin Smith <root@gws.fyi>2019-12-30T16·31-0500
committerGriffin Smith <root@gws.fyi>2019-12-30T16·31-0500
commite76567b9e776070812838828d8de8220c2a461e7 (patch)
tree40a801de9684b39a3258f4f33f121b14dd407a64 /src/Xanthous/Generators/CaveAutomata.hs
parent6f427fe4d6ba9a03f122d15839298040a7cfb925 (diff)
Add dungeon level generation
Add a dungeon level generator, which:

1. generates an infinite sequence of rectangular rooms within the
   dimensions of the level
2. removes any duplicates from that sequence
3. Generates a graph from the delaunay triangulation of the centerpoints
   of those rooms
4. Generates the minimum-spanning-tree of that delaunay triangulation,
   with weights given by line length in points
5. Adds back a subset (default 10-15%) of edges from the delaunay
   triangulation to the graph
6. Uses the resulting graph to draw corridors between the rooms, using a
   random point on the near edge of each room to pick the points of the
   corridors
Diffstat (limited to 'src/Xanthous/Generators/CaveAutomata.hs')
-rw-r--r--src/Xanthous/Generators/CaveAutomata.hs31
1 files changed, 13 insertions, 18 deletions
diff --git a/src/Xanthous/Generators/CaveAutomata.hs b/src/Xanthous/Generators/CaveAutomata.hs
index e885f4ed1a..5a7c081d03 100644
--- a/src/Xanthous/Generators/CaveAutomata.hs
+++ b/src/Xanthous/Generators/CaveAutomata.hs
@@ -2,23 +2,25 @@
 {-# LANGUAGE ViewPatterns #-}
 {-# LANGUAGE RecordWildCards #-}
 {-# LANGUAGE TemplateHaskell #-}
-
+--------------------------------------------------------------------------------
 module Xanthous.Generators.CaveAutomata
   ( Params(..)
   , defaultParams
   , parseParams
   , generate
   ) where
-
-import Xanthous.Prelude
-import Control.Monad.Random (RandomGen, runRandT)
-import Data.Array.ST
-import Data.Array.Unboxed
+--------------------------------------------------------------------------------
+import           Xanthous.Prelude
+import           Control.Monad.Random (RandomGen, runRandT)
+import           Data.Array.ST
+import           Data.Array.Unboxed
 import qualified Options.Applicative as Opt
-
-import Xanthous.Util (between)
-import Xanthous.Data (Dimensions, width, height)
-import Xanthous.Generators.Util
+--------------------------------------------------------------------------------
+import           Xanthous.Util (between)
+import           Xanthous.Util.Optparse
+import           Xanthous.Data (Dimensions, width, height)
+import           Xanthous.Generators.Util
+--------------------------------------------------------------------------------
 
 data Params = Params
   { _aliveStartChance :: Double
@@ -70,13 +72,6 @@ parseParams = Params
       <> Opt.metavar "STEPS"
       )
   where
-    readWithGuard predicate errmsg = do
-      res <- Opt.auto
-      unless (predicate res)
-        $ Opt.readerError
-        $ errmsg res
-      pure res
-
     parseChance = readWithGuard
       (between 0 1)
       $ \res -> "Chance must be in the range [0,1], got: " <> show res
@@ -85,7 +80,7 @@ parseParams = Params
       (between 0 8)
       $ \res -> "Neighbors must be in the range [0,8], got: " <> show res
 
-generate :: RandomGen g => Params -> Dimensions -> g -> UArray (Word, Word) Bool
+generate :: RandomGen g => Params -> Dimensions -> g -> Cells
 generate params dims gen
   = runSTUArray
   $ fmap fst