screeps-purescript-bot/src/Shimmy/Spawning.purs

74 lines
2.3 KiB
Plaintext

module Shimmy.Spawning where
import Prelude
import Data.Either (Either(..), hush)
import Data.Int (decimal, fromString, toStringAs)
import Data.Maybe (Maybe(..), fromMaybe)
import Effect (Effect)
import Effect.Console (log)
import Foreign.Object as F
import Screeps.Const (pCarry, pMove, pWork)
import Screeps.Game as Game
import Screeps.Memory as Memory
import Screeps.Room (room, setRoomMem)
import Screeps.Spawn (spawnStoreEnergy)
import Screeps.Types (BodyPartType(..), Creep, GameGlobal, Role(..), Spawn)
getLastId :: Memory.MemoryGlobal -> Effect (Maybe String)
getLastId memory = do
res <- Memory.get memory "last_id"
pure (join $ hush res)
decodeId :: Maybe String -> Effect Int
decodeId str = do
case str of
Nothing -> pure 0
Just int -> pure (fromMaybe 0 (fromString int))
encodeId :: Effect Int -> Effect String
encodeId int = do
int <#> (toStringAs decimal)
incrementId :: Int -> Effect Int
incrementId int = pure $ int + 1
namify :: Effect Int -> Effect String
namify int = do
(pure "shimmy") <> encodeId int
getCreepName :: Memory.MemoryGlobal -> Effect String
getCreepName memory = do
currentMin <- getLastId memory
nextMin <- decodeId currentMin >>= incrementId
creepName <- namify $ pure nextMin
(encodeId $ pure nextMin) >>= Memory.set memory "last_id"
pure creepName
spawnCreep :: Spawn -> Array BodyPartType -> String -> Role -> Effect Unit
spawnCreep spawn parts name role = do
res <- Game.rawSpawnCreep spawn parts name role
case res of
Left err -> log $ show err
Right str -> log $ str <> " spawned"
createIdleCreep :: Spawn -> Memory.MemoryGlobal -> Array BodyPartType -> Effect Unit
createIdleCreep spawn memory body = do
name <- getCreepName memory
spawnCreep spawn body name RoleIdle
doSpawnCheck :: Spawn -> Int -> Memory.MemoryGlobal -> Effect Unit
doSpawnCheck spawn numCreeps memory = if availableEnergy > 250 && numCreeps < 3 then do
createIdleCreep spawn memory [pWork, pCarry, pMove, pMove]
else pure unit
where availableEnergy = spawnStoreEnergy spawn
initSpawn :: F.Object Creep -> GameGlobal -> Memory.MemoryGlobal -> Effect Unit
initSpawn hash game mem = do
let spawns = Game.spawns game
spawn1 = F.lookup "Spawn1" spawns
case spawn1 of
Nothing -> pure unit
Just s1 -> do
let r = room s1
setRoomMem r 0 0