veloren_rtsim/rule/npc_ai/
mod.rs

1//! This rule is by far the most significant rule in rtsim to date and governs
2//! the behaviour of rtsim NPCs. It uses a novel combinator-based API to express
3//! long-running NPC actions in a manner that's halfway between [async/coroutine programming](https://en.wikipedia.org/wiki/Coroutine) and traditional
4//! [AI decision trees](https://en.wikipedia.org/wiki/Decision_tree).
5//!
6//! It may feel unintuitive when you first work with it, but trust us:
7//! expressing your AI behaviour in this way brings radical advantages and will
8//! simplify your code and make debugging exponentially easier.
9//!
10//! The fundamental abstraction is that of [`Action`]s. [`Action`]s, somewhat
11//! like [`core::future::Future`], represent a long-running behaviour performed
12//! by an NPC. See [`Action`] for a deeper explanation of actions and the
13//! methods that can be used to combine them together.
14//!
15//! NPC actions act upon the NPC's [`crate::data::npc::Controller`]. This type
16//! represent the immediate behavioural intentions of the NPC during simulation,
17//! such as by specifying a location to walk to, an action to perform, speech to
18//! say, or some persistent state to change (like the NPC's home site).
19//!
20//! After brain simulation has occurred, the resulting controller state is
21//! passed to either rtsim's internal NPC simulation rule
22//! ([`crate::rule::simulate_npcs`]) or, if the chunk the NPC is loaded, are
23//! passed to the Veloren server's agent system which attempts to act in
24//! accordance with it.
25
26mod airship_ai;
27pub mod dialogue;
28pub mod movement;
29pub mod util;
30
31use std::{collections::VecDeque, hash::BuildHasherDefault, sync::Arc};
32
33use crate::{
34    RtState, Rule, RuleError,
35    ai::{
36        Action, NpcCtx, State, casual, choose, finish, important, just, now,
37        predicate::{Chance, EveryRange, Predicate, every_range, timeout},
38        seq, until,
39    },
40    data::{
41        ReportKind, Sentiment, Sites,
42        npc::{Brain, DialogueSession, PathData, SimulationMode},
43    },
44    event::OnTick,
45};
46use common::{
47    assets::AssetExt,
48    astar::{Astar, PathResult},
49    comp::{
50        self, Content, bird_large,
51        compass::{Direction, Distance},
52        item::ItemDef,
53    },
54    path::Path,
55    rtsim::{
56        Actor, ChunkResource, DialogueKind, NpcInput, PersonalityTrait, Profession, Response, Role,
57        SiteId,
58    },
59    spiral::Spiral2d,
60    store::Id,
61    terrain::{CoordinateConversions, TerrainChunkSize, sprite},
62    time::DayPeriod,
63    util::Dir,
64};
65use core::ops::ControlFlow;
66use fxhash::FxHasher64;
67use itertools::{Either, Itertools};
68use rand::prelude::*;
69use rand_chacha::ChaChaRng;
70use rayon::iter::{IntoParallelRefMutIterator, ParallelIterator};
71use vek::*;
72use world::{
73    IndexRef, World,
74    civ::{self, Track},
75    site::{
76        self, PlotKind, Site as WorldSite, SiteKind, TileKind,
77        plot::{PlotKindMeta, tavern},
78    },
79    util::NEIGHBORS,
80};
81
82use self::{
83    movement::{
84        follow_actor, goto, goto_2d, goto_2d_flying, goto_actor, travel_to_point, travel_to_site,
85    },
86    util::do_dialogue,
87};
88
89/// How many ticks should pass between running NPC AI.
90/// Note that this only applies to simulated NPCs: loaded NPCs have their AI
91/// code run every tick. This means that AI code should be broadly
92/// DT-independent.
93const SIMULATED_TICK_SKIP: u64 = 10;
94
95pub struct NpcAi;
96
97#[derive(Clone)]
98struct DefaultState {
99    socialize_timer: EveryRange,
100    move_home_timer: Chance<EveryRange>,
101}
102
103impl Rule for NpcAi {
104    fn start(rtstate: &mut RtState) -> Result<Self, RuleError> {
105        // Keep track of the last `SIMULATED_TICK_SKIP` ticks, to know the deltatime
106        // since the last tick we ran the npc.
107        let mut last_ticks: VecDeque<_> = [1.0 / 30.0; SIMULATED_TICK_SKIP as usize]
108            .into_iter()
109            .collect();
110
111        rtstate.bind::<Self, OnTick>(move |ctx| {
112            last_ticks.push_front(ctx.event.dt);
113            if last_ticks.len() >= SIMULATED_TICK_SKIP as usize {
114                last_ticks.pop_back();
115            }
116            // Temporarily take the brains of NPCs out of their heads to appease the borrow
117            // checker
118            let mut npc_data = {
119                let mut data = ctx.state.data_mut();
120                data.npcs
121                    .iter_mut()
122                    // Don't run AI for dead NPCs
123                    .filter(|(_, npc)| !npc.is_dead() && !matches!(npc.role, Role::Vehicle))
124                    // Don't run AI for simulated NPCs every tick
125                    .filter(|(_, npc)| matches!(npc.mode, SimulationMode::Loaded) || (npc.seed as u64 + ctx.event.tick) % SIMULATED_TICK_SKIP == 0)
126                    .map(|(npc_id, npc)| {
127                        let controller = std::mem::take(&mut npc.controller);
128                        let inbox = std::mem::take(&mut npc.inbox);
129                        let sentiments = std::mem::take(&mut npc.sentiments);
130                        let known_reports = std::mem::take(&mut npc.known_reports);
131                        let brain = npc.brain.take().unwrap_or_else(|| Brain {
132                            action: Box::new(think().repeat().with_state(DefaultState {
133                                socialize_timer: every_range(15.0..30.0),
134                                move_home_timer: every_range(400.0..2000.0).chance(0.5),
135                            })),
136                        });
137                        (npc_id, controller, inbox, sentiments, known_reports, brain)
138                    })
139                    .collect::<Vec<_>>()
140            };
141
142            // The sum of the last `SIMULATED_TICK_SKIP` tick deltatimes is the deltatime since
143            // simulated npcs ran this tick had their ai ran.
144            let simulated_dt = last_ticks.iter().sum::<f32>();
145
146            // Do a little thinking
147            {
148                let data = &*ctx.state.data();
149
150                npc_data
151                    .par_iter_mut()
152                    .for_each(|(npc_id, controller, inbox, sentiments, known_reports, brain)| {
153                        let npc = &data.npcs[*npc_id];
154
155                        controller.reset();
156
157                        brain.action.tick(&mut NpcCtx {
158                            state: ctx.state,
159                            world: ctx.world,
160                            index: ctx.index,
161                            time_of_day: ctx.event.time_of_day,
162                            time: ctx.event.time,
163                            npc,
164                            npc_id: *npc_id,
165                            controller,
166                            inbox,
167                            known_reports,
168                            sentiments,
169                            dt: if matches!(npc.mode, SimulationMode::Loaded) {
170                                ctx.event.dt
171                            } else {
172                                simulated_dt
173                            },
174                            rng: ChaChaRng::from_seed(thread_rng().gen::<[u8; 32]>()),
175                            system_data: &*ctx.system_data,
176                        }, &mut ());
177
178                        // If an input wasn't processed by the brain, we no longer have a use for it
179                        inbox.clear();
180                    });
181            }
182
183            // Reinsert NPC brains
184            let mut data = ctx.state.data_mut();
185            for (npc_id, controller, inbox, sentiments, known_reports, brain) in npc_data {
186                data.npcs[npc_id].controller = controller;
187                data.npcs[npc_id].brain = Some(brain);
188                data.npcs[npc_id].inbox = inbox;
189                data.npcs[npc_id].sentiments = sentiments;
190                data.npcs[npc_id].known_reports = known_reports;
191            }
192        });
193
194        Ok(Self)
195    }
196}
197
198fn idle<S: State>() -> impl Action<S> + Clone {
199    just(|ctx, _| ctx.controller.do_idle()).debug(|| "idle")
200}
201
202fn talk_to<S: State>(tgt: Actor) -> impl Action<S> {
203    now(move |ctx, _| {
204        if ctx.sentiments.toward(tgt).is(Sentiment::ENEMY) {
205            just(move |ctx, _| {
206                ctx.controller
207                    .say(tgt, Content::localized("npc-speech-reject_rival"))
208            })
209            .boxed()
210        } else if matches!(tgt, Actor::Character(_)) {
211            do_dialogue(tgt, move |session| dialogue::general(tgt, session)).boxed()
212        } else {
213            smalltalk_to(tgt).boxed()
214        }
215    })
216}
217
218fn tell_site_content(ctx: &NpcCtx, site: SiteId) -> Option<Content> {
219    if let Some(world_site) = ctx.state.data().sites.get(site)
220        && let Some(site_name) = util::site_name(ctx, site)
221    {
222        Some(Content::localized_with_args("npc-speech-tell_site", [
223            ("site", Content::Plain(site_name)),
224            (
225                "dir",
226                Direction::from_dir(world_site.wpos.as_() - ctx.npc.wpos.xy()).localize_npc(),
227            ),
228            (
229                "dist",
230                Distance::from_length(world_site.wpos.as_().distance(ctx.npc.wpos.xy()) as i32)
231                    .localize_npc(),
232            ),
233        ]))
234    } else {
235        None
236    }
237}
238
239fn smalltalk_to<S: State>(tgt: Actor) -> impl Action<S> {
240    now(move |ctx, _| {
241        if matches!(tgt, Actor::Npc(_)) && ctx.rng.gen_bool(0.2) {
242            // Cut off the conversation sometimes to avoid infinite conversations (but only
243            // if the target is an NPC!) TODO: Don't special case this, have
244            // some sort of 'bored of conversation' system
245            idle().boxed()
246        } else {
247            // Mention nearby sites
248            let comment = if ctx.rng.gen_bool(0.3)
249                && let Some(current_site) = ctx.npc.current_site
250                && let Some(current_site) = ctx.state.data().sites.get(current_site)
251                && let Some(mention_site) = current_site.nearby_sites_by_size.choose(&mut ctx.rng)
252                && let Some(content) = tell_site_content(ctx, *mention_site)
253            {
254                content
255            // Mention current site
256            } else if ctx.rng.gen_bool(0.3)
257                && let Some(current_site) = ctx.npc.current_site
258                && let Some(current_site_name) = util::site_name(ctx, current_site)
259            {
260                Content::localized_with_args("npc-speech-site", [(
261                    "site",
262                    Content::Plain(current_site_name),
263                )])
264
265            // Mention nearby monsters
266            } else if ctx.rng.gen_bool(0.3)
267                && let Some(monster) = ctx
268                    .state
269                    .data()
270                    .npcs
271                    .values()
272                    .filter(|other| matches!(&other.role, Role::Monster))
273                    .min_by_key(|other| other.wpos.xy().distance(ctx.npc.wpos.xy()) as i32)
274            {
275                Content::localized_with_args("npc-speech-tell_monster", [
276                    ("body", monster.body.localize_npc()),
277                    (
278                        "dir",
279                        Direction::from_dir(monster.wpos.xy() - ctx.npc.wpos.xy()).localize_npc(),
280                    ),
281                    (
282                        "dist",
283                        Distance::from_length(monster.wpos.xy().distance(ctx.npc.wpos.xy()) as i32)
284                            .localize_npc(),
285                    ),
286                ])
287            // Specific night dialog
288            } else if ctx.rng.gen_bool(0.6) && DayPeriod::from(ctx.time_of_day.0).is_dark() {
289                Content::localized("npc-speech-night")
290            } else {
291                ctx.npc.personality.get_generic_comment(&mut ctx.rng)
292            };
293            // TODO: Don't special-case players
294            let wait = if matches!(tgt, Actor::Character(_)) {
295                0.0
296            } else {
297                1.5
298            };
299            idle()
300                .repeat()
301                .stop_if(timeout(wait))
302                .then(just(move |ctx, _| ctx.controller.say(tgt, comment.clone())))
303                .boxed()
304        }
305    })
306}
307
308fn socialize() -> impl Action<EveryRange> {
309    now(move |ctx, socialize: &mut EveryRange| {
310        // Skip most socialising actions if we're not loaded
311        if matches!(ctx.npc.mode, SimulationMode::Loaded)
312            && socialize.should(ctx)
313            && !ctx.npc.personality.is(PersonalityTrait::Introverted)
314        {
315            // Sometimes dance
316            if ctx.rng.gen_bool(0.15) {
317                return just(|ctx, _| ctx.controller.do_dance(None))
318                    .repeat()
319                    .stop_if(timeout(6.0))
320                    .debug(|| "dancing")
321                    .map(|_, _| ())
322                    .l()
323                    .l();
324            // Talk to nearby NPCs
325            } else if let Some(other) = ctx
326                .state
327                .data()
328                .npcs
329                .nearby(Some(ctx.npc_id), ctx.npc.wpos, 8.0)
330                .choose(&mut ctx.rng)
331            {
332                return smalltalk_to(other)
333                    // After talking, wait for a while
334                    .then(idle().repeat().stop_if(timeout(4.0)))
335                    .map(|_, _| ())
336                    .r().l();
337            }
338        }
339        idle().r()
340    })
341}
342
343fn adventure() -> impl Action<DefaultState> {
344    choose(|ctx, _| {
345        // Choose a random site that's fairly close by
346        if let Some(tgt_site) = ctx
347            .state
348            .data()
349            .sites
350            .iter()
351            .filter(|(site_id, site)| {
352                site.world_site.is_some_and(|ws| ctx.index.sites.get(ws).any_plot(|plot| matches!(plot.meta(), Some(PlotKindMeta::Workshop { .. })))) && (ctx.npc.current_site != Some(*site_id))
353                    && ctx.rng.gen_bool(0.25)
354            })
355            .min_by_key(|(_, site)| site.wpos.as_().distance(ctx.npc.wpos.xy()) as i32)
356            .map(|(site_id, _)| site_id)
357        {
358            let wait_time = if matches!(ctx.npc.profession(), Some(Profession::Merchant)) {
359                60.0 * 15.0
360            } else {
361                60.0 * 3.0
362            };
363            let site_name = util::site_name(ctx, tgt_site).unwrap_or_default();
364            // Travel to the site
365            important(just(move |ctx, _| ctx.controller.say(None, Content::localized_with_args("npc-speech-moving_on", [("site", site_name.clone())])))
366                          .then(travel_to_site(tgt_site, 0.6))
367                          // Stop for a few minutes
368                          .then(villager(tgt_site).repeat().stop_if(timeout(wait_time)))
369                          .map(|_, _| ())
370                          .boxed(),
371            )
372        } else {
373            casual(finish().boxed())
374        }
375    })
376    .debug(move || "adventure")
377}
378
379fn hired<S: State>(tgt: Actor) -> impl Action<S> {
380    follow_actor(tgt, 5.0)
381        // Stop following if we're no longer hired
382        .stop_if(move |ctx: &mut NpcCtx| ctx.npc.hiring.is_none_or(|(a, _)| a != tgt))
383        .debug(move|| format!("hired by {tgt:?}"))
384        .interrupt_with(move |ctx, _| {
385            // End hiring for various reasons
386            if let Some((tgt, expires)) = ctx.npc.hiring {
387                // Hiring period has expired
388                if ctx.time > expires {
389                    ctx.controller.end_hiring();
390                    // If the actor exists, tell them that the hiring is over
391                    if util::actor_exists(ctx, tgt) {
392                        return Some(goto_actor(tgt, 2.0)
393                            .then(do_dialogue(tgt, |session| {
394                                session.say_statement(Content::localized("npc-dialogue-hire_expired"))
395                            }))
396                            .boxed());
397                    }
398                }
399
400                if ctx.sentiments.toward(tgt).is(Sentiment::RIVAL) {
401                    ctx.controller.end_hiring();
402                    // If the actor exists, tell them that the hiring is over
403                    if util::actor_exists(ctx, tgt) {
404                        return Some(goto_actor(tgt, 2.0)
405                            .then(do_dialogue(tgt, |session| {
406                                session.say_statement(Content::localized(
407                                    "npc-dialogue-hire_cancelled_unhappy",
408                                ))
409                            }))
410                            .boxed());
411                    }
412                }
413            }
414
415            None
416        })
417        .map(|_, _| ())
418}
419
420fn gather_ingredients<S: State>() -> impl Action<S> {
421    just(|ctx, _| {
422        ctx.controller.do_gather(
423            &[
424                ChunkResource::Fruit,
425                ChunkResource::Mushroom,
426                ChunkResource::Plant,
427            ][..],
428        )
429    })
430    .debug(|| "gather ingredients")
431}
432
433fn hunt_animals<S: State>() -> impl Action<S> {
434    just(|ctx, _| ctx.controller.do_hunt_animals()).debug(|| "hunt_animals")
435}
436
437fn find_forest(ctx: &mut NpcCtx) -> Option<Vec2<f32>> {
438    let chunk_pos = ctx.npc.wpos.xy().as_().wpos_to_cpos();
439    Spiral2d::new()
440        .skip(ctx.rng.gen_range(1..=64))
441        .take(24)
442        .map(|rpos| chunk_pos + rpos)
443        .find(|cpos| {
444            ctx.world
445                .sim()
446                .get(*cpos)
447                .is_some_and(|c| c.tree_density > 0.75 && c.surface_veg > 0.5)
448        })
449        .map(|chunk| TerrainChunkSize::center_wpos(chunk).as_())
450}
451
452fn find_farm(ctx: &mut NpcCtx, site: SiteId) -> Option<Vec2<f32>> {
453    ctx.state.data().sites.get(site).and_then(|site| {
454        let site = ctx.index.sites.get(site.world_site?);
455        let farm = site
456            .filter_plots(|p| matches!(p.kind(), PlotKind::FarmField(_)))
457            .choose(&mut ctx.rng)?;
458
459        Some(site.tile_center_wpos(farm.root_tile()).as_())
460    })
461}
462
463fn choose_plaza(ctx: &mut NpcCtx, site: SiteId) -> Option<Vec2<f32>> {
464    ctx.state.data().sites.get(site).and_then(|site| {
465        let site = ctx.index.sites.get(site.world_site?);
466        let plaza = &site.plots[site.plazas().choose(&mut ctx.rng)?];
467        let tile = plaza
468            .tiles()
469            .choose(&mut ctx.rng)
470            .unwrap_or_else(|| plaza.root_tile());
471        Some(site.tile_center_wpos(tile).as_())
472    })
473}
474
475const WALKING_SPEED: f32 = 0.35;
476
477fn villager(visiting_site: SiteId) -> impl Action<DefaultState> {
478    choose(move |ctx, state: &mut DefaultState| {
479        // Consider moving home if the home site gets too full
480        if state.move_home_timer.should(ctx)
481            && let Some(home) = ctx.npc.home
482            && Some(home) == ctx.npc.current_site
483            && let Some(home_pop_ratio) = ctx.state.data().sites.get(home)
484                .and_then(|site| Some((site, ctx.index.sites.get(site.world_site?))))
485                .and_then(|(site, world_site)| { let houses = world_site.filter_plots(|p| matches!(p.meta(), Some(PlotKindMeta::House { .. }))).count(); if houses == 0 { return None } Some(site.population.len() as f32 / houses as f32) } )
486                // Only consider moving if the population is more than 1.5x the number of homes
487                .filter(|pop_ratio| *pop_ratio > 1.5)
488            && let Some(new_home) = ctx
489                .state
490                .data()
491                .sites
492                .iter()
493                // Don't try to move to the site that's currently our home
494                .filter(|(site_id, _)| Some(*site_id) != ctx.npc.home)
495                // Only consider towns as potential homes
496                .filter_map(|(site_id, site)| {
497                    let world_site = site.world_site.map(|ws| ctx.index.sites.get(ws))?;
498                    let house_count = world_site.filter_plots(|p| matches!(p.meta(), Some(PlotKindMeta::House { .. }))).count();
499
500                    if house_count == 0 {
501                        return None;
502                    }
503                    Some((site_id, site, house_count))
504                })
505                // Only select sites that are less densely populated than our own
506                .filter(|(_, site, houses)| (site.population.len() as f32 / *houses as f32) < home_pop_ratio)
507                // Find the closest of the candidate sites
508                .min_by_key(|(_, site, _)| site.wpos.as_().distance(ctx.npc.wpos.xy()) as i32)
509                .map(|(site_id, _, _)| site_id)
510        {
511            let site_name = util::site_name(ctx, new_home);
512            return important(just(move |ctx, _| {
513                if let Some(site_name) = &site_name {
514                    ctx.controller.say(None, Content::localized_with_args("npc-speech-migrating", [("site", site_name.clone())]))
515                }
516            })
517                .then(travel_to_site(new_home, 0.5))
518                .then(just(move |ctx, _| ctx.controller.set_new_home(new_home))));
519        }
520        let day_period = DayPeriod::from(ctx.time_of_day.0);
521        let is_weekend = ctx.time_of_day.day() as u64 % 6 == 0;
522        let is_evening = day_period == DayPeriod::Evening;
523
524        let is_free_time = is_weekend || is_evening;
525
526        // Go to a house if it's dark
527        if day_period.is_dark()
528            && !matches!(ctx.npc.profession(), Some(Profession::Guard))
529        {
530            return important(
531                now(move |ctx, _| {
532                    if let Some(house_wpos) = ctx
533                        .state
534                        .data()
535                        .sites
536                        .get(visiting_site)
537                        .and_then(|site| Some(ctx.index.sites.get(site.world_site?)))
538                        .and_then(|site| {
539                            // Find a house in the site we're visiting
540                            let house = site
541                                .plots()
542                                .filter(|p| matches!(p.kind().meta(), Some(PlotKindMeta::House { .. })))
543                                .choose(&mut ctx.rng)?;
544                            Some(site.tile_center_wpos(house.root_tile()).as_())
545                        })
546                    {
547                        just(|ctx, _| {
548                            ctx.controller
549                                .say(None, Content::localized("npc-speech-night_time"))
550                        })
551                        .then(travel_to_point(house_wpos, 0.65))
552                        .debug(|| "walk to house")
553                        .then(socialize().repeat().map_state(|state: &mut DefaultState| &mut state.socialize_timer).debug(|| "wait in house"))
554                        .stop_if(|ctx: &mut NpcCtx| DayPeriod::from(ctx.time_of_day.0).is_light())
555                        .then(just(|ctx, _| {
556                            ctx.controller
557                                .say(None, Content::localized("npc-speech-day_time"))
558                        }))
559                        .map(|_, _| ())
560                        .boxed()
561                    } else {
562                        finish().boxed()
563                    }
564                })
565                .debug(|| "find somewhere to sleep"),
566            );
567        }
568        // Go do something fun on evenings and holidays, or on random days.
569        else if
570            // Ain't no rest for the wicked
571            !matches!(ctx.npc.profession(), Some(Profession::Guard | Profession::Chef))
572            && (matches!(day_period, DayPeriod::Evening) || is_free_time || ctx.rng.gen_bool(0.05)) {
573            let mut fun_activities = Vec::new();
574
575            if let Some(ws_id) = ctx.state.data().sites[visiting_site].world_site {
576                let ws = ctx.index.sites.get(ws_id);
577                if let Some(arena) = ws.plots().find_map(|p| match p.kind() { PlotKind::DesertCityArena(a) => Some(a), _ => None}) {
578                    let wait_time = ctx.rng.gen_range(100.0..300.0);
579                    // We don't use Z coordinates for seats because they are complicated to calculate from the Ramp procedural generation
580                    // and using goto_2d seems to work just fine. However it also means that NPC will never go seat on the stands
581                    // on the first floor of the arena. This is a compromise that was made because in the current arena procedural generation
582                    // there is also no pathways to the stands on the first floor for NPCs.
583                    let arena_center = Vec3::new(arena.center.x, arena.center.y, arena.base).as_::<f32>();
584                    let stand_dist = arena.stand_dist as f32;
585                    let seat_var_width = ctx.rng.gen_range(0..arena.stand_width) as f32;
586                    let seat_var_length = ctx.rng.gen_range(-arena.stand_length..arena.stand_length) as f32;
587                    // Select a seat on one of the 4 arena stands
588                    let seat = match ctx.rng.gen_range(0..4) {
589                        0 => Vec3::new(arena_center.x - stand_dist + seat_var_width, arena_center.y + seat_var_length, arena_center.z),
590                        1 => Vec3::new(arena_center.x + stand_dist - seat_var_width, arena_center.y + seat_var_length, arena_center.z),
591                        2 => Vec3::new(arena_center.x + seat_var_length, arena_center.y - stand_dist + seat_var_width, arena_center.z),
592                        _ => Vec3::new(arena_center.x + seat_var_length, arena_center.y + stand_dist - seat_var_width, arena_center.z),
593                    };
594                    let look_dir = Dir::from_unnormalized(arena_center - seat);
595                    // Walk to an arena seat, cheer, sit and dance
596                    let action = casual(just(move |ctx, _| ctx.controller.say(None, Content::localized("npc-speech-arena")))
597                            .then(goto_2d(seat.xy(), 0.6, 1.0).debug(|| "go to arena"))
598                            // Turn toward the centre of the arena and watch the action!
599                            .then(choose(move |ctx, _| if ctx.rng.gen_bool(0.3) {
600                                casual(just(move |ctx,_| ctx.controller.do_cheer(look_dir)).repeat().stop_if(timeout(5.0)))
601                            } else if ctx.rng.gen_bool(0.15) {
602                                casual(just(move |ctx,_| ctx.controller.do_dance(look_dir)).repeat().stop_if(timeout(5.0)))
603                            } else {
604                                casual(just(move |ctx,_| ctx.controller.do_sit(look_dir, None)).repeat().stop_if(timeout(15.0)))
605                            })
606                                .repeat()
607                                .stop_if(timeout(wait_time)))
608                            .map(|_, _| ())
609                            .boxed());
610                    fun_activities.push(action);
611                }
612                if let Some(tavern) = ws.plots().filter_map(|p| match p.kind() {  PlotKind::Tavern(a) => Some(a), _ => None }).choose(&mut ctx.rng) {
613                    let tavern_name = tavern.name.clone();
614                    let wait_time = ctx.rng.gen_range(100.0..300.0);
615
616                    let (stage_aabr, stage_z) = tavern.rooms.values().flat_map(|room| {
617                        room.details.iter().filter_map(|detail| match detail {
618                            tavern::Detail::Stage { aabr } => Some((*aabr, room.bounds.min.z + 1)),
619                            _ => None,
620                        })
621                    }).choose(&mut ctx.rng).unwrap_or((tavern.bounds, tavern.door_wpos.z));
622
623                    let bar_pos = tavern.rooms.values().flat_map(|room|
624                        room.details.iter().filter_map(|detail| match detail {
625                            tavern::Detail::Bar { aabr } => {
626                                let side = site::util::Dir::from_vec2(room.bounds.center().xy() - aabr.center());
627                                let pos = side.select_aabr_with(*aabr, aabr.center()) + side.to_vec2();
628
629                                Some(pos.with_z(room.bounds.min.z))
630                            }
631                            _ => None,
632                        })
633                    ).choose(&mut ctx.rng).unwrap_or(stage_aabr.center().with_z(stage_z));
634
635                    // Pick a chair that is theirs for the stay
636                    let chair_pos = tavern.rooms.values().flat_map(|room| {
637                        let z = room.bounds.min.z;
638                        room.details.iter().filter_map(move |detail| match detail {
639                            tavern::Detail::Table { pos, chairs } => Some(chairs.into_iter().map(move |dir| pos.with_z(z) + dir.to_vec2())),
640                            _ => None,
641                        })
642                        .flatten()
643                    }
644                    ).choose(&mut ctx.rng)
645                    // This path is possible, but highly unlikely.
646                    .unwrap_or(bar_pos);
647
648                    let stage_aabr = stage_aabr.as_::<f32>();
649                    let stage_z = stage_z as f32;
650
651                    let action = casual(travel_to_point(tavern.door_wpos.xy().as_() + 0.5, 0.8).then(choose(move |ctx, (last_action, _)| {
652                            let action = [0, 1, 2].into_iter().filter(|i| *last_action != Some(*i)).choose(&mut ctx.rng).expect("We have at least 2 elements");
653                            let socialize_repeat = || socialize().map_state(|(_, timer)| timer).repeat();
654                            match action {
655                                // Go and dance on a stage.
656                                0 => {
657                                    casual(
658                                        now(move |ctx, (last_action, _)| {
659                                            *last_action = Some(action);
660                                            goto(stage_aabr.min.map2(stage_aabr.max, |a, b| ctx.rng.gen_range(a..b)).with_z(stage_z), WALKING_SPEED, 1.0)
661                                        })
662                                        .then(just(move |ctx,_| ctx.controller.do_dance(None)).repeat().stop_if(timeout(ctx.rng.gen_range(20.0..30.0))))
663                                        .map(|_, _| ())
664                                        .debug(|| "Dancing on the stage")
665                                    )
666                                },
667                                // Go and sit at a table.
668                                1 => {
669                                    casual(
670                                        now(move |ctx, (last_action, _)| {
671                                            *last_action = Some(action);
672                                            goto(chair_pos.as_() + 0.5, WALKING_SPEED, 1.0)
673                                                .then(just(move |ctx, _| ctx.controller.do_sit(None, Some(chair_pos)))
674                                                    // .then(socialize().map_state(|(_, timer)| timer))
675                                                    .repeat().stop_if(timeout(ctx.rng.gen_range(30.0..60.0)))
676                                                )
677                                                .map(|_, _| ())
678                                        })
679                                        .debug(move || format!("Sitting in a chair at {} {} {}", chair_pos.x, chair_pos.y, chair_pos.z))
680                                    )
681                                },
682                                // Go to the bar.
683                                _ => {
684                                    casual(
685                                        now(move |ctx, (last_action, _)| {
686                                            *last_action = Some(action);
687                                            goto(bar_pos.as_() + 0.5, WALKING_SPEED, 1.0).then(socialize_repeat().stop_if(timeout(ctx.rng.gen_range(10.0..25.0)))).map(|_, _| ())
688                                        }).debug(|| "At the bar")
689                                    )
690                                },
691                            }
692                        })
693                        .with_state((None::<u32>, every_range(5.0..10.0)))
694                        .repeat()
695                        .stop_if(timeout(wait_time)))
696                        .map(|_, _| ())
697                        .debug(move || format!("At the tavern '{}'", tavern_name))
698                        .boxed()
699                    );
700
701                    fun_activities.push(action);
702                }
703            }
704
705
706            if !fun_activities.is_empty() {
707                let i = ctx.rng.gen_range(0..fun_activities.len());
708                return fun_activities.swap_remove(i);
709            }
710        }
711        // Villagers with roles should perform those roles
712        else if matches!(ctx.npc.profession(), Some(Profession::Herbalist)) && ctx.rng.gen_bool(0.8)
713        {
714            if let Some(forest_wpos) = find_forest(ctx) {
715                return casual(
716                    travel_to_point(forest_wpos, 0.5)
717                        .debug(|| "walk to forest")
718                        .then({
719                            let wait_time = ctx.rng.gen_range(10.0..30.0);
720                            gather_ingredients().repeat().stop_if(timeout(wait_time))
721                        })
722                        .map(|_, _| ()),
723                );
724            }
725        } else if matches!(ctx.npc.profession(), Some(Profession::Farmer)) && ctx.rng.gen_bool(0.8)
726        {
727            if let Some(farm_wpos) = find_farm(ctx, visiting_site) {
728                return casual(
729                    travel_to_point(farm_wpos, 0.5)
730                        .debug(|| "walk to farm")
731                        .then({
732                            let wait_time = ctx.rng.gen_range(30.0..120.0);
733                            gather_ingredients().repeat().stop_if(timeout(wait_time))
734                        })
735                        .map(|_, _| ()),
736                );
737            }
738        } else if matches!(ctx.npc.profession(), Some(Profession::Hunter)) && ctx.rng.gen_bool(0.8) {
739            if let Some(forest_wpos) = find_forest(ctx) {
740                return casual(
741                    just(|ctx, _| {
742                        ctx.controller
743                            .say(None, Content::localized("npc-speech-start_hunting"))
744                    })
745                    .then(travel_to_point(forest_wpos, 0.75))
746                    .debug(|| "walk to forest")
747                    .then({
748                        let wait_time = ctx.rng.gen_range(30.0..60.0);
749                        hunt_animals().repeat().stop_if(timeout(wait_time))
750                    })
751                    .map(|_, _| ()),
752                );
753            }
754        } else if matches!(ctx.npc.profession(), Some(Profession::Guard)) && ctx.rng.gen_bool(0.7) {
755            if let Some(plaza_wpos) = choose_plaza(ctx, visiting_site) {
756                return casual(
757                    travel_to_point(plaza_wpos, 0.4)
758                        .debug(|| "patrol")
759                        .interrupt_with(move |ctx, _| {
760                            if ctx.rng.gen_bool(0.0003) {
761                                Some(just(move |ctx, _| {
762                                    ctx.controller
763                                        .say(None, Content::localized("npc-speech-guard_thought"))
764                                }))
765                            } else {
766                                None
767                            }
768                        })
769                        .map(|_, _| ()),
770                );
771            }
772        } else if matches!(ctx.npc.profession(), Some(Profession::Merchant)) && ctx.rng.gen_bool(0.8)
773        {
774            return casual(
775                just(|ctx, _| {
776                    // Try to direct our speech at nearby actors, if there are any
777                    let (target, phrase) = if ctx.rng.gen_bool(0.3) && let Some(other) = ctx
778                        .state
779                        .data()
780                        .npcs
781                        .nearby(Some(ctx.npc_id), ctx.npc.wpos, 8.0)
782                        .choose(&mut ctx.rng)
783                    {
784                        (Some(other), "npc-speech-merchant_sell_directed")
785                    } else {
786                        // Otherwise, resort to generic expressions
787                        (None, "npc-speech-merchant_sell_undirected")
788                    };
789
790                    ctx.controller.say(target, Content::localized(phrase));
791                })
792                .then(idle().repeat().stop_if(timeout(8.0)))
793                .repeat()
794                .stop_if(timeout(60.0))
795                .debug(|| "sell wares")
796                .map(|_, _| ()),
797            );
798        } else if matches!(ctx.npc.profession(), Some(Profession::Chef))
799            && ctx.rng.gen_bool(0.8)
800            && let Some(ws_id) = ctx.state.data().sites[visiting_site].world_site
801            && let Some(tavern) = ctx.index.sites.get(ws_id).plots().filter_map(|p| match p.kind() {  PlotKind::Tavern(a) => Some(a), _ => None }).choose(&mut ctx.rng)
802            && let Some((bar_pos, room_center)) = tavern.rooms.values().flat_map(|room|
803                room.details.iter().filter_map(|detail| match detail {
804                    tavern::Detail::Bar { aabr } => {
805                        let center = aabr.center();
806                        Some((center.with_z(room.bounds.min.z), room.bounds.center().xy()))
807                    }
808                    _ => None,
809                })
810            ).choose(&mut ctx.rng) {
811
812            let face_dir = Dir::from_unnormalized((room_center - bar_pos).as_::<f32>().with_z(0.0)).unwrap_or_else(|| Dir::random_2d(&mut ctx.rng));
813
814            return casual(
815                travel_to_point(tavern.door_wpos.xy().as_(), 0.5)
816                    .then(goto(bar_pos.as_() + Vec2::new(0.5, 0.5), WALKING_SPEED, 2.0))
817                    // TODO: Just dance there for now, in the future do other stuff.
818                    .then(just(move |ctx, _| ctx.controller.do_dance(Some(face_dir))).repeat().stop_if(timeout(60.0)))
819                    .debug(|| "cook food").map(|_, _| ())
820            )
821        }
822
823        // If nothing else needs doing, walk between plazas and socialize
824        casual(now(move |ctx, _| {
825            // Choose a plaza in the site we're visiting to walk to
826            if let Some(plaza_wpos) = choose_plaza(ctx, visiting_site) {
827                // Walk to the plaza...
828                Either::Left(travel_to_point(plaza_wpos, 0.5)
829                    .debug(|| "walk to plaza"))
830            } else {
831                // No plazas? :(
832                Either::Right(finish())
833            }
834                // ...then socialize for some time before moving on
835                .then(socialize()
836                    .repeat()
837                    .map_state(|state: &mut DefaultState| &mut state.socialize_timer)
838                    .stop_if(timeout(ctx.rng.gen_range(30.0..90.0)))
839                    .debug(|| "wait at plaza"))
840                .map(|_, _| ())
841        }))
842    })
843    .debug(move || format!("villager at site {:?}", visiting_site))
844}
845
846fn pilot<S: State>(ship: common::comp::ship::Body) -> impl Action<S> {
847    // Travel between different towns in a straight line
848    now(move |ctx, _| {
849        let data = &*ctx.state.data();
850        let station_wpos = data
851            .sites
852            .iter()
853            .filter(|(id, _)| Some(*id) != ctx.npc.current_site)
854            .filter_map(|(_, site)| Some(ctx.index.sites.get(site.world_site?)))
855            .flat_map(|site| {
856                site.filter_plots(|plot| {
857                    matches!(plot.kind().meta(), Some(PlotKindMeta::AirshipDock { .. }))
858                })
859                .map(|plot| site.tile_center_wpos(plot.root_tile()))
860            })
861            .choose(&mut ctx.rng);
862        if let Some(station_wpos) = station_wpos {
863            Either::Right(
864                goto_2d_flying(
865                    station_wpos.as_(),
866                    1.0,
867                    50.0,
868                    150.0,
869                    110.0,
870                    ship.flying_height(),
871                )
872                .then(goto_2d_flying(
873                    station_wpos.as_(),
874                    1.0,
875                    10.0,
876                    32.0,
877                    16.0,
878                    30.0,
879                )),
880            )
881        } else {
882            Either::Left(finish())
883        }
884    })
885    .repeat()
886    .map(|_, _| ())
887}
888
889fn captain<S: State>() -> impl Action<S> {
890    // For now just randomly travel the sea
891    now(|ctx, _| {
892        let chunk = ctx.npc.wpos.xy().as_().wpos_to_cpos();
893        if let Some(chunk) = NEIGHBORS
894            .into_iter()
895            .map(|neighbor| chunk + neighbor)
896            .filter(|neighbor| {
897                ctx.world
898                    .sim()
899                    .get(*neighbor)
900                    .is_some_and(|c| c.river.river_kind.is_some())
901            })
902            .choose(&mut ctx.rng)
903        {
904            let wpos = TerrainChunkSize::center_wpos(chunk);
905            let wpos = wpos.as_().with_z(
906                ctx.world
907                    .sim()
908                    .get_interpolated(wpos, |chunk| chunk.water_alt)
909                    .unwrap_or(0.0),
910            );
911            goto(wpos, 0.7, 5.0).boxed()
912        } else {
913            idle().boxed()
914        }
915    })
916    .repeat()
917    .map(|_, _| ())
918}
919
920fn check_inbox<S: State>(ctx: &mut NpcCtx) -> Option<impl Action<S> + use<S>> {
921    let mut action = None;
922    ctx.inbox.retain(|input| {
923        match input {
924            NpcInput::Report(report_id) if !ctx.known_reports.contains(report_id) => {
925                let data = ctx.state.data();
926                let Some(report) = data.reports.get(*report_id) else {
927                    return false;
928                };
929
930                const REPORT_RESPONSE_TIME: f64 = 60.0 * 5.0;
931
932                match report.kind {
933                    ReportKind::Death { killer, actor, .. }
934                        if matches!(&ctx.npc.role, Role::Civilised(_)) =>
935                    {
936                        // TODO: Don't report self
937                        let phrase = if let Some(killer) = killer {
938                            // TODO: For now, we don't make sentiment changes if the killer was an
939                            // NPC because NPCs can't hurt one-another.
940                            // This should be changed in the future.
941                            if !matches!(killer, Actor::Npc(_)) {
942                                // TODO: Don't hard-code sentiment change
943                                let change = if ctx.sentiments.toward(actor).is(Sentiment::ENEMY) {
944                                    // Like the killer if we have negative sentiment towards the
945                                    // killed.
946                                    0.25
947                                } else {
948                                    -0.75
949                                };
950                                ctx.sentiments
951                                    .toward_mut(killer)
952                                    .change_by(change, Sentiment::VILLAIN);
953                            }
954
955                            // This is a murder of a player. Feel bad for the player and stop
956                            // attacking them.
957                            if let Actor::Character(_) = actor {
958                                ctx.sentiments
959                                    .toward_mut(actor)
960                                    .limit_below(Sentiment::ENEMY)
961                            }
962
963                            if ctx.sentiments.toward(actor).is(Sentiment::ENEMY) {
964                                "npc-speech-witness_enemy_murder"
965                            } else {
966                                "npc-speech-witness_murder"
967                            }
968                        } else {
969                            "npc-speech-witness_death"
970                        };
971                        ctx.known_reports.insert(*report_id);
972
973                        if ctx.time_of_day.0 - report.at_tod.0 < REPORT_RESPONSE_TIME {
974                            action = Some(
975                                just(move |ctx, _| {
976                                    ctx.controller.say(killer, Content::localized(phrase))
977                                })
978                                .l()
979                                .l(),
980                            );
981                        }
982                        false
983                    },
984                    ReportKind::Theft {
985                        thief,
986                        site,
987                        sprite,
988                    } => {
989                        // Check if this happened at home, where we know what belongs to who
990                        if let Some(site) = site
991                            && ctx.npc.home == Some(site)
992                        {
993                            // TODO: Don't hardcode sentiment change.
994                            ctx.sentiments
995                                .toward_mut(thief)
996                                .change_by(-0.2, Sentiment::ENEMY);
997                            ctx.known_reports.insert(*report_id);
998
999                            let phrase = if matches!(ctx.npc.profession(), Some(Profession::Farmer))
1000                                && matches!(sprite.category(), sprite::Category::Plant)
1001                            {
1002                                "npc-speech-witness_theft_owned"
1003                            } else {
1004                                "npc-speech-witness_theft"
1005                            };
1006
1007                            if ctx.time_of_day.0 - report.at_tod.0 < REPORT_RESPONSE_TIME {
1008                                action = Some(
1009                                    just(move |ctx, _| {
1010                                        ctx.controller.say(thief, Content::localized(phrase))
1011                                    })
1012                                    .r()
1013                                    .l(),
1014                                );
1015                            }
1016                        }
1017                        false
1018                    },
1019                    // We don't care about deaths of non-civilians
1020                    ReportKind::Death { .. } => false,
1021                }
1022            },
1023            NpcInput::Report(_) => false, // Reports we already know of are ignored
1024            NpcInput::Interaction(by) => {
1025                action = Some(talk_to(*by).r());
1026                false
1027            },
1028            // Dialogue inputs get retained because they're handled by specific conversation actions
1029            // later
1030            NpcInput::Dialogue(_, _) => true,
1031        }
1032    });
1033
1034    action
1035}
1036
1037fn check_for_enemies<S: State>(ctx: &mut NpcCtx) -> Option<impl Action<S> + use<S>> {
1038    // TODO: Instead of checking all nearby actors every tick, it would be more
1039    // effective to have the actor grid generate a per-tick diff so that we only
1040    // need to check new actors in the local area. Be careful though:
1041    // implementing this means accounting for changes in sentiment (that could
1042    // suddenly make a nearby actor an enemy) as well as variable NPC tick
1043    // rates!
1044    ctx.state
1045        .data()
1046        .npcs
1047        .nearby(Some(ctx.npc_id), ctx.npc.wpos, 24.0)
1048        .find(|actor| ctx.sentiments.toward(*actor).is(Sentiment::ENEMY))
1049        .map(|enemy| just(move |ctx, _| ctx.controller.attack(enemy)))
1050}
1051
1052fn react_to_events<S: State>(ctx: &mut NpcCtx, _: &mut S) -> Option<impl Action<S> + use<S>> {
1053    check_inbox::<S>(ctx)
1054        .map(|action| action.boxed())
1055        .or_else(|| check_for_enemies(ctx).map(|action| action.boxed()))
1056}
1057
1058fn humanoid() -> impl Action<DefaultState> {
1059    choose(|ctx, _| {
1060        if let Some(riding) = &ctx.state.data().npcs.mounts.get_mount_link(ctx.npc_id) {
1061            if riding.is_steering {
1062                if let Some(vehicle) = ctx.state.data().npcs.get(riding.mount) {
1063                    match vehicle.body {
1064                        comp::Body::Ship(body @ comp::ship::Body::AirBalloon) => {
1065                            important(pilot(body))
1066                        },
1067                        comp::Body::Ship(comp::ship::Body::DefaultAirship) => {
1068                            important(airship_ai::pilot_airship())
1069                        },
1070                        comp::Body::Ship(
1071                            comp::ship::Body::SailBoat | comp::ship::Body::Galleon,
1072                        ) => important(captain()),
1073                        _ => casual(idle()),
1074                    }
1075                } else {
1076                    casual(finish())
1077                }
1078            } else {
1079                important(
1080                    socialize().map_state(|state: &mut DefaultState| &mut state.socialize_timer),
1081                )
1082            }
1083        } else if let Some((tgt, _)) = ctx.npc.hiring
1084            && util::actor_exists(ctx, tgt)
1085        {
1086            important(hired(tgt).interrupt_with(react_to_events))
1087        } else {
1088            let action = if matches!(
1089                ctx.npc.profession(),
1090                Some(Profession::Adventurer(_) | Profession::Merchant)
1091            ) {
1092                adventure().l().l()
1093            } else if let Some(home) = ctx.npc.home {
1094                villager(home).r().l()
1095            } else {
1096                idle().r() // Homeless
1097            };
1098
1099            casual(action.interrupt_with(react_to_events))
1100        }
1101    })
1102}
1103
1104fn bird_large() -> impl Action<DefaultState> {
1105    now(|ctx, bearing: &mut Vec2<f32>| {
1106        *bearing = bearing
1107            .map(|e| e + ctx.rng.gen_range(-0.1..0.1))
1108            .try_normalized()
1109            .unwrap_or_default();
1110        let bearing_dist = 15.0;
1111        let mut pos = ctx.npc.wpos.xy() + *bearing * bearing_dist;
1112        let is_deep_water =
1113            matches!(ctx.npc.body, common::comp::Body::BirdLarge(b) if matches!(b.species, bird_large::Species::SeaWyvern))
1114                || ctx
1115                .world
1116                .sim()
1117                .get(pos.as_().wpos_to_cpos()).is_none_or(|c| {
1118                    c.alt - c.water_alt < -120.0 && (c.river.is_ocean() || c.river.is_lake())
1119                });
1120        if is_deep_water {
1121            *bearing *= -1.0;
1122            pos = ctx.npc.wpos.xy() + *bearing * bearing_dist;
1123        };
1124        // when high tree_density fly high, otherwise fly low-mid
1125        let npc_pos = ctx.npc.wpos.xy();
1126        let trees = ctx
1127            .world
1128            .sim()
1129            .get(npc_pos.as_().wpos_to_cpos()).is_some_and(|c| c.tree_density > 0.1);
1130        let height_factor = if trees {
1131            2.0
1132        } else {
1133            ctx.rng.gen_range(0.4..0.9)
1134        };
1135
1136        let data = ctx.state.data();
1137        // without destination site fly to next waypoint
1138        let mut dest_site = pos;
1139        if let Some(home) = ctx.npc.home {
1140            let is_home = ctx.npc.current_site == Some(home);
1141            if is_home {
1142                if let Some((id, _)) = data
1143                    .sites
1144                    .iter()
1145                    .filter(|(id, site)| {
1146                        *id != home
1147                            && site.world_site.is_some_and(|site| {
1148                            match ctx.npc.body {
1149                                common::comp::Body::BirdLarge(b) => match b.species {
1150                                    bird_large::Species::Phoenix => matches!(ctx.index.sites.get(site).kind,
1151                                    Some(SiteKind::Terracotta
1152                                    | SiteKind::Haniwa
1153                                    | SiteKind::Myrmidon
1154                                    | SiteKind::Adlet
1155                                    | SiteKind::DwarvenMine
1156                                    | SiteKind::ChapelSite
1157                                    | SiteKind::Cultist
1158                                    | SiteKind::Gnarling
1159                                    | SiteKind::Sahagin
1160                                    | SiteKind::VampireCastle)),
1161                                    bird_large::Species::Cockatrice => matches!(ctx.index.sites.get(site).kind,
1162                                    Some(SiteKind::GiantTree)),
1163                                    bird_large::Species::Roc => matches!(ctx.index.sites.get(site).kind,
1164                                    Some(SiteKind::Haniwa
1165                                    | SiteKind::Cultist)),
1166                                    bird_large::Species::FlameWyvern => matches!(ctx.index.sites.get(site).kind,
1167                                    Some(SiteKind::DwarvenMine
1168                                    | SiteKind::Terracotta)),
1169                                    bird_large::Species::CloudWyvern => matches!(ctx.index.sites.get(site).kind,
1170                                    Some(SiteKind::ChapelSite
1171                                    | SiteKind::Sahagin)),
1172                                    bird_large::Species::FrostWyvern => matches!(ctx.index.sites.get(site).kind,
1173                                    Some(SiteKind::Adlet
1174                                    | SiteKind::Myrmidon)),
1175                                    bird_large::Species::SeaWyvern => matches!(ctx.index.sites.get(site).kind,
1176                                    Some(SiteKind::ChapelSite
1177                                    | SiteKind::Sahagin)),
1178                                    bird_large::Species::WealdWyvern => matches!(ctx.index.sites.get(site).kind,
1179                                    Some(SiteKind::GiantTree
1180                                    | SiteKind::Gnarling)),
1181                                },
1182                                _ => matches!(&ctx.index.sites.get(site).kind, Some(SiteKind::GiantTree)),
1183                            }
1184                        })
1185                    })
1186                    /*choose closest destination:
1187                    .min_by_key(|(_, site)| site.wpos.as_().distance(npc_pos) as i32)*/
1188                //choose random destination:
1189                .choose(&mut ctx.rng)
1190                {
1191                    ctx.controller.set_new_home(id)
1192                }
1193            } else if let Some(site) = data.sites.get(home) {
1194                dest_site = site.wpos.as_::<f32>()
1195            }
1196        }
1197        goto_2d_flying(
1198            pos,
1199            0.2,
1200            bearing_dist,
1201            8.0,
1202            8.0,
1203            ctx.npc.body.flying_height() * height_factor,
1204        )
1205            // If we are too far away from our waypoint position we can stop since we aren't going to a specific place.
1206            // If waypoint position is further away from destination site find a new waypoint
1207            .stop_if(move |ctx: &mut NpcCtx| {
1208                ctx.npc.wpos.xy().distance_squared(pos) > (bearing_dist + 5.0).powi(2)
1209                    || dest_site.distance_squared(pos) > dest_site.distance_squared(npc_pos)
1210            })
1211            // If waypoint position wasn't reached within 10 seconds we're probably stuck and need to find a new waypoint.
1212            .stop_if(timeout(10.0))
1213            .debug({
1214                let bearing = *bearing;
1215                move || format!("Moving with a bearing of {:?}", bearing)
1216            })
1217    })
1218        .repeat()
1219        .with_state(Vec2::<f32>::zero())
1220        .map(|_, _| ())
1221}
1222
1223fn monster() -> impl Action<DefaultState> {
1224    now(|ctx, bearing: &mut Vec2<f32>| {
1225        *bearing = bearing
1226            .map(|e| e + ctx.rng.gen_range(-0.1..0.1))
1227            .try_normalized()
1228            .unwrap_or_default();
1229        let bearing_dist = 24.0;
1230        let mut pos = ctx.npc.wpos.xy() + *bearing * bearing_dist;
1231        let is_deep_water = ctx
1232            .world
1233            .sim()
1234            .get(pos.as_().wpos_to_cpos())
1235            .is_none_or(|c| {
1236                c.alt - c.water_alt < -10.0 && (c.river.is_ocean() || c.river.is_lake())
1237            });
1238        if !is_deep_water {
1239            goto_2d(pos, 0.7, 8.0)
1240        } else {
1241            *bearing *= -1.0;
1242
1243            pos = ctx.npc.wpos.xy() + *bearing * 24.0;
1244
1245            goto_2d(pos, 0.7, 8.0)
1246        }
1247        // If we are too far away from our goal position we can stop since we aren't going to a specific place.
1248        .stop_if(move |ctx: &mut NpcCtx| {
1249            ctx.npc.wpos.xy().distance_squared(pos) > (bearing_dist + 5.0).powi(2)
1250        })
1251        .debug({
1252            let bearing = *bearing;
1253            move || format!("Moving with a bearing of {:?}", bearing)
1254        })
1255    })
1256    .repeat()
1257    .with_state(Vec2::<f32>::zero())
1258    .map(|_, _| ())
1259}
1260
1261fn think() -> impl Action<DefaultState> {
1262    now(|ctx, _| match ctx.npc.body {
1263        common::comp::Body::Humanoid(_) => humanoid().l().l().l(),
1264        common::comp::Body::BirdLarge(_) => bird_large().r().l().l(),
1265        _ => match &ctx.npc.role {
1266            Role::Civilised(_) => socialize()
1267                .map_state(|state: &mut DefaultState| &mut state.socialize_timer)
1268                .l()
1269                .r()
1270                .l(),
1271            Role::Monster => monster().r().r().l(),
1272            Role::Wild => idle().r(),
1273            Role::Vehicle => idle().r(),
1274        },
1275    })
1276}