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