- wood 1
- avoid - build archers and knights
This commit is contained in:
5
code_royal/.vscode/tasks.json
vendored
5
code_royal/.vscode/tasks.json
vendored
@@ -15,12 +15,13 @@
|
||||
"group": {
|
||||
"kind": "build",
|
||||
"isDefault": true
|
||||
}
|
||||
},
|
||||
"problemMatcher": []
|
||||
},
|
||||
{
|
||||
"label": "build_purescript_old",
|
||||
"type": "shell",
|
||||
"command": "spago bundle-app && sed -i \"$ d\" index.js && uglifyjs index.js --compress --mangle --output index.js",
|
||||
"command": "spago bundle-app && uglifyjs index.js --compress --mangle --output index.js",
|
||||
"group": "build"
|
||||
}
|
||||
]
|
||||
|
||||
@@ -3,13 +3,7 @@ Welcome to a Spago project!
|
||||
You can edit this file as you like.
|
||||
-}
|
||||
{ name = "code_royal"
|
||||
, dependencies =
|
||||
[ "arrays"
|
||||
, "console"
|
||||
, "effect"
|
||||
, "integers"
|
||||
, "math"
|
||||
]
|
||||
, dependencies = [ "arrays", "console", "effect", "integers", "math", "random" ]
|
||||
, packages = ./packages.dhall
|
||||
, sources = [ "src/**/*.purs", "test/**/*.purs" ]
|
||||
}
|
||||
|
||||
@@ -3,8 +3,9 @@ module Lib where
|
||||
import Prelude
|
||||
|
||||
import Data.Int (fromNumber, pow, toNumber)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Maybe (fromJust)
|
||||
import Math as M
|
||||
import Partial.Unsafe (unsafePartial)
|
||||
import Range (Area(..), Pos(..), Range(..))
|
||||
|
||||
maxPos :: Pos -> Int
|
||||
@@ -20,10 +21,10 @@ getMiddlePos (Area (Range x1 x2) (Range y1 y2)) = Pos x y
|
||||
y = abs (y1 + y2) / 2
|
||||
|
||||
abs :: Int -> Int
|
||||
abs x = fromMaybe 0 $ fromNumber $ M.abs $ toNumber x
|
||||
abs x = unsafePartial $ fromJust $ fromNumber $ M.abs $ toNumber x
|
||||
|
||||
sqrt :: Int -> Int
|
||||
sqrt x = fromMaybe 0 $ fromNumber $ M.sqrt $ toNumber x
|
||||
sqrt x = unsafePartial $ fromJust $ fromNumber $ M.floor $ M.sqrt $ toNumber x
|
||||
|
||||
dist :: forall a b. { x :: Int, y :: Int | a } -> { x :: Int, y :: Int | b } -> Int
|
||||
dist p1 p2 = sqrt $ a2 + b2
|
||||
|
||||
@@ -2,14 +2,15 @@ module Main where
|
||||
|
||||
import Prelude
|
||||
|
||||
import Data.Array (any, drop, filter, head, length, sortBy)
|
||||
import Control.MonadZero (guard)
|
||||
import Data.Array (any, filter, foldl, head, length, reverse, sortBy, (!!))
|
||||
import Data.Maybe (Maybe(..), fromJust)
|
||||
import Effect (Effect)
|
||||
import Effect.Console (log, error)
|
||||
import GameInput (Site, Minion, SiteInfo, parseInitInput, parseInput)
|
||||
import Lib (dist, toPos)
|
||||
import Effect.Random (randomInt)
|
||||
import GameInput (Minion, Site, SiteInfo, ProtoSite, parseInitInput, parseInput)
|
||||
import Lib (dist)
|
||||
import Partial.Unsafe (unsafePartial)
|
||||
import Range (Pos(..))
|
||||
|
||||
main :: Effect Unit
|
||||
main = do
|
||||
@@ -20,36 +21,120 @@ main = do
|
||||
loop :: Int -> Array SiteInfo -> Effect Unit
|
||||
loop numSites siteInfo = do
|
||||
input <- parseInput numSites
|
||||
|
||||
|
||||
let touchedSite = if input.touchedSite == -1
|
||||
then Nothing
|
||||
else Just input.touchedSite
|
||||
|
||||
loop' numSites input.gold touchedSite siteInfo input.sites input.units
|
||||
loop' numSites input.gold touchedSite (combinedSites input.sites) input.units
|
||||
where
|
||||
-- combine sites with siteInfo
|
||||
combinedSites :: Array ProtoSite -> Array Site
|
||||
combinedSites sites = do
|
||||
protoS <- sites
|
||||
infoS <- siteInfo
|
||||
guard $ protoS.id == infoS.id
|
||||
pure { id: protoS.id
|
||||
, structureType: protoS.structureType
|
||||
, owner: protoS.owner
|
||||
, param1: protoS.param1
|
||||
, param2: protoS.param2
|
||||
, x: infoS.x
|
||||
, y: infoS.y
|
||||
, radius: infoS.radius
|
||||
}
|
||||
|
||||
loop' :: Int -> Int -> Maybe Int -> Array SiteInfo -> Array Site -> Array Minion -> Effect Unit
|
||||
loop' numSites gold touchedSite siteInfo sites units = do
|
||||
error $ "Sites: " <> show sites
|
||||
error $ "SiteI: " <> show siteInfo
|
||||
loop' :: Int -> Int -> Maybe Int -> Array Site -> Array Minion -> Effect Unit
|
||||
loop' numSites gold touchedSite sites units = do
|
||||
-- error $ "Free sites: " <> (show $ map (\s -> s.id) freeSites)
|
||||
-- error $ "Near sites: " <> (show $ map (\s -> s.id) nearSites)
|
||||
|
||||
let queen = unsafePartial $ fromJust $ head $ filter (\u -> u.unitType == -1 && u.owner == 0) units
|
||||
let siteInfo' = sortBy (compareSiteInfoDist queen) siteInfo
|
||||
if (length $ friendlySites sites) > 3
|
||||
then log avoid
|
||||
else case head $ nearSites queen sites of
|
||||
Just sInfo -> do
|
||||
let typ = if hasKnightsBarrack sites then 1 else 0
|
||||
log $ build sInfo typ
|
||||
Nothing -> do
|
||||
log avoid
|
||||
|
||||
case head siteInfo' of
|
||||
Just sInfo -> do
|
||||
log $ build sInfo
|
||||
log $ "TRAIN " <> show sInfo.id
|
||||
Nothing -> do
|
||||
log $ "WAIT"
|
||||
log $ "TRAIN"
|
||||
t <- trainAll gold sites
|
||||
log $ t
|
||||
|
||||
loop numSites siteInfo
|
||||
loop numSites (toSiteInfo <$> sites)
|
||||
where
|
||||
avoid :: String
|
||||
avoid = case nearestEnemy of
|
||||
Just enemy -> "MOVE " <> show (site enemy).x <> " " <> show (site enemy).y
|
||||
Nothing -> "MOVE 0 0"
|
||||
where site enemy = unsafePartial $ fromJust $ head $
|
||||
sortBy (\s1 s2 -> compare (dist enemy s2) (dist enemy s1)) (friendlySites sites)
|
||||
|
||||
compareSiteInfoDist :: Minion -> SiteInfo -> SiteInfo -> Ordering
|
||||
queen :: Minion
|
||||
queen = unsafePartial $ fromJust $ head $ filter (\u -> u.unitType == -1 && u.owner == 0) units
|
||||
|
||||
enemyQueen :: Minion
|
||||
enemyQueen = unsafePartial $ fromJust $ head $ filter (\u -> u.unitType == -1 && u.owner == 1) units
|
||||
|
||||
-- nearest non-queen enemy
|
||||
nearestEnemy :: Maybe Minion
|
||||
nearestEnemy = head $ filter (\u -> u.unitType /= -1 && isEnemy u) units
|
||||
|
||||
-- TODO: make pure
|
||||
trainAll :: Int -> Array Site -> Effect String
|
||||
trainAll gold sites = do
|
||||
randBarrack <- randomBarrack
|
||||
choose <- randomInt 1 100
|
||||
let barrack = if gold > 100 && choose < 23 then knightBarrack else randBarrack
|
||||
pure $ foldl siteToIds "TRAIN" barrack
|
||||
where
|
||||
siteToIds acc site = acc <> " " <> show site.id
|
||||
knightBarrack = case head $ knightBarracks sites of
|
||||
Just barrack -> [barrack]
|
||||
Nothing -> []
|
||||
randomBarrack = do
|
||||
let ownBarracks = filter isOwn $ barracks sites
|
||||
rand <- randomInt 0 $ length ownBarracks
|
||||
case ownBarracks !! rand of
|
||||
Just barrack -> pure [barrack]
|
||||
Nothing -> pure []
|
||||
|
||||
freeSites :: Array Site -> Array Site
|
||||
freeSites = filter (\s -> s.owner == -1)
|
||||
|
||||
friendlySites :: Array Site -> Array Site
|
||||
friendlySites = filter (\s -> s.owner == 0)
|
||||
|
||||
nearSites :: Minion -> Array Site -> Array Site
|
||||
nearSites unit sites = sortBy (compareSiteInfoDist unit) (freeSites sites)
|
||||
|
||||
hasKnightsBarrack :: Array Site -> Boolean
|
||||
hasKnightsBarrack sites = any (\s -> s.param2 == 0) (friendlySites sites)
|
||||
|
||||
knightBarracks :: Array Site -> Array Site
|
||||
knightBarracks sites = filter (\s -> s.param2 == 0) (friendlySites sites)
|
||||
|
||||
toSiteInfo :: Site -> SiteInfo
|
||||
toSiteInfo s = { id: s.id, x: s.x, y: s.y, radius: s.radius }
|
||||
|
||||
compareSiteInfoDist :: Minion -> Site -> Site -> Ordering
|
||||
compareSiteInfoDist u s1 s2 = compare (dist s1 u) (dist s2 u)
|
||||
|
||||
build :: forall e. { id :: Int | e } -> String
|
||||
build s = "BUILD " <> show s.id <> " BARRACKS-ARCHER"
|
||||
build :: forall e. { id :: Int | e } -> Int -> String
|
||||
build s typ = "BUILD " <> show s.id <> " BARRACKS-" <> t
|
||||
where t = if typ == 0 then "KNIGHT" else "ARCHER"
|
||||
|
||||
isOwn :: forall a. { owner :: Int | a } -> Boolean
|
||||
isOwn = owner 0
|
||||
|
||||
isEnemy :: forall a. { owner :: Int | a } -> Boolean
|
||||
isEnemy = owner 1
|
||||
|
||||
owner :: Int -> forall a. { owner :: Int | a } -> Boolean
|
||||
owner oId r = r.owner == oId
|
||||
|
||||
barracks :: Array Site -> Array Site
|
||||
barracks sites = filter (\b -> b.structureType == 2) sites
|
||||
|
||||
moveToPos :: forall e. { x :: Int, y :: Int | e } -> String
|
||||
moveToPos p = "MOVE " <> show p.x <> " " <> show p.y
|
||||
|
||||
@@ -10,7 +10,7 @@ type GameInitInput =
|
||||
type GameInput =
|
||||
{ gold :: Int
|
||||
, touchedSite :: Int -- -1 if none
|
||||
, sites :: Array Site
|
||||
, sites :: Array ProtoSite
|
||||
, units :: Array Minion
|
||||
}
|
||||
|
||||
@@ -21,7 +21,7 @@ type SiteInfo =
|
||||
, radius :: Int
|
||||
}
|
||||
|
||||
type Site =
|
||||
type ProtoSite =
|
||||
{ id :: Int
|
||||
, structureType :: Int -- -1 No structure, 2 Barracks
|
||||
, owner :: Int -- -1 No structure, 0 friendly, 1 enemy
|
||||
@@ -29,6 +29,17 @@ type Site =
|
||||
, param2 :: Int -- -1 No structure, barracks: 0 knight 1 archer
|
||||
}
|
||||
|
||||
type Site =
|
||||
{ id :: Int
|
||||
, x :: Int
|
||||
, y :: Int
|
||||
, radius :: Int
|
||||
, structureType :: Int
|
||||
, owner :: Int
|
||||
, param1 :: Int
|
||||
, param2 :: Int
|
||||
}
|
||||
|
||||
type Minion =
|
||||
{ x :: Int
|
||||
, y :: Int
|
||||
|
||||
Reference in New Issue
Block a user