muse2/simulation/
investment.rs

1//! Code for performing agent investment.
2use super::optimisation::{DispatchRun, FlowMap};
3use crate::agent::{Agent, AgentID};
4use crate::asset::{Asset, AssetCapacity, AssetIterator, AssetRef, AssetState};
5use crate::commodity::{Commodity, CommodityID, CommodityMap};
6use crate::model::Model;
7use crate::output::DataWriter;
8use crate::region::RegionID;
9use crate::simulation::CommodityPrices;
10use crate::time_slice::{TimeSliceID, TimeSliceInfo};
11use crate::units::{Capacity, Dimensionless, Flow, FlowPerCapacity};
12use anyhow::{Context, Result, ensure};
13use indexmap::IndexMap;
14use itertools::{Itertools, chain};
15use log::debug;
16use std::cmp::Ordering;
17use std::collections::{HashMap, HashSet};
18use std::fmt::Display;
19
20pub mod appraisal;
21use appraisal::coefficients::calculate_coefficients_for_assets;
22use appraisal::{AppraisalOutput, appraise_investment};
23
24/// A map of demand across time slices for a specific market
25type DemandMap = IndexMap<TimeSliceID, Flow>;
26
27/// Demand for a given combination of commodity, region and time slice
28type AllDemandMap = IndexMap<(CommodityID, RegionID, TimeSliceID), Flow>;
29
30/// Represents a set of markets which are invested in together.
31#[derive(PartialEq, Debug, Clone, Eq, Hash)]
32pub enum InvestmentSet {
33    /// Assets are selected for a single market using `select_assets_for_single_market`
34    Single((CommodityID, RegionID)),
35    /// Assets are selected for a group of markets which forms a cycle.
36    /// Experimental: handled by `select_assets_for_cycle` and guarded by the broken options
37    /// parameter.
38    Cycle(Vec<(CommodityID, RegionID)>),
39    /// Assets are selected for a layer of independent `InvestmentSet`s
40    Layer(Vec<InvestmentSet>),
41}
42
43impl InvestmentSet {
44    /// Recursively iterate over all markets contained in this `InvestmentSet`.
45    pub fn iter_markets<'a>(
46        &'a self,
47    ) -> Box<dyn Iterator<Item = &'a (CommodityID, RegionID)> + 'a> {
48        match self {
49            InvestmentSet::Single(market) => Box::new(std::iter::once(market)),
50            InvestmentSet::Cycle(markets) => Box::new(markets.iter()),
51            InvestmentSet::Layer(set) => Box::new(set.iter().flat_map(|s| s.iter_markets())),
52        }
53    }
54
55    /// Selects assets for this investment set variant and passes through the shared
56    /// context needed by single-market, cycle, or layered selection.
57    ///
58    /// # Arguments
59    ///
60    /// * `model` – Simulation model supplying parameters, processes, and dispatch.
61    /// * `year` – Planning year being solved.
62    /// * `demand` – Net demand profiles available to all markets before selection.
63    /// * `existing_assets` – Assets already commissioned in the system.
64    /// * `prices` – Commodity price assumptions to use when valuing investments.
65    /// * `seen_markets` – Markets for which investments have already been settled.
66    /// * `previously_selected_assets` – Assets chosen in earlier investment sets.
67    /// * `writer` – Data sink used to log optimisation artefacts.
68    #[allow(clippy::too_many_arguments)]
69    fn select_assets(
70        &self,
71        model: &Model,
72        year: u32,
73        demand: &AllDemandMap,
74        existing_assets: &[AssetRef],
75        prices: &CommodityPrices,
76        seen_markets: &[(CommodityID, RegionID)],
77        previously_selected_assets: &[AssetRef],
78        writer: &mut DataWriter,
79    ) -> Result<Vec<AssetRef>> {
80        match self {
81            InvestmentSet::Single((commodity_id, region_id)) => select_assets_for_single_market(
82                model,
83                commodity_id,
84                region_id,
85                year,
86                demand,
87                existing_assets,
88                prices,
89                writer,
90            ),
91            InvestmentSet::Cycle(markets) => {
92                debug!("Starting investment for cycle '{self}'");
93                select_assets_for_cycle(
94                    model,
95                    markets,
96                    year,
97                    demand,
98                    existing_assets,
99                    prices,
100                    seen_markets,
101                    previously_selected_assets,
102                    writer,
103                )
104                .with_context(|| {
105                    format!(
106                        "Investments failed for market set {self} with cyclical dependencies. \
107                         Please note that the investment algorithm is currently experimental for \
108                         models with circular commodity dependencies and may not be able to find \
109                         a solution in all cases."
110                    )
111                })
112            }
113            InvestmentSet::Layer(investment_sets) => {
114                debug!("Starting asset selection for layer '{self}'");
115                let mut all_assets = Vec::new();
116                for investment_set in investment_sets {
117                    let assets = investment_set.select_assets(
118                        model,
119                        year,
120                        demand,
121                        existing_assets,
122                        prices,
123                        seen_markets,
124                        previously_selected_assets,
125                        writer,
126                    )?;
127                    all_assets.extend(assets);
128                }
129                debug!("Completed asset selection for layer '{self}'");
130                Ok(all_assets)
131            }
132        }
133    }
134}
135
136impl Display for InvestmentSet {
137    fn fmt(&self, f: &mut std::fmt::Formatter<'_>) -> std::fmt::Result {
138        match self {
139            InvestmentSet::Single((commodity_id, region_id)) => {
140                write!(f, "{commodity_id}|{region_id}")
141            }
142            InvestmentSet::Cycle(markets) => {
143                write!(
144                    f,
145                    "({})",
146                    markets.iter().map(|(c, r)| format!("{c}|{r}")).join(", ")
147                )
148            }
149            InvestmentSet::Layer(ids) => {
150                write!(f, "[{}]", ids.iter().join(", "))
151            }
152        }
153    }
154}
155
156/// Perform agent investment to determine capacity investment of new assets for next milestone year.
157///
158/// # Arguments
159///
160/// * `model` - The model
161/// * `year` - Current milestone year
162/// * `existing_assets` - The asset pool (commissioned and otherwise)
163/// * `prices` - Commodity prices calculated in the previous full system dispatch
164/// * `writer` - Data writer
165///
166/// # Returns
167///
168/// The assets selected (including retained commissioned assets) for the given planning `year` or an
169/// error.
170pub fn perform_agent_investment(
171    model: &Model,
172    year: u32,
173    existing_assets: &[AssetRef],
174    prices: &CommodityPrices,
175    writer: &mut DataWriter,
176) -> Result<Vec<AssetRef>> {
177    // Initialise net demand map
178    let mut net_demand =
179        flatten_preset_demands_for_year(&model.commodities, &model.time_slice_info, year);
180
181    // Keep a list of all the assets selected
182    // This includes Commissioned assets that are selected for retention, and new Selected assets
183    let mut all_selected_assets = Vec::new();
184
185    let investment_order = &model.investment_order[&year];
186    debug!(
187        "Investment order for year '{year}': {}",
188        investment_order.iter().join(" -> ")
189    );
190
191    // Keep track of the markets that have been seen so far. This will be used to apply
192    // balance constraints in the dispatch optimisation - we only apply balance constraints for
193    // markets that have been seen so far.
194    let mut seen_markets = Vec::new();
195
196    // Iterate over investment sets in the investment order for this year
197    for investment_set in investment_order {
198        // Select assets for this investment set
199        let selected_assets = investment_set.select_assets(
200            model,
201            year,
202            &net_demand,
203            existing_assets,
204            prices,
205            &seen_markets,
206            &all_selected_assets,
207            writer,
208        )?;
209
210        // Update our list of seen markets
211        for market in investment_set.iter_markets() {
212            seen_markets.push(market.clone());
213        }
214
215        // If no assets have been selected, skip dispatch optimisation
216        // **TODO**: this probably means there's no demand for the market, which we could
217        // presumably preempt
218        if selected_assets.is_empty() {
219            debug!("No assets selected for '{investment_set}'");
220            continue;
221        }
222
223        // Add the selected assets to the list of all selected assets
224        all_selected_assets.extend(selected_assets.iter().cloned());
225
226        // Perform dispatch optimisation with assets that have been selected so far
227        // **TODO**: presumably we only need to do this for selected_assets, as assets added in
228        // previous iterations should not change
229        debug!("Running post-investment dispatch for '{investment_set}'");
230
231        // As upstream markets by definition will not yet have producers, we explicitly set
232        // their prices using external values so that they don't appear free
233        let solution = DispatchRun::new(model, &all_selected_assets, year)
234            .with_market_balance_subset(&seen_markets)
235            .with_input_prices(prices)
236            .run(&format!("post {investment_set} investment"), writer)?;
237
238        // Update demand map with flows from newly added assets
239        update_net_demand_map(
240            &mut net_demand,
241            &solution.create_flow_map(),
242            &selected_assets,
243        );
244    }
245
246    Ok(all_selected_assets)
247}
248
249/// Select assets for a single market in a given year
250///
251/// Returns a list of assets that are selected for investment for this market in this year.
252#[allow(clippy::too_many_arguments)]
253fn select_assets_for_single_market(
254    model: &Model,
255    commodity_id: &CommodityID,
256    region_id: &RegionID,
257    year: u32,
258    demand: &AllDemandMap,
259    existing_assets: &[AssetRef],
260    prices: &CommodityPrices,
261    writer: &mut DataWriter,
262) -> Result<Vec<AssetRef>> {
263    let commodity = &model.commodities[commodity_id];
264
265    let mut selected_assets = Vec::new();
266    for (agent, commodity_portion) in
267        get_responsible_agents(model.agents.values(), commodity_id, region_id, year)
268    {
269        debug!(
270            "Running asset selection for agent '{}' in market '{}|{}'",
271            &agent.id, commodity_id, region_id
272        );
273
274        // Get demand portion for this market for this agent in this year
275        let demand_portion_for_market = get_demand_portion_for_market(
276            &model.time_slice_info,
277            demand,
278            commodity_id,
279            region_id,
280            commodity_portion,
281        );
282
283        // Existing and candidate assets from which to choose
284        let opt_assets = get_asset_options(
285            &model.time_slice_info,
286            existing_assets,
287            &demand_portion_for_market,
288            agent,
289            commodity,
290            region_id,
291            year,
292        )
293        .collect();
294
295        // Choose assets from among existing pool and candidates
296        let best_assets = select_best_assets(
297            model,
298            opt_assets,
299            commodity,
300            agent,
301            region_id,
302            prices,
303            demand_portion_for_market,
304            year,
305            writer,
306        )?;
307        selected_assets.extend(best_assets);
308    }
309
310    Ok(selected_assets)
311}
312
313/// Iterates through the a pre-ordered set of markets forming a cycle, selecting assets for each
314/// market in turn.
315///
316/// Dispatch optimisation is performed after each market is visited to rebalance demand.
317/// While dispatching, newly selected (`Selected`) assets are given flexible capacity (bounded by
318/// `capacity_margin`) so small demand shifts caused by later markets can be absorbed. After all
319/// markets have been visited once, the final set of assets is returned, applying any capacity
320/// adjustments from the final full-system dispatch optimisation.
321///
322/// Dispatch may fail at any point if new demands are encountered for previously visited markets,
323/// and the `capacity_margin` is not sufficient to absorb the demand shift. At this point, the
324/// simulation is terminated with an error prompting the user to increase the `capacity_margin`.
325/// A longer-term solution (TODO) may be to trigger re-investment for the affected markets. Other
326/// yet-to-implement features may also help to stabilise the cycle, such as capacity growth limits.
327#[allow(clippy::too_many_arguments)]
328fn select_assets_for_cycle(
329    model: &Model,
330    markets: &[(CommodityID, RegionID)],
331    year: u32,
332    demand: &AllDemandMap,
333    existing_assets: &[AssetRef],
334    prices: &CommodityPrices,
335    seen_markets: &[(CommodityID, RegionID)],
336    previously_selected_assets: &[AssetRef],
337    writer: &mut DataWriter,
338) -> Result<Vec<AssetRef>> {
339    // Precompute a joined string for logging
340    let markets_str = markets.iter().map(|(c, r)| format!("{c}|{r}")).join(", ");
341
342    // Iterate over the markets to select assets
343    let mut current_demand = demand.clone();
344    let mut assets_for_cycle = IndexMap::new();
345    let mut last_solution = None;
346    for (idx, (commodity_id, region_id)) in markets.iter().enumerate() {
347        // Select assets for this market
348        let assets = select_assets_for_single_market(
349            model,
350            commodity_id,
351            region_id,
352            year,
353            &current_demand,
354            existing_assets,
355            prices,
356            writer,
357        )?;
358        assets_for_cycle.insert((commodity_id.clone(), region_id.clone()), assets);
359
360        // Assemble full list of assets for dispatch (previously selected + all chosen so far)
361        let mut all_assets = previously_selected_assets.to_vec();
362        let assets_for_cycle_flat: Vec<_> = assets_for_cycle
363            .values()
364            .flat_map(|v| v.iter().cloned())
365            .collect();
366        all_assets.extend_from_slice(&assets_for_cycle_flat);
367
368        // We balance all previously seen markets plus all cycle markets up to and including this one
369        let mut markets_to_balance = seen_markets.to_vec();
370        markets_to_balance.extend_from_slice(&markets[0..=idx]);
371
372        // We allow all `Selected` state assets to have flexible capacity
373        let flexible_capacity_assets: Vec<_> = assets_for_cycle_flat
374            .iter()
375            .filter(|asset| matches!(asset.state(), AssetState::Selected { .. }))
376            .cloned()
377            .collect();
378
379        // Run dispatch
380        let solution = DispatchRun::new(model, &all_assets, year)
381            .with_market_balance_subset(&markets_to_balance)
382            .with_flexible_capacity_assets(
383                &flexible_capacity_assets,
384                // Gives newly selected cycle assets limited capacity wiggle-room; existing assets stay fixed.
385                model.parameters.capacity_margin,
386            )
387            .run(
388                &format!("cycle ({markets_str}) post {commodity_id}|{region_id} investment",),
389                writer,
390            )
391            .with_context(|| {
392                format!(
393                    "Cycle balancing failed for cycle ({markets_str}), capacity_margin: {}. \
394                     Try increasing the capacity_margin.",
395                    model.parameters.capacity_margin
396                )
397            })?;
398
399        // Calculate new net demand map with all assets selected so far
400        current_demand.clone_from(demand);
401        update_net_demand_map(
402            &mut current_demand,
403            &solution.create_flow_map(),
404            &assets_for_cycle_flat,
405        );
406        last_solution = Some(solution);
407    }
408
409    // Finally, update flexible capacity assets based on the final solution
410    let mut all_cycle_assets: Vec<_> = assets_for_cycle.into_values().flatten().collect();
411    if let Some(solution) = last_solution {
412        let new_capacities: HashMap<_, _> = solution.iter_capacity().collect();
413        for asset in &mut all_cycle_assets {
414            if let Some(new_capacity) = new_capacities.get(asset) {
415                debug!(
416                    "Capacity of asset '{}' modified during cycle balancing ({} to {})",
417                    asset.process_id(),
418                    asset.capacity().total_capacity(),
419                    new_capacity.total_capacity()
420                );
421                asset.make_mut().set_capacity(*new_capacity);
422            }
423        }
424    }
425
426    Ok(all_cycle_assets)
427}
428
429/// Flatten the preset commodity demands for a given year into a map of commodity, region and
430/// time slice to demand.
431///
432/// Since demands for some commodities may be specified at a coarser time slice level, we need to
433/// distribute these demands over all time slices. Note: the way that we do this distribution is
434/// irrelevant, as demands will only be balanced to the appropriate level, but we still need to do
435/// this for the solver to work.
436///
437/// **TODO**: these assumptions may need to be revisited, e.g. when we come to storage technologies
438fn flatten_preset_demands_for_year(
439    commodities: &CommodityMap,
440    time_slice_info: &TimeSliceInfo,
441    year: u32,
442) -> AllDemandMap {
443    let mut demand_map = AllDemandMap::new();
444    for (commodity_id, commodity) in commodities {
445        for ((region_id, data_year, time_slice_selection), demand) in &commodity.demand {
446            if *data_year != year {
447                continue;
448            }
449
450            // We split the demand equally over all time slices in the selection
451            // NOTE: since demands will only be balanced to the time slice level of the commodity
452            // it doesn't matter how we do this distribution, only the total matters.
453            #[allow(clippy::cast_precision_loss)]
454            let n_time_slices = time_slice_selection.iter(time_slice_info).count() as f64;
455            let demand_per_slice = *demand / Dimensionless(n_time_slices);
456            for (time_slice, _) in time_slice_selection.iter(time_slice_info) {
457                demand_map.insert(
458                    (commodity_id.clone(), region_id.clone(), time_slice.clone()),
459                    demand_per_slice,
460                );
461            }
462        }
463    }
464    demand_map
465}
466
467/// Update net demand map with flows from a set of assets
468///
469/// Non-primary output flows are ignored. This way, demand profiles aren't affected by production
470/// of side-products from other assets. The result is that all commodity demands must be met by
471/// assets with that commodity as their primary output. Effectively, agents do not see production of
472/// side-products from other assets when making investment decisions.
473///
474/// TODO: this is a very flawed approach. The proper solution might be for agents to consider
475/// multiple commodities simultaneously, but that would require substantial work to implement.
476fn update_net_demand_map(demand: &mut AllDemandMap, flows: &FlowMap, assets: &[AssetRef]) {
477    for ((asset, commodity_id, time_slice), flow) in flows {
478        if assets.contains(asset) {
479            let key = (
480                commodity_id.clone(),
481                asset.region_id().clone(),
482                time_slice.clone(),
483            );
484
485            // Only consider input flows and output flows from the primary output commodity
486            // (excluding secondary outputs)
487            if (flow < &Flow(0.0))
488                || asset
489                    .primary_output()
490                    .is_some_and(|p| &p.commodity.id == commodity_id)
491            {
492                // Note: we use the negative of the flow as input flows are negative in the flow map.
493                demand
494                    .entry(key)
495                    .and_modify(|value| *value -= *flow)
496                    .or_insert(-*flow);
497            }
498        }
499    }
500}
501
502/// Get a portion of the demand profile for this market
503fn get_demand_portion_for_market(
504    time_slice_info: &TimeSliceInfo,
505    demand: &AllDemandMap,
506    commodity_id: &CommodityID,
507    region_id: &RegionID,
508    commodity_portion: Dimensionless,
509) -> DemandMap {
510    time_slice_info
511        .iter_ids()
512        .map(|time_slice| {
513            (
514                time_slice.clone(),
515                commodity_portion
516                    * *demand
517                        .get(&(commodity_id.clone(), region_id.clone(), time_slice.clone()))
518                        .unwrap_or(&Flow(0.0)),
519            )
520        })
521        .collect()
522}
523
524/// Get the agents responsible for a given market in a given year along with the commodity
525/// portion for which they are responsible
526fn get_responsible_agents<'a, I>(
527    agents: I,
528    commodity_id: &'a CommodityID,
529    region_id: &'a RegionID,
530    year: u32,
531) -> impl Iterator<Item = (&'a Agent, Dimensionless)>
532where
533    I: Iterator<Item = &'a Agent>,
534{
535    agents.filter_map(move |agent| {
536        if !agent.regions.contains(region_id) {
537            return None;
538        }
539        let portion = agent
540            .commodity_portions
541            .get(&(commodity_id.clone(), year))?;
542
543        Some((agent, *portion))
544    })
545}
546
547/// Get the maximum required capacity across time slices
548fn get_demand_limiting_capacity(
549    time_slice_info: &TimeSliceInfo,
550    asset: &Asset,
551    commodity: &Commodity,
552    demand: &DemandMap,
553) -> Capacity {
554    let coeff = asset.get_flow(&commodity.id).unwrap().coeff;
555    let mut capacity = Capacity(0.0);
556
557    for time_slice_selection in time_slice_info.iter_selections_at_level(commodity.time_slice_level)
558    {
559        let demand_for_selection: Flow = time_slice_selection
560            .iter(time_slice_info)
561            .map(|(time_slice, _)| demand[time_slice])
562            .sum();
563
564        // Calculate max capacity required for this time slice selection
565        // For commodities with a coarse time slice level, we have to allow the possibility that all
566        // of the demand gets served by production in a single time slice
567        for (time_slice, _) in time_slice_selection.iter(time_slice_info) {
568            let max_flow_per_cap =
569                *asset.get_activity_per_capacity_limits(time_slice).end() * coeff;
570            if max_flow_per_cap != FlowPerCapacity(0.0) {
571                capacity = capacity.max(demand_for_selection / max_flow_per_cap);
572            }
573        }
574    }
575
576    capacity
577}
578
579/// Get options from existing and potential assets for the given parameters
580fn get_asset_options<'a>(
581    time_slice_info: &'a TimeSliceInfo,
582    all_existing_assets: &'a [AssetRef],
583    demand: &'a DemandMap,
584    agent: &'a Agent,
585    commodity: &'a Commodity,
586    region_id: &'a RegionID,
587    year: u32,
588) -> impl Iterator<Item = AssetRef> + 'a {
589    // Get existing assets which produce the commodity of interest
590    let existing_assets = all_existing_assets
591        .iter()
592        .filter_agent(&agent.id)
593        .filter_region(region_id)
594        .filter_primary_producers_of(&commodity.id)
595        .cloned();
596
597    // Get candidates assets which produce the commodity of interest
598    let candidate_assets =
599        get_candidate_assets(time_slice_info, demand, agent, region_id, commodity, year);
600
601    chain(existing_assets, candidate_assets)
602}
603
604/// Get candidate assets which produce a particular commodity for a given agent
605fn get_candidate_assets<'a>(
606    time_slice_info: &'a TimeSliceInfo,
607    demand: &'a DemandMap,
608    agent: &'a Agent,
609    region_id: &'a RegionID,
610    commodity: &'a Commodity,
611    year: u32,
612) -> impl Iterator<Item = AssetRef> + 'a {
613    agent
614        .iter_possible_producers_of(region_id, &commodity.id, year)
615        .map(move |process| {
616            let mut asset =
617                Asset::new_candidate(process.clone(), region_id.clone(), Capacity(0.0), year)
618                    .unwrap();
619
620            // Set capacity based on demand
621            // This will serve as the upper limit when appraising the asset
622            let capacity = get_demand_limiting_capacity(time_slice_info, &asset, commodity, demand);
623            let asset_capacity = AssetCapacity::from_capacity(capacity, asset.unit_size());
624            asset.set_capacity(asset_capacity);
625
626            asset.into()
627        })
628}
629
630/// Print debug message if there are multiple equally good outputs
631fn warn_on_equal_appraisal_outputs(
632    outputs: &[AppraisalOutput],
633    agent_id: &AgentID,
634    commodity_id: &CommodityID,
635    region_id: &RegionID,
636) {
637    if outputs.is_empty() {
638        return;
639    }
640
641    // Count the number of identical (or nearly identical) appraisal outputs
642    let num_identical = outputs[1..]
643        .iter()
644        .take_while(|output| outputs[0].compare_metric(output).is_eq())
645        .count();
646
647    if num_identical > 0 {
648        let asset_details = outputs[..=num_identical]
649            .iter()
650            .map(|output| {
651                let asset = &output.asset;
652                format!(
653                    "Process ID: '{}' (State: {}{}, Commission year: {})",
654                    asset.process_id(),
655                    asset.state(),
656                    asset
657                        .id()
658                        .map(|id| format!(", Asset ID: {id}"))
659                        .unwrap_or_default(),
660                    asset.commission_year()
661                )
662            })
663            .join(", ");
664        debug!(
665            "Found equally good appraisals for Agent ID: {agent_id}, Commodity: '{commodity_id}', \
666            Region: {region_id}. Options: [{asset_details}]. Selecting first option.",
667        );
668    }
669}
670
671/// Get the best assets for meeting demand for the given commodity
672#[allow(clippy::too_many_arguments)]
673fn select_best_assets(
674    model: &Model,
675    mut opt_assets: Vec<AssetRef>,
676    commodity: &Commodity,
677    agent: &Agent,
678    region_id: &RegionID,
679    prices: &CommodityPrices,
680    mut demand: DemandMap,
681    year: u32,
682    writer: &mut DataWriter,
683) -> Result<Vec<AssetRef>> {
684    let objective_type = &agent.objectives[&year];
685
686    // Calculate coefficients for all asset options according to the agent's objective
687    let coefficients =
688        calculate_coefficients_for_assets(model, objective_type, &opt_assets, prices, year);
689
690    let mut remaining_candidate_capacity = HashMap::from_iter(
691        opt_assets
692            .iter()
693            .filter(|asset| !asset.is_commissioned())
694            .map(|asset| (asset.clone(), asset.capacity())),
695    );
696
697    let mut round = 0;
698    let mut best_assets: Vec<AssetRef> = Vec::new();
699    while is_any_remaining_demand(&demand) {
700        ensure!(
701            !opt_assets.is_empty(),
702            "Failed to meet demand for commodity '{}' with provided assets",
703            &commodity.id
704        );
705
706        // Since all assets with the same `group_id` are identical, we only need to appraise one
707        // from each group.
708        let mut seen_groups = HashSet::new();
709
710        // Appraise all options
711        let mut outputs_for_opts = Vec::new();
712        for asset in &opt_assets {
713            let max_capacity = (!asset.is_commissioned()).then(|| {
714                let max_capacity = asset
715                    .capacity()
716                    .apply_limit_factor(model.parameters.capacity_limit_factor);
717
718                let remaining_capacity = remaining_candidate_capacity[asset];
719                max_capacity.min(remaining_capacity)
720            });
721
722            // Skip any assets from groups we've already seen
723            if let Some(group_id) = asset.group_id()
724                && !seen_groups.insert(group_id)
725            {
726                continue;
727            }
728
729            let output = appraise_investment(
730                model,
731                asset,
732                max_capacity,
733                commodity,
734                objective_type,
735                &coefficients[asset],
736                &demand,
737            )?;
738            outputs_for_opts.push(output);
739        }
740
741        // Save appraisal results
742        writer.write_appraisal_debug_info(
743            year,
744            &format!("{} {} round {}", &commodity.id, &agent.id, round),
745            &outputs_for_opts,
746        )?;
747
748        // Sort assets by appraisal metric
749        let assets_sorted_by_metric = outputs_for_opts
750            .into_iter()
751            .filter(|output| output.capacity.total_capacity() > Capacity(0.0))
752            .sorted_by(|output1, output2| match output1.compare_metric(output2) {
753                // If equal, we fall back on comparing asset properties
754                Ordering::Equal => compare_asset_fallback(&output1.asset, &output2.asset),
755                cmp => cmp,
756            })
757            .collect_vec();
758
759        // Check if all options have zero capacity. If so, we cannot meet demand, so have to bail
760        // out.
761        //
762        // This may happen if:
763        // - the asset has zero activity limits for all time slices with
764        // demand.
765        // - known issue with the NPV objective
766        // (see https://github.com/EnergySystemsModellingLab/MUSE2/issues/716).
767        ensure!(
768            !assets_sorted_by_metric.is_empty(),
769            "No feasible investment options for commodity '{}' after appraisal",
770            &commodity.id
771        );
772
773        // Warn if there are multiple equally good assets
774        warn_on_equal_appraisal_outputs(
775            &assets_sorted_by_metric,
776            &agent.id,
777            &commodity.id,
778            region_id,
779        );
780
781        let best_output = assets_sorted_by_metric.into_iter().next().unwrap();
782
783        // Log the selected asset
784        debug!(
785            "Selected {} asset '{}' (capacity: {})",
786            &best_output.asset.state(),
787            &best_output.asset.process_id(),
788            best_output.capacity.total_capacity()
789        );
790
791        // Update the assets
792        update_assets(
793            best_output.asset,
794            best_output.capacity,
795            &mut opt_assets,
796            &mut remaining_candidate_capacity,
797            &mut best_assets,
798        );
799
800        demand = best_output.unmet_demand;
801        round += 1;
802    }
803
804    // Convert Candidate assets to Selected
805    // At this point we also assign the agent ID to the asset
806    for asset in &mut best_assets {
807        if let AssetState::Candidate = asset.state() {
808            asset
809                .make_mut()
810                .select_candidate_for_investment(agent.id.clone());
811        }
812    }
813
814    Ok(best_assets)
815}
816
817/// Check whether there is any remaining demand that is unmet in any time slice
818fn is_any_remaining_demand(demand: &DemandMap) -> bool {
819    demand.values().any(|flow| *flow > Flow(0.0))
820}
821
822/// Compare assets as a fallback if metrics are equal.
823///
824/// Commissioned assets are ordered before uncommissioned and newer before older.
825///
826/// Used as a fallback to sort assets when they have equal appraisal tool outputs.
827fn compare_asset_fallback(asset1: &Asset, asset2: &Asset) -> Ordering {
828    (asset2.is_commissioned(), asset2.commission_year())
829        .cmp(&(asset1.is_commissioned(), asset1.commission_year()))
830}
831
832/// Update capacity of chosen asset, if needed, and update both asset options and chosen assets
833fn update_assets(
834    mut best_asset: AssetRef,
835    capacity: AssetCapacity,
836    opt_assets: &mut Vec<AssetRef>,
837    remaining_candidate_capacity: &mut HashMap<AssetRef, AssetCapacity>,
838    best_assets: &mut Vec<AssetRef>,
839) {
840    match best_asset.state() {
841        AssetState::Commissioned { .. } => {
842            // Remove this asset from the options
843            opt_assets.retain(|asset| *asset != best_asset);
844            best_assets.push(best_asset);
845        }
846        AssetState::Candidate => {
847            // Remove this capacity from the available remaining capacity for this asset
848            let remaining_capacity = remaining_candidate_capacity.get_mut(&best_asset).unwrap();
849            *remaining_capacity = *remaining_capacity - capacity;
850
851            // If there's no capacity remaining, remove the asset from the options
852            if remaining_capacity.total_capacity() <= Capacity(0.0) {
853                let old_idx = opt_assets
854                    .iter()
855                    .position(|asset| *asset == best_asset)
856                    .unwrap();
857                opt_assets.swap_remove(old_idx);
858                remaining_candidate_capacity.remove(&best_asset);
859            }
860
861            if let Some(existing_asset) = best_assets.iter_mut().find(|asset| **asset == best_asset)
862            {
863                // If the asset is already in the list of best assets, add the additional required capacity
864                existing_asset.make_mut().increase_capacity(capacity);
865            } else {
866                // Otherwise, update the capacity of the chosen asset and add it to the list of best assets
867                best_asset.make_mut().set_capacity(capacity);
868                best_assets.push(best_asset);
869            }
870        }
871        _ => panic!("update_assets should only be called with Commissioned or Candidate assets"),
872    }
873}
874
875#[cfg(test)]
876mod tests {
877    use super::*;
878    use crate::agent::AgentID;
879    use crate::asset::Asset;
880    use crate::commodity::Commodity;
881    use crate::fixture::{
882        agent_id, asset, process, process_activity_limits_map, process_flows_map, region_id,
883        svd_commodity, time_slice, time_slice_info, time_slice_info2,
884    };
885    use crate::process::{ActivityLimits, FlowType, Process, ProcessFlow};
886    use crate::region::RegionID;
887    use crate::time_slice::{TimeSliceID, TimeSliceInfo};
888    use crate::units::{Capacity, Flow, FlowPerActivity, MoneyPerFlow};
889    use indexmap::indexmap;
890    use rstest::rstest;
891    use std::rc::Rc;
892
893    #[rstest]
894    fn get_demand_limiting_capacity_works(
895        time_slice: TimeSliceID,
896        time_slice_info: TimeSliceInfo,
897        svd_commodity: Commodity,
898        mut process: Process,
899    ) {
900        // Add flows for the process using the existing commodity fixture
901        let commodity_rc = Rc::new(svd_commodity);
902        let process_flow = ProcessFlow {
903            commodity: Rc::clone(&commodity_rc),
904            coeff: FlowPerActivity(2.0), // 2 units of flow per unit of activity
905            kind: FlowType::Fixed,
906            cost: MoneyPerFlow(0.0),
907        };
908        let process_flows = indexmap! { commodity_rc.id.clone() => process_flow.clone() };
909        let process_flows_map = process_flows_map(process.regions.clone(), Rc::new(process_flows));
910        process.flows = process_flows_map;
911
912        // Create asset with the configured process
913        let asset = asset(process);
914
915        // Create demand map - demand of 10.0 for our time slice
916        let demand = indexmap! { time_slice.clone() => Flow(10.0)};
917
918        // Call the function
919        let result = get_demand_limiting_capacity(&time_slice_info, &asset, &commodity_rc, &demand);
920
921        // Expected calculation:
922        // max_flow_per_cap = activity_per_capacity_limit (1.0) * coeff (2.0) = 2.0
923        // required_capacity = demand (10.0) / max_flow_per_cap (2.0) = 5.0
924        assert_eq!(result, Capacity(5.0));
925    }
926
927    #[rstest]
928    fn get_demand_limiting_capacity_multiple_time_slices(
929        time_slice_info2: TimeSliceInfo,
930        svd_commodity: Commodity,
931        mut process: Process,
932    ) {
933        let (time_slice1, time_slice2) =
934            time_slice_info2.time_slices.keys().collect_tuple().unwrap();
935
936        // Add flows for the process using the existing commodity fixture
937        let commodity_rc = Rc::new(svd_commodity);
938        let process_flow = ProcessFlow {
939            commodity: Rc::clone(&commodity_rc),
940            coeff: FlowPerActivity(1.0), // 1 unit of flow per unit of activity
941            kind: FlowType::Fixed,
942            cost: MoneyPerFlow(0.0),
943        };
944        let process_flows = indexmap! { commodity_rc.id.clone() => process_flow.clone() };
945        let process_flows_map = process_flows_map(process.regions.clone(), Rc::new(process_flows));
946        process.flows = process_flows_map;
947
948        // Add activity limits for the process
949        let mut limits = ActivityLimits::new_with_full_availability(&time_slice_info2);
950        limits.add_time_slice_limit(time_slice1.clone(), Dimensionless(0.0)..=Dimensionless(0.2));
951        limits.add_time_slice_limit(time_slice2.clone(), Dimensionless(0.0)..=Dimensionless(0.0));
952        let limits_map = process_activity_limits_map(process.regions.clone(), limits);
953        process.activity_limits = limits_map;
954
955        // Create asset with the configured process
956        let asset = asset(process);
957
958        // Create demand map with different demands for each time slice
959        let demand = indexmap! {
960            time_slice1.clone() => Flow(4.0), // Requires capacity of 4.0/0.2 = 20.0
961            time_slice2.clone() => Flow(3.0), // Would require infinite capacity, but should be skipped
962        };
963
964        // Call the function
965        let result =
966            get_demand_limiting_capacity(&time_slice_info2, &asset, &commodity_rc, &demand);
967
968        // Expected: maximum of the capacity requirements across time slices (excluding zero limit)
969        // Time slice 1: demand (4.0) / (activity_limit (0.2) * coeff (1.0)) = 20.0
970        // Time slice 2: skipped due to zero activity limit
971        // Maximum = 20.0
972        assert_eq!(result, Capacity(20.0));
973    }
974
975    #[rstest]
976    fn compare_assets_fallback(process: Process, region_id: RegionID, agent_id: AgentID) {
977        let process = Rc::new(process);
978        let capacity = Capacity(2.0);
979        let asset1 = Asset::new_commissioned(
980            agent_id.clone(),
981            process.clone(),
982            region_id.clone(),
983            capacity,
984            2015,
985        )
986        .unwrap();
987        let asset2 =
988            Asset::new_candidate(process.clone(), region_id.clone(), capacity, 2015).unwrap();
989        let asset3 =
990            Asset::new_commissioned(agent_id, process, region_id.clone(), capacity, 2010).unwrap();
991
992        assert!(compare_asset_fallback(&asset1, &asset1).is_eq());
993        assert!(compare_asset_fallback(&asset2, &asset2).is_eq());
994        assert!(compare_asset_fallback(&asset3, &asset3).is_eq());
995        assert!(compare_asset_fallback(&asset1, &asset2).is_lt());
996        assert!(compare_asset_fallback(&asset2, &asset1).is_gt());
997        assert!(compare_asset_fallback(&asset1, &asset3).is_lt());
998        assert!(compare_asset_fallback(&asset3, &asset1).is_gt());
999        assert!(compare_asset_fallback(&asset3, &asset2).is_lt());
1000        assert!(compare_asset_fallback(&asset2, &asset3).is_gt());
1001    }
1002}