style/
custom_properties.rs

1/* This Source Code Form is subject to the terms of the Mozilla Public
2 * License, v. 2.0. If a copy of the MPL was not distributed with this
3 * file, You can obtain one at https://mozilla.org/MPL/2.0/. */
4
5//! Support for [custom properties for cascading variables][custom].
6//!
7//! [custom]: https://drafts.csswg.org/css-variables/
8
9use crate::applicable_declarations::CascadePriority;
10use crate::custom_properties_map::CustomPropertiesMap;
11use crate::media_queries::Device;
12use crate::properties::{
13    CSSWideKeyword, CustomDeclaration, CustomDeclarationValue, LonghandId, LonghandIdSet,
14    PropertyDeclaration,
15};
16use crate::properties_and_values::{
17    registry::PropertyRegistrationData,
18    syntax::data_type::DependentDataTypes,
19    value::{
20        AllowComputationallyDependent, ComputedValue as ComputedRegisteredValue,
21        SpecifiedValue as SpecifiedRegisteredValue,
22    },
23};
24use crate::selector_map::{PrecomputedHashMap, PrecomputedHashSet};
25use crate::stylesheets::UrlExtraData;
26use crate::stylist::Stylist;
27use crate::values::computed::{self, ToComputedValue};
28use crate::values::specified::FontRelativeLength;
29use crate::Atom;
30use cssparser::{
31    CowRcStr, Delimiter, Parser, ParserInput, SourcePosition, Token, TokenSerializationType,
32};
33use selectors::parser::SelectorParseErrorKind;
34use servo_arc::Arc;
35use smallvec::SmallVec;
36use std::borrow::Cow;
37use std::collections::hash_map::Entry;
38use std::fmt::{self, Write};
39use std::ops::{Index, IndexMut};
40use std::{cmp, num};
41use style_traits::{CssWriter, ParseError, StyleParseErrorKind, ToCss};
42
43/// The environment from which to get `env` function values.
44///
45/// TODO(emilio): If this becomes a bit more complex we should probably move it
46/// to the `media_queries` module, or something.
47#[derive(Debug, MallocSizeOf)]
48pub struct CssEnvironment;
49
50type EnvironmentEvaluator = fn(device: &Device, url_data: &UrlExtraData) -> VariableValue;
51
52struct EnvironmentVariable {
53    name: Atom,
54    evaluator: EnvironmentEvaluator,
55}
56
57macro_rules! make_variable {
58    ($name:expr, $evaluator:expr) => {{
59        EnvironmentVariable {
60            name: $name,
61            evaluator: $evaluator,
62        }
63    }};
64}
65
66fn get_safearea_inset_top(device: &Device, url_data: &UrlExtraData) -> VariableValue {
67    VariableValue::pixels(device.safe_area_insets().top, url_data)
68}
69
70fn get_safearea_inset_bottom(device: &Device, url_data: &UrlExtraData) -> VariableValue {
71    VariableValue::pixels(device.safe_area_insets().bottom, url_data)
72}
73
74fn get_safearea_inset_left(device: &Device, url_data: &UrlExtraData) -> VariableValue {
75    VariableValue::pixels(device.safe_area_insets().left, url_data)
76}
77
78fn get_safearea_inset_right(device: &Device, url_data: &UrlExtraData) -> VariableValue {
79    VariableValue::pixels(device.safe_area_insets().right, url_data)
80}
81
82#[cfg(feature = "gecko")]
83fn get_content_preferred_color_scheme(device: &Device, url_data: &UrlExtraData) -> VariableValue {
84    use crate::queries::values::PrefersColorScheme;
85    let prefers_color_scheme = unsafe {
86        crate::gecko_bindings::bindings::Gecko_MediaFeatures_PrefersColorScheme(
87            device.document(),
88            /* use_content = */ true,
89        )
90    };
91    VariableValue::ident(
92        match prefers_color_scheme {
93            PrefersColorScheme::Light => "light",
94            PrefersColorScheme::Dark => "dark",
95        },
96        url_data,
97    )
98}
99
100#[cfg(feature = "servo")]
101fn get_content_preferred_color_scheme(_device: &Device, url_data: &UrlExtraData) -> VariableValue {
102    // TODO: Add an implementation for Servo.
103    VariableValue::ident("light", url_data)
104}
105
106fn get_scrollbar_inline_size(device: &Device, url_data: &UrlExtraData) -> VariableValue {
107    VariableValue::pixels(device.scrollbar_inline_size().px(), url_data)
108}
109
110fn get_hairline(device: &Device, url_data: &UrlExtraData) -> VariableValue {
111    VariableValue::pixels(
112        app_units::Au(device.app_units_per_device_pixel()).to_f32_px(),
113        url_data,
114    )
115}
116
117static ENVIRONMENT_VARIABLES: [EnvironmentVariable; 4] = [
118    make_variable!(atom!("safe-area-inset-top"), get_safearea_inset_top),
119    make_variable!(atom!("safe-area-inset-bottom"), get_safearea_inset_bottom),
120    make_variable!(atom!("safe-area-inset-left"), get_safearea_inset_left),
121    make_variable!(atom!("safe-area-inset-right"), get_safearea_inset_right),
122];
123
124#[cfg(feature = "gecko")]
125macro_rules! lnf_int {
126    ($id:ident) => {
127        unsafe {
128            crate::gecko_bindings::bindings::Gecko_GetLookAndFeelInt(
129                crate::gecko_bindings::bindings::LookAndFeel_IntID::$id as i32,
130            )
131        }
132    };
133}
134
135#[cfg(feature = "servo")]
136macro_rules! lnf_int {
137    ($id:ident) => {
138        // TODO: Add an implementation for Servo.
139        0
140    };
141}
142
143macro_rules! lnf_int_variable {
144    ($atom:expr, $id:ident, $ctor:ident) => {{
145        fn __eval(_: &Device, url_data: &UrlExtraData) -> VariableValue {
146            VariableValue::$ctor(lnf_int!($id), url_data)
147        }
148        make_variable!($atom, __eval)
149    }};
150}
151
152fn eval_gtk_csd_titlebar_radius(device: &Device, url_data: &UrlExtraData) -> VariableValue {
153    let int_pixels = lnf_int!(TitlebarRadius);
154    let unzoomed_scale =
155        device.device_pixel_ratio_ignoring_full_zoom().get() / device.device_pixel_ratio().get();
156    VariableValue::pixels(int_pixels as f32 * unzoomed_scale, url_data)
157}
158
159static CHROME_ENVIRONMENT_VARIABLES: [EnvironmentVariable; 9] = [
160    make_variable!(
161        atom!("-moz-gtk-csd-titlebar-radius"),
162        eval_gtk_csd_titlebar_radius
163    ),
164    lnf_int_variable!(
165        atom!("-moz-gtk-csd-tooltip-radius"),
166        TooltipRadius,
167        int_pixels
168    ),
169    lnf_int_variable!(
170        atom!("-moz-gtk-csd-close-button-position"),
171        GTKCSDCloseButtonPosition,
172        integer
173    ),
174    lnf_int_variable!(
175        atom!("-moz-gtk-csd-minimize-button-position"),
176        GTKCSDMinimizeButtonPosition,
177        integer
178    ),
179    lnf_int_variable!(
180        atom!("-moz-gtk-csd-maximize-button-position"),
181        GTKCSDMaximizeButtonPosition,
182        integer
183    ),
184    lnf_int_variable!(
185        atom!("-moz-overlay-scrollbar-fade-duration"),
186        ScrollbarFadeDuration,
187        int_ms
188    ),
189    make_variable!(
190        atom!("-moz-content-preferred-color-scheme"),
191        get_content_preferred_color_scheme
192    ),
193    make_variable!(atom!("scrollbar-inline-size"), get_scrollbar_inline_size),
194    make_variable!(atom!("hairline"), get_hairline),
195];
196
197impl CssEnvironment {
198    #[inline]
199    fn get(&self, name: &Atom, device: &Device, url_data: &UrlExtraData) -> Option<VariableValue> {
200        if let Some(var) = ENVIRONMENT_VARIABLES.iter().find(|var| var.name == *name) {
201            return Some((var.evaluator)(device, url_data));
202        }
203        if !url_data.chrome_rules_enabled() {
204            return None;
205        }
206        let var = CHROME_ENVIRONMENT_VARIABLES
207            .iter()
208            .find(|var| var.name == *name)?;
209        Some((var.evaluator)(device, url_data))
210    }
211}
212
213/// A custom property name is just an `Atom`.
214///
215/// Note that this does not include the `--` prefix
216pub type Name = Atom;
217
218/// Parse a custom property name.
219///
220/// <https://drafts.csswg.org/css-variables/#typedef-custom-property-name>
221pub fn parse_name(s: &str) -> Result<&str, ()> {
222    if s.starts_with("--") && s.len() > 2 {
223        Ok(&s[2..])
224    } else {
225        Err(())
226    }
227}
228
229/// A value for a custom property is just a set of tokens.
230///
231/// We preserve the original CSS for serialization, and also the variable
232/// references to other custom property names.
233#[derive(Clone, Debug, MallocSizeOf, ToShmem)]
234pub struct VariableValue {
235    /// The raw CSS string.
236    pub css: String,
237
238    /// The url data of the stylesheet where this value came from.
239    pub url_data: UrlExtraData,
240
241    first_token_type: TokenSerializationType,
242    last_token_type: TokenSerializationType,
243
244    /// var(), env(), or non-custom property (e.g. through `em`) references.
245    references: References,
246}
247
248trivial_to_computed_value!(VariableValue);
249
250/// Given a potentially registered variable value turn it into a computed custom property value.
251pub fn compute_variable_value(
252    value: &Arc<VariableValue>,
253    registration: &PropertyRegistrationData,
254    computed_context: &computed::Context,
255) -> Option<ComputedRegisteredValue> {
256    if registration.syntax.is_universal() {
257        return Some(ComputedRegisteredValue::universal(Arc::clone(value)));
258    }
259    compute_value(&value.css, &value.url_data, registration, computed_context).ok()
260}
261
262// For all purposes, we want values to be considered equal if their css text is equal.
263impl PartialEq for VariableValue {
264    fn eq(&self, other: &Self) -> bool {
265        self.css == other.css
266    }
267}
268
269impl Eq for VariableValue {}
270
271impl ToCss for SpecifiedValue {
272    fn to_css<W>(&self, dest: &mut CssWriter<W>) -> fmt::Result
273    where
274        W: Write,
275    {
276        dest.write_str(&self.css)
277    }
278}
279
280/// A pair of separate CustomPropertiesMaps, split between custom properties
281/// that have the inherit flag set and those with the flag unset.
282#[repr(C)]
283#[derive(Clone, Debug, Default, PartialEq)]
284pub struct ComputedCustomProperties {
285    /// Map for custom properties with inherit flag set, including non-registered
286    /// ones.
287    pub inherited: CustomPropertiesMap,
288    /// Map for custom properties with inherit flag unset.
289    pub non_inherited: CustomPropertiesMap,
290}
291
292impl ComputedCustomProperties {
293    /// Return whether the inherited and non_inherited maps are none.
294    pub fn is_empty(&self) -> bool {
295        self.inherited.is_empty() && self.non_inherited.is_empty()
296    }
297
298    /// Return the name and value of the property at specified index, if any.
299    pub fn property_at(&self, index: usize) -> Option<(&Name, &Option<ComputedRegisteredValue>)> {
300        // Just expose the custom property items from custom_properties.inherited, followed
301        // by custom property items from custom_properties.non_inherited.
302        self.inherited
303            .get_index(index)
304            .or_else(|| self.non_inherited.get_index(index - self.inherited.len()))
305    }
306
307    /// Insert a custom property in the corresponding inherited/non_inherited
308    /// map, depending on whether the inherit flag is set or unset.
309    fn insert(
310        &mut self,
311        registration: &PropertyRegistrationData,
312        name: &Name,
313        value: ComputedRegisteredValue,
314    ) {
315        self.map_mut(registration).insert(name, value)
316    }
317
318    /// Remove a custom property from the corresponding inherited/non_inherited
319    /// map, depending on whether the inherit flag is set or unset.
320    fn remove(&mut self, registration: &PropertyRegistrationData, name: &Name) {
321        self.map_mut(registration).remove(name);
322    }
323
324    /// Shrink the capacity of the inherited maps as much as possible.
325    fn shrink_to_fit(&mut self) {
326        self.inherited.shrink_to_fit();
327        self.non_inherited.shrink_to_fit();
328    }
329
330    fn map_mut(&mut self, registration: &PropertyRegistrationData) -> &mut CustomPropertiesMap {
331        if registration.inherits() {
332            &mut self.inherited
333        } else {
334            &mut self.non_inherited
335        }
336    }
337
338    /// Returns the relevant custom property value given a registration.
339    pub fn get(
340        &self,
341        registration: &PropertyRegistrationData,
342        name: &Name,
343    ) -> Option<&ComputedRegisteredValue> {
344        if registration.inherits() {
345            self.inherited.get(name)
346        } else {
347            self.non_inherited.get(name)
348        }
349    }
350}
351
352/// Both specified and computed values are VariableValues, the difference is
353/// whether var() functions are expanded.
354pub type SpecifiedValue = VariableValue;
355/// Both specified and computed values are VariableValues, the difference is
356/// whether var() functions are expanded.
357pub type ComputedValue = VariableValue;
358
359/// Set of flags to non-custom references this custom property makes.
360#[derive(Clone, Copy, Debug, Default, PartialEq, Eq, MallocSizeOf, ToShmem)]
361struct NonCustomReferences(u8);
362
363bitflags! {
364    impl NonCustomReferences: u8 {
365        /// At least one custom property depends on font-relative units.
366        const FONT_UNITS = 1 << 0;
367        /// At least one custom property depends on root element's font-relative units.
368        const ROOT_FONT_UNITS = 1 << 1;
369        /// At least one custom property depends on line height units.
370        const LH_UNITS = 1 << 2;
371        /// At least one custom property depends on root element's line height units.
372        const ROOT_LH_UNITS = 1 << 3;
373        /// All dependencies not depending on the root element.
374        const NON_ROOT_DEPENDENCIES = Self::FONT_UNITS.0 | Self::LH_UNITS.0;
375        /// All dependencies depending on the root element.
376        const ROOT_DEPENDENCIES = Self::ROOT_FONT_UNITS.0 | Self::ROOT_LH_UNITS.0;
377    }
378}
379
380impl NonCustomReferences {
381    fn for_each<F>(&self, mut f: F)
382    where
383        F: FnMut(SingleNonCustomReference),
384    {
385        for (_, r) in self.iter_names() {
386            let single = match r {
387                Self::FONT_UNITS => SingleNonCustomReference::FontUnits,
388                Self::ROOT_FONT_UNITS => SingleNonCustomReference::RootFontUnits,
389                Self::LH_UNITS => SingleNonCustomReference::LhUnits,
390                Self::ROOT_LH_UNITS => SingleNonCustomReference::RootLhUnits,
391                _ => unreachable!("Unexpected single bit value"),
392            };
393            f(single);
394        }
395    }
396
397    fn from_unit(value: &CowRcStr) -> Self {
398        // For registered properties, any reference to font-relative dimensions
399        // make it dependent on font-related properties.
400        // TODO(dshin): When we unit algebra gets implemented and handled -
401        // Is it valid to say that `calc(1em / 2em * 3px)` triggers this?
402        if value.eq_ignore_ascii_case(FontRelativeLength::LH) {
403            return Self::FONT_UNITS | Self::LH_UNITS;
404        }
405        if value.eq_ignore_ascii_case(FontRelativeLength::EM)
406            || value.eq_ignore_ascii_case(FontRelativeLength::EX)
407            || value.eq_ignore_ascii_case(FontRelativeLength::CAP)
408            || value.eq_ignore_ascii_case(FontRelativeLength::CH)
409            || value.eq_ignore_ascii_case(FontRelativeLength::IC)
410        {
411            return Self::FONT_UNITS;
412        }
413        if value.eq_ignore_ascii_case(FontRelativeLength::RLH) {
414            return Self::ROOT_FONT_UNITS | Self::ROOT_LH_UNITS;
415        }
416        if value.eq_ignore_ascii_case(FontRelativeLength::REM) {
417            return Self::ROOT_FONT_UNITS;
418        }
419        Self::empty()
420    }
421}
422
423#[derive(Clone, Copy, Debug, Eq, PartialEq)]
424enum SingleNonCustomReference {
425    FontUnits = 0,
426    RootFontUnits,
427    LhUnits,
428    RootLhUnits,
429}
430
431struct NonCustomReferenceMap<T>([Option<T>; 4]);
432
433impl<T> Default for NonCustomReferenceMap<T> {
434    fn default() -> Self {
435        NonCustomReferenceMap(Default::default())
436    }
437}
438
439impl<T> Index<SingleNonCustomReference> for NonCustomReferenceMap<T> {
440    type Output = Option<T>;
441
442    fn index(&self, reference: SingleNonCustomReference) -> &Self::Output {
443        &self.0[reference as usize]
444    }
445}
446
447impl<T> IndexMut<SingleNonCustomReference> for NonCustomReferenceMap<T> {
448    fn index_mut(&mut self, reference: SingleNonCustomReference) -> &mut Self::Output {
449        &mut self.0[reference as usize]
450    }
451}
452
453/// Whether to defer resolving custom properties referencing font relative units.
454#[derive(Clone, Copy, PartialEq, Eq)]
455#[allow(missing_docs)]
456pub enum DeferFontRelativeCustomPropertyResolution {
457    Yes,
458    No,
459}
460
461#[derive(Clone, Debug, MallocSizeOf, PartialEq, ToShmem)]
462struct VariableFallback {
463    start: num::NonZeroUsize,
464    first_token_type: TokenSerializationType,
465    last_token_type: TokenSerializationType,
466}
467
468#[derive(Clone, Debug, MallocSizeOf, PartialEq, ToShmem)]
469struct VarOrEnvReference {
470    name: Name,
471    start: usize,
472    end: usize,
473    fallback: Option<VariableFallback>,
474    prev_token_type: TokenSerializationType,
475    next_token_type: TokenSerializationType,
476    is_var: bool,
477}
478
479/// A struct holding information about the external references to that a custom
480/// property value may have.
481#[derive(Clone, Debug, Default, MallocSizeOf, PartialEq, ToShmem)]
482struct References {
483    refs: Vec<VarOrEnvReference>,
484    non_custom_references: NonCustomReferences,
485    any_env: bool,
486    any_var: bool,
487}
488
489impl References {
490    fn has_references(&self) -> bool {
491        !self.refs.is_empty()
492    }
493
494    fn non_custom_references(&self, is_root_element: bool) -> NonCustomReferences {
495        let mut mask = NonCustomReferences::NON_ROOT_DEPENDENCIES;
496        if is_root_element {
497            mask |= NonCustomReferences::ROOT_DEPENDENCIES
498        }
499        self.non_custom_references & mask
500    }
501}
502
503impl VariableValue {
504    fn empty(url_data: &UrlExtraData) -> Self {
505        Self {
506            css: String::new(),
507            last_token_type: Default::default(),
508            first_token_type: Default::default(),
509            url_data: url_data.clone(),
510            references: Default::default(),
511        }
512    }
513
514    /// Create a new custom property without parsing if the CSS is known to be valid and contain no
515    /// references.
516    pub fn new(
517        css: String,
518        url_data: &UrlExtraData,
519        first_token_type: TokenSerializationType,
520        last_token_type: TokenSerializationType,
521    ) -> Self {
522        Self {
523            css,
524            url_data: url_data.clone(),
525            first_token_type,
526            last_token_type,
527            references: Default::default(),
528        }
529    }
530
531    fn push<'i>(
532        &mut self,
533        css: &str,
534        css_first_token_type: TokenSerializationType,
535        css_last_token_type: TokenSerializationType,
536    ) -> Result<(), ()> {
537        /// Prevent values from getting terribly big since you can use custom
538        /// properties exponentially.
539        ///
540        /// This number (2MB) is somewhat arbitrary, but silly enough that no
541        /// reasonable page should hit it. We could limit by number of total
542        /// substitutions, but that was very easy to work around in practice
543        /// (just choose a larger initial value and boom).
544        const MAX_VALUE_LENGTH_IN_BYTES: usize = 2 * 1024 * 1024;
545
546        if self.css.len() + css.len() > MAX_VALUE_LENGTH_IN_BYTES {
547            return Err(());
548        }
549
550        // This happens e.g. between two subsequent var() functions:
551        // `var(--a)var(--b)`.
552        //
553        // In that case, css_*_token_type is nonsensical.
554        if css.is_empty() {
555            return Ok(());
556        }
557
558        self.first_token_type.set_if_nothing(css_first_token_type);
559        // If self.first_token_type was nothing,
560        // self.last_token_type is also nothing and this will be false:
561        if self
562            .last_token_type
563            .needs_separator_when_before(css_first_token_type)
564        {
565            self.css.push_str("/**/")
566        }
567        self.css.push_str(css);
568        self.last_token_type = css_last_token_type;
569        Ok(())
570    }
571
572    /// Parse a custom property value.
573    pub fn parse<'i, 't>(
574        input: &mut Parser<'i, 't>,
575        url_data: &UrlExtraData,
576    ) -> Result<Self, ParseError<'i>> {
577        input.skip_whitespace();
578
579        let mut references = References::default();
580        let mut missing_closing_characters = String::new();
581        let start_position = input.position();
582        let (first_token_type, last_token_type) = parse_declaration_value(
583            input,
584            start_position,
585            &mut references,
586            &mut missing_closing_characters,
587        )?;
588        let mut css = input.slice_from(start_position).to_owned();
589        if !missing_closing_characters.is_empty() {
590            // Unescaped backslash at EOF in a quoted string is ignored.
591            if css.ends_with("\\")
592                && matches!(missing_closing_characters.as_bytes()[0], b'"' | b'\'')
593            {
594                css.pop();
595            }
596            css.push_str(&missing_closing_characters);
597        }
598
599        css.shrink_to_fit();
600        references.refs.shrink_to_fit();
601
602        Ok(Self {
603            css,
604            url_data: url_data.clone(),
605            first_token_type,
606            last_token_type,
607            references,
608        })
609    }
610
611    /// Create VariableValue from an int.
612    fn integer(number: i32, url_data: &UrlExtraData) -> Self {
613        Self::from_token(
614            Token::Number {
615                has_sign: false,
616                value: number as f32,
617                int_value: Some(number),
618            },
619            url_data,
620        )
621    }
622
623    /// Create VariableValue from an int.
624    fn ident(ident: &'static str, url_data: &UrlExtraData) -> Self {
625        Self::from_token(Token::Ident(ident.into()), url_data)
626    }
627
628    /// Create VariableValue from a float amount of CSS pixels.
629    fn pixels(number: f32, url_data: &UrlExtraData) -> Self {
630        // FIXME (https://github.com/servo/rust-cssparser/issues/266):
631        // No way to get TokenSerializationType::Dimension without creating
632        // Token object.
633        Self::from_token(
634            Token::Dimension {
635                has_sign: false,
636                value: number,
637                int_value: None,
638                unit: CowRcStr::from("px"),
639            },
640            url_data,
641        )
642    }
643
644    /// Create VariableValue from an integer amount of milliseconds.
645    fn int_ms(number: i32, url_data: &UrlExtraData) -> Self {
646        Self::from_token(
647            Token::Dimension {
648                has_sign: false,
649                value: number as f32,
650                int_value: Some(number),
651                unit: CowRcStr::from("ms"),
652            },
653            url_data,
654        )
655    }
656
657    /// Create VariableValue from an integer amount of CSS pixels.
658    fn int_pixels(number: i32, url_data: &UrlExtraData) -> Self {
659        Self::from_token(
660            Token::Dimension {
661                has_sign: false,
662                value: number as f32,
663                int_value: Some(number),
664                unit: CowRcStr::from("px"),
665            },
666            url_data,
667        )
668    }
669
670    fn from_token(token: Token, url_data: &UrlExtraData) -> Self {
671        let token_type = token.serialization_type();
672        let mut css = token.to_css_string();
673        css.shrink_to_fit();
674
675        VariableValue {
676            css,
677            url_data: url_data.clone(),
678            first_token_type: token_type,
679            last_token_type: token_type,
680            references: Default::default(),
681        }
682    }
683
684    /// Returns the raw CSS text from this VariableValue
685    pub fn css_text(&self) -> &str {
686        &self.css
687    }
688
689    /// Returns whether this variable value has any reference to the environment or other
690    /// variables.
691    pub fn has_references(&self) -> bool {
692        self.references.has_references()
693    }
694}
695
696/// <https://drafts.csswg.org/css-syntax-3/#typedef-declaration-value>
697fn parse_declaration_value<'i, 't>(
698    input: &mut Parser<'i, 't>,
699    input_start: SourcePosition,
700    references: &mut References,
701    missing_closing_characters: &mut String,
702) -> Result<(TokenSerializationType, TokenSerializationType), ParseError<'i>> {
703    input.parse_until_before(Delimiter::Bang | Delimiter::Semicolon, |input| {
704        parse_declaration_value_block(input, input_start, references, missing_closing_characters)
705    })
706}
707
708/// Like parse_declaration_value, but accept `!` and `;` since they are only invalid at the top level.
709fn parse_declaration_value_block<'i, 't>(
710    input: &mut Parser<'i, 't>,
711    input_start: SourcePosition,
712    references: &mut References,
713    missing_closing_characters: &mut String,
714) -> Result<(TokenSerializationType, TokenSerializationType), ParseError<'i>> {
715    let mut is_first = true;
716    let mut first_token_type = TokenSerializationType::Nothing;
717    let mut last_token_type = TokenSerializationType::Nothing;
718    let mut prev_reference_index: Option<usize> = None;
719    loop {
720        let token_start = input.position();
721        let Ok(token) = input.next_including_whitespace_and_comments() else {
722            break;
723        };
724
725        let prev_token_type = last_token_type;
726        let serialization_type = token.serialization_type();
727        last_token_type = serialization_type;
728        if is_first {
729            first_token_type = last_token_type;
730            is_first = false;
731        }
732
733        macro_rules! nested {
734            () => {
735                input.parse_nested_block(|input| {
736                    parse_declaration_value_block(
737                        input,
738                        input_start,
739                        references,
740                        missing_closing_characters,
741                    )
742                })?
743            };
744        }
745        macro_rules! check_closed {
746            ($closing:expr) => {
747                if !input.slice_from(token_start).ends_with($closing) {
748                    missing_closing_characters.push_str($closing)
749                }
750            };
751        }
752        if let Some(index) = prev_reference_index.take() {
753            references.refs[index].next_token_type = serialization_type;
754        }
755        match *token {
756            Token::Comment(_) => {
757                let token_slice = input.slice_from(token_start);
758                if !token_slice.ends_with("*/") {
759                    missing_closing_characters.push_str(if token_slice.ends_with('*') {
760                        "/"
761                    } else {
762                        "*/"
763                    })
764                }
765            },
766            Token::BadUrl(ref u) => {
767                let e = StyleParseErrorKind::BadUrlInDeclarationValueBlock(u.clone());
768                return Err(input.new_custom_error(e));
769            },
770            Token::BadString(ref s) => {
771                let e = StyleParseErrorKind::BadStringInDeclarationValueBlock(s.clone());
772                return Err(input.new_custom_error(e));
773            },
774            Token::CloseParenthesis => {
775                let e = StyleParseErrorKind::UnbalancedCloseParenthesisInDeclarationValueBlock;
776                return Err(input.new_custom_error(e));
777            },
778            Token::CloseSquareBracket => {
779                let e = StyleParseErrorKind::UnbalancedCloseSquareBracketInDeclarationValueBlock;
780                return Err(input.new_custom_error(e));
781            },
782            Token::CloseCurlyBracket => {
783                let e = StyleParseErrorKind::UnbalancedCloseCurlyBracketInDeclarationValueBlock;
784                return Err(input.new_custom_error(e));
785            },
786            Token::Function(ref name) => {
787                let is_var = name.eq_ignore_ascii_case("var");
788                if is_var || name.eq_ignore_ascii_case("env") {
789                    let our_ref_index = references.refs.len();
790                    let fallback = input.parse_nested_block(|input| {
791                        // TODO(emilio): For env() this should be <custom-ident> per spec, but no other browser does
792                        // that, see https://github.com/w3c/csswg-drafts/issues/3262.
793                        let name = input.expect_ident()?;
794                        let name = Atom::from(if is_var {
795                            match parse_name(name.as_ref()) {
796                                Ok(name) => name,
797                                Err(()) => {
798                                    let name = name.clone();
799                                    return Err(input.new_custom_error(
800                                        SelectorParseErrorKind::UnexpectedIdent(name),
801                                    ));
802                                },
803                            }
804                        } else {
805                            name.as_ref()
806                        });
807
808                        // We want the order of the references to match source order. So we need to reserve our slot
809                        // now, _before_ parsing our fallback. Note that we don't care if parsing fails after all, since
810                        // if this fails we discard the whole result anyways.
811                        let start = token_start.byte_index() - input_start.byte_index();
812                        references.refs.push(VarOrEnvReference {
813                            name,
814                            start,
815                            // To be fixed up after parsing fallback and auto-closing via our_ref_index.
816                            end: start,
817                            prev_token_type,
818                            // To be fixed up (if needed) on the next loop iteration via prev_reference_index.
819                            next_token_type: TokenSerializationType::Nothing,
820                            // To be fixed up after parsing fallback.
821                            fallback: None,
822                            is_var,
823                        });
824
825                        let mut fallback = None;
826                        if input.try_parse(|input| input.expect_comma()).is_ok() {
827                            input.skip_whitespace();
828                            let fallback_start = num::NonZeroUsize::new(
829                                input.position().byte_index() - input_start.byte_index(),
830                            )
831                            .unwrap();
832                            // NOTE(emilio): Intentionally using parse_declaration_value rather than
833                            // parse_declaration_value_block, since that's what parse_fallback used to do.
834                            let (first, last) = parse_declaration_value(
835                                input,
836                                input_start,
837                                references,
838                                missing_closing_characters,
839                            )?;
840                            fallback = Some(VariableFallback {
841                                start: fallback_start,
842                                first_token_type: first,
843                                last_token_type: last,
844                            });
845                        } else {
846                            let state = input.state();
847                            // We still need to consume the rest of the potentially-unclosed
848                            // tokens, but make sure to not consume tokens that would otherwise be
849                            // invalid, by calling reset().
850                            parse_declaration_value_block(
851                                input,
852                                input_start,
853                                references,
854                                missing_closing_characters,
855                            )?;
856                            input.reset(&state);
857                        }
858                        Ok(fallback)
859                    })?;
860                    check_closed!(")");
861                    prev_reference_index = Some(our_ref_index);
862                    let reference = &mut references.refs[our_ref_index];
863                    reference.end = input.position().byte_index() - input_start.byte_index()
864                        + missing_closing_characters.len();
865                    reference.fallback = fallback;
866                    if is_var {
867                        references.any_var = true;
868                    } else {
869                        references.any_env = true;
870                    }
871                } else {
872                    nested!();
873                    check_closed!(")");
874                }
875            },
876            Token::ParenthesisBlock => {
877                nested!();
878                check_closed!(")");
879            },
880            Token::CurlyBracketBlock => {
881                nested!();
882                check_closed!("}");
883            },
884            Token::SquareBracketBlock => {
885                nested!();
886                check_closed!("]");
887            },
888            Token::QuotedString(_) => {
889                let token_slice = input.slice_from(token_start);
890                let quote = &token_slice[..1];
891                debug_assert!(matches!(quote, "\"" | "'"));
892                if !(token_slice.ends_with(quote) && token_slice.len() > 1) {
893                    missing_closing_characters.push_str(quote)
894                }
895            },
896            Token::Ident(ref value)
897            | Token::AtKeyword(ref value)
898            | Token::Hash(ref value)
899            | Token::IDHash(ref value)
900            | Token::UnquotedUrl(ref value)
901            | Token::Dimension {
902                unit: ref value, ..
903            } => {
904                references
905                    .non_custom_references
906                    .insert(NonCustomReferences::from_unit(value));
907                let is_unquoted_url = matches!(token, Token::UnquotedUrl(_));
908                if value.ends_with("�") && input.slice_from(token_start).ends_with("\\") {
909                    // Unescaped backslash at EOF in these contexts is interpreted as U+FFFD
910                    // Check the value in case the final backslash was itself escaped.
911                    // Serialize as escaped U+FFFD, which is also interpreted as U+FFFD.
912                    // (Unescaped U+FFFD would also work, but removing the backslash is annoying.)
913                    missing_closing_characters.push_str("�")
914                }
915                if is_unquoted_url {
916                    check_closed!(")");
917                }
918            },
919            _ => {},
920        };
921    }
922    Ok((first_token_type, last_token_type))
923}
924
925/// A struct that takes care of encapsulating the cascade process for custom properties.
926pub struct CustomPropertiesBuilder<'a, 'b: 'a> {
927    seen: PrecomputedHashSet<&'a Name>,
928    may_have_cycles: bool,
929    has_color_scheme: bool,
930    custom_properties: ComputedCustomProperties,
931    reverted: PrecomputedHashMap<&'a Name, (CascadePriority, bool)>,
932    stylist: &'a Stylist,
933    computed_context: &'a mut computed::Context<'b>,
934    references_from_non_custom_properties: NonCustomReferenceMap<Vec<Name>>,
935}
936
937fn find_non_custom_references(
938    registration: &PropertyRegistrationData,
939    value: &VariableValue,
940    may_have_color_scheme: bool,
941    is_root_element: bool,
942    include_universal: bool,
943) -> Option<NonCustomReferences> {
944    let dependent_types = registration.syntax.dependent_types();
945    let may_reference_length = dependent_types.intersects(DependentDataTypes::LENGTH)
946        || (include_universal && registration.syntax.is_universal());
947    if may_reference_length {
948        let value_dependencies = value.references.non_custom_references(is_root_element);
949        if !value_dependencies.is_empty() {
950            return Some(value_dependencies);
951        }
952    }
953    if dependent_types.intersects(DependentDataTypes::COLOR) && may_have_color_scheme {
954        // NOTE(emilio): We might want to add a NonCustomReferences::COLOR_SCHEME or something but
955        // it's not really needed for correctness, so for now we use an Option for that to signal
956        // that there might be a dependencies.
957        return Some(NonCustomReferences::empty());
958    }
959    None
960}
961
962impl<'a, 'b: 'a> CustomPropertiesBuilder<'a, 'b> {
963    /// Create a new builder, inheriting from a given custom properties map.
964    ///
965    /// We expose this publicly mostly for @keyframe blocks.
966    pub fn new_with_properties(
967        stylist: &'a Stylist,
968        custom_properties: ComputedCustomProperties,
969        computed_context: &'a mut computed::Context<'b>,
970    ) -> Self {
971        Self {
972            seen: PrecomputedHashSet::default(),
973            reverted: Default::default(),
974            may_have_cycles: false,
975            has_color_scheme: false,
976            custom_properties,
977            stylist,
978            computed_context,
979            references_from_non_custom_properties: NonCustomReferenceMap::default(),
980        }
981    }
982
983    /// Create a new builder, inheriting from the right style given context.
984    pub fn new(stylist: &'a Stylist, context: &'a mut computed::Context<'b>) -> Self {
985        let is_root_element = context.is_root_element();
986
987        let inherited = context.inherited_custom_properties();
988        let initial_values = stylist.get_custom_property_initial_values();
989        let properties = ComputedCustomProperties {
990            inherited: if is_root_element {
991                debug_assert!(inherited.is_empty());
992                initial_values.inherited.clone()
993            } else {
994                inherited.inherited.clone()
995            },
996            non_inherited: initial_values.non_inherited.clone(),
997        };
998
999        // Reuse flags from computing registered custom properties initial values, such as
1000        // whether they depend on viewport units.
1001        context
1002            .style()
1003            .add_flags(stylist.get_custom_property_initial_values_flags());
1004        Self::new_with_properties(stylist, properties, context)
1005    }
1006
1007    /// Cascade a given custom property declaration.
1008    pub fn cascade(&mut self, declaration: &'a CustomDeclaration, priority: CascadePriority) {
1009        let CustomDeclaration {
1010            ref name,
1011            ref value,
1012        } = *declaration;
1013
1014        if let Some(&(reverted_priority, is_origin_revert)) = self.reverted.get(&name) {
1015            if !reverted_priority.allows_when_reverted(&priority, is_origin_revert) {
1016                return;
1017            }
1018        }
1019
1020        let was_already_present = !self.seen.insert(name);
1021        if was_already_present {
1022            return;
1023        }
1024
1025        if !self.value_may_affect_style(name, value) {
1026            return;
1027        }
1028
1029        let map = &mut self.custom_properties;
1030        let registration = self.stylist.get_custom_property_registration(&name);
1031        match value {
1032            CustomDeclarationValue::Unparsed(unparsed_value) => {
1033                // At this point of the cascade we're not guaranteed to have seen the color-scheme
1034                // declaration, so need to assume the worst. We could track all system color
1035                // keyword tokens + the light-dark() function, but that seems non-trivial /
1036                // probably overkill.
1037                let may_have_color_scheme = true;
1038                // Non-custom dependency is really relevant for registered custom properties
1039                // that require computed value of such dependencies.
1040                let has_dependency = unparsed_value.references.any_var
1041                    || find_non_custom_references(
1042                        registration,
1043                        unparsed_value,
1044                        may_have_color_scheme,
1045                        self.computed_context.is_root_element(),
1046                        /* include_unregistered = */ false,
1047                    )
1048                    .is_some();
1049                // If the variable value has no references to other properties, perform
1050                // substitution here instead of forcing a full traversal in `substitute_all`
1051                // afterwards.
1052                if !has_dependency {
1053                    return substitute_references_if_needed_and_apply(
1054                        name,
1055                        unparsed_value,
1056                        map,
1057                        self.stylist,
1058                        self.computed_context,
1059                    );
1060                }
1061                self.may_have_cycles = true;
1062                let value = ComputedRegisteredValue::universal(Arc::clone(unparsed_value));
1063                map.insert(registration, name, value);
1064            },
1065            CustomDeclarationValue::Parsed(parsed_value) => {
1066                let value = parsed_value.to_computed_value(&self.computed_context);
1067                map.insert(registration, name, value);
1068            },
1069            CustomDeclarationValue::CSSWideKeyword(keyword) => match keyword {
1070                CSSWideKeyword::RevertLayer | CSSWideKeyword::Revert => {
1071                    let origin_revert = matches!(keyword, CSSWideKeyword::Revert);
1072                    self.seen.remove(name);
1073                    self.reverted.insert(name, (priority, origin_revert));
1074                },
1075                CSSWideKeyword::Initial => {
1076                    // For non-inherited custom properties, 'initial' was handled in value_may_affect_style.
1077                    debug_assert!(registration.inherits(), "Should've been handled earlier");
1078                    remove_and_insert_initial_value(name, registration, map);
1079                },
1080                CSSWideKeyword::Inherit => {
1081                    // For inherited custom properties, 'inherit' was handled in value_may_affect_style.
1082                    debug_assert!(!registration.inherits(), "Should've been handled earlier");
1083                    if let Some(inherited_value) = self
1084                        .computed_context
1085                        .inherited_custom_properties()
1086                        .non_inherited
1087                        .get(name)
1088                    {
1089                        map.insert(registration, name, inherited_value.clone());
1090                    }
1091                },
1092                // handled in value_may_affect_style
1093                CSSWideKeyword::Unset => unreachable!(),
1094            },
1095        }
1096    }
1097
1098    /// Fast check to avoid calling maybe_note_non_custom_dependency in ~all cases.
1099    #[inline]
1100    pub fn might_have_non_custom_dependency(id: LonghandId, decl: &PropertyDeclaration) -> bool {
1101        if id == LonghandId::ColorScheme {
1102            return true;
1103        }
1104        if matches!(id, LonghandId::LineHeight | LonghandId::FontSize) {
1105            return matches!(decl, PropertyDeclaration::WithVariables(..));
1106        }
1107        false
1108    }
1109
1110    /// Note a non-custom property with variable reference that may in turn depend on that property.
1111    /// e.g. `font-size` depending on a custom property that may be a registered property using `em`.
1112    pub fn maybe_note_non_custom_dependency(&mut self, id: LonghandId, decl: &PropertyDeclaration) {
1113        debug_assert!(Self::might_have_non_custom_dependency(id, decl));
1114        if id == LonghandId::ColorScheme {
1115            // If we might change the color-scheme, we need to defer computation of colors.
1116            self.has_color_scheme = true;
1117            return;
1118        }
1119
1120        let refs = match decl {
1121            PropertyDeclaration::WithVariables(ref v) => &v.value.variable_value.references,
1122            _ => return,
1123        };
1124
1125        if !refs.any_var {
1126            return;
1127        }
1128
1129        // With unit algebra in `calc()`, references aren't limited to `font-size`.
1130        // For example, `--foo: 100ex; font-weight: calc(var(--foo) / 1ex);`,
1131        // or `--foo: 1em; zoom: calc(var(--foo) * 30px / 2em);`
1132        let references = match id {
1133            LonghandId::FontSize => {
1134                if self.computed_context.is_root_element() {
1135                    NonCustomReferences::ROOT_FONT_UNITS
1136                } else {
1137                    NonCustomReferences::FONT_UNITS
1138                }
1139            },
1140            LonghandId::LineHeight => {
1141                if self.computed_context.is_root_element() {
1142                    NonCustomReferences::ROOT_LH_UNITS | NonCustomReferences::ROOT_FONT_UNITS
1143                } else {
1144                    NonCustomReferences::LH_UNITS | NonCustomReferences::FONT_UNITS
1145                }
1146            },
1147            _ => return,
1148        };
1149
1150        let variables: Vec<Atom> = refs
1151            .refs
1152            .iter()
1153            .filter_map(|reference| {
1154                if !reference.is_var {
1155                    return None;
1156                }
1157                let registration = self
1158                    .stylist
1159                    .get_custom_property_registration(&reference.name);
1160                if !registration
1161                    .syntax
1162                    .dependent_types()
1163                    .intersects(DependentDataTypes::LENGTH)
1164                {
1165                    return None;
1166                }
1167                Some(reference.name.clone())
1168            })
1169            .collect();
1170        references.for_each(|idx| {
1171            let entry = &mut self.references_from_non_custom_properties[idx];
1172            let was_none = entry.is_none();
1173            let v = entry.get_or_insert_with(|| variables.clone());
1174            if was_none {
1175                return;
1176            }
1177            v.extend(variables.iter().cloned());
1178        });
1179    }
1180
1181    fn value_may_affect_style(&self, name: &Name, value: &CustomDeclarationValue) -> bool {
1182        let registration = self.stylist.get_custom_property_registration(&name);
1183        match *value {
1184            CustomDeclarationValue::CSSWideKeyword(CSSWideKeyword::Inherit) => {
1185                // For inherited custom properties, explicit 'inherit' means we
1186                // can just use any existing value in the inherited
1187                // CustomPropertiesMap.
1188                if registration.inherits() {
1189                    return false;
1190                }
1191            },
1192            CustomDeclarationValue::CSSWideKeyword(CSSWideKeyword::Initial) => {
1193                // For non-inherited custom properties, explicit 'initial' means
1194                // we can just use any initial value in the registration.
1195                if !registration.inherits() {
1196                    return false;
1197                }
1198            },
1199            CustomDeclarationValue::CSSWideKeyword(CSSWideKeyword::Unset) => {
1200                // Explicit 'unset' means we can either just use any existing
1201                // value in the inherited CustomPropertiesMap or the initial
1202                // value in the registration.
1203                return false;
1204            },
1205            _ => {},
1206        }
1207
1208        let existing_value = self.custom_properties.get(registration, &name);
1209        let existing_value = match existing_value {
1210            None => {
1211                if matches!(
1212                    value,
1213                    CustomDeclarationValue::CSSWideKeyword(CSSWideKeyword::Initial)
1214                ) {
1215                    debug_assert!(registration.inherits(), "Should've been handled earlier");
1216                    // The initial value of a custom property without a
1217                    // guaranteed-invalid initial value is the same as it
1218                    // not existing in the map.
1219                    if registration.initial_value.is_none() {
1220                        return false;
1221                    }
1222                }
1223                return true;
1224            },
1225            Some(v) => v,
1226        };
1227        let computed_value = match value {
1228            CustomDeclarationValue::Unparsed(value) => {
1229                // Don't bother overwriting an existing value with the same
1230                // specified value.
1231                if let Some(existing_value) = existing_value.as_universal() {
1232                    return existing_value != value;
1233                }
1234                if !registration.syntax.is_universal() {
1235                    compute_value(
1236                        &value.css,
1237                        &value.url_data,
1238                        registration,
1239                        self.computed_context,
1240                    )
1241                    .ok()
1242                } else {
1243                    None
1244                }
1245            },
1246            CustomDeclarationValue::Parsed(value) => {
1247                Some(value.to_computed_value(&self.computed_context))
1248            },
1249            CustomDeclarationValue::CSSWideKeyword(kw) => {
1250                match kw {
1251                    CSSWideKeyword::Inherit => {
1252                        debug_assert!(!registration.inherits(), "Should've been handled earlier");
1253                        // existing_value is the registered initial value.
1254                        // Don't bother adding it to self.custom_properties.non_inherited
1255                        // if the key is also absent from self.inherited.non_inherited.
1256                        if self
1257                            .computed_context
1258                            .inherited_custom_properties()
1259                            .non_inherited
1260                            .get(name)
1261                            .is_none()
1262                        {
1263                            return false;
1264                        }
1265                    },
1266                    CSSWideKeyword::Initial => {
1267                        debug_assert!(registration.inherits(), "Should've been handled earlier");
1268                        // Don't bother overwriting an existing value with the initial value specified in
1269                        // the registration.
1270                        if let Some(initial_value) = self
1271                            .stylist
1272                            .get_custom_property_initial_values()
1273                            .get(registration, name)
1274                        {
1275                            return existing_value != initial_value;
1276                        }
1277                    },
1278                    CSSWideKeyword::Unset => {
1279                        debug_assert!(false, "Should've been handled earlier");
1280                    },
1281                    CSSWideKeyword::Revert | CSSWideKeyword::RevertLayer => {},
1282                }
1283                None
1284            },
1285        };
1286
1287        if let Some(value) = computed_value {
1288            return existing_value.v != value.v;
1289        }
1290
1291        true
1292    }
1293
1294    /// Computes the map of applicable custom properties, as well as
1295    /// longhand properties that are now considered invalid-at-compute time.
1296    /// The result is saved into the computed context.
1297    ///
1298    /// If there was any specified property or non-inherited custom property
1299    /// with an initial value, we've created a new map and now we
1300    /// need to remove any potential cycles (And marking non-custom
1301    /// properties), and wrap it in an arc.
1302    ///
1303    /// Some registered custom properties may require font-related properties
1304    /// be resolved to resolve. If these properties are not resolved at this time,
1305    /// `defer` should be set to `Yes`, which will leave such custom properties,
1306    /// and other properties referencing them, untouched. These properties are
1307    /// returned separately, to be resolved by `build_deferred` to fully resolve
1308    /// all custom properties after all necessary non-custom properties are resolved.
1309    pub fn build(
1310        mut self,
1311        defer: DeferFontRelativeCustomPropertyResolution,
1312    ) -> Option<CustomPropertiesMap> {
1313        let mut deferred_custom_properties = None;
1314        if self.may_have_cycles {
1315            if defer == DeferFontRelativeCustomPropertyResolution::Yes {
1316                deferred_custom_properties = Some(CustomPropertiesMap::default());
1317            }
1318            let mut invalid_non_custom_properties = LonghandIdSet::default();
1319            substitute_all(
1320                &mut self.custom_properties,
1321                deferred_custom_properties.as_mut(),
1322                &mut invalid_non_custom_properties,
1323                self.has_color_scheme,
1324                &self.seen,
1325                &self.references_from_non_custom_properties,
1326                self.stylist,
1327                self.computed_context,
1328            );
1329            self.computed_context.builder.invalid_non_custom_properties =
1330                invalid_non_custom_properties;
1331        }
1332
1333        self.custom_properties.shrink_to_fit();
1334
1335        // Some pages apply a lot of redundant custom properties, see e.g.
1336        // bug 1758974 comment 5. Try to detect the case where the values
1337        // haven't really changed, and save some memory by reusing the inherited
1338        // map in that case.
1339        let initial_values = self.stylist.get_custom_property_initial_values();
1340        self.computed_context.builder.custom_properties = ComputedCustomProperties {
1341            inherited: if self
1342                .computed_context
1343                .inherited_custom_properties()
1344                .inherited
1345                == self.custom_properties.inherited
1346            {
1347                self.computed_context
1348                    .inherited_custom_properties()
1349                    .inherited
1350                    .clone()
1351            } else {
1352                self.custom_properties.inherited
1353            },
1354            non_inherited: if initial_values.non_inherited == self.custom_properties.non_inherited {
1355                initial_values.non_inherited.clone()
1356            } else {
1357                self.custom_properties.non_inherited
1358            },
1359        };
1360
1361        deferred_custom_properties
1362    }
1363
1364    /// Fully resolve all deferred custom properties, assuming that the incoming context
1365    /// has necessary properties resolved.
1366    pub fn build_deferred(
1367        deferred: CustomPropertiesMap,
1368        stylist: &Stylist,
1369        computed_context: &mut computed::Context,
1370    ) {
1371        if deferred.is_empty() {
1372            return;
1373        }
1374        let mut custom_properties = std::mem::take(&mut computed_context.builder.custom_properties);
1375        // Since `CustomPropertiesMap` preserves insertion order, we shouldn't have to worry about
1376        // resolving in a wrong order.
1377        for (k, v) in deferred.iter() {
1378            let Some(v) = v else { continue };
1379            let Some(v) = v.as_universal() else {
1380                unreachable!("Computing should have been deferred!")
1381            };
1382            substitute_references_if_needed_and_apply(
1383                k,
1384                v,
1385                &mut custom_properties,
1386                stylist,
1387                computed_context,
1388            );
1389        }
1390        computed_context.builder.custom_properties = custom_properties;
1391    }
1392}
1393
1394/// Resolve all custom properties to either substituted, invalid, or unset
1395/// (meaning we should use the inherited value).
1396///
1397/// It does cycle dependencies removal at the same time as substitution.
1398fn substitute_all(
1399    custom_properties_map: &mut ComputedCustomProperties,
1400    mut deferred_properties_map: Option<&mut CustomPropertiesMap>,
1401    invalid_non_custom_properties: &mut LonghandIdSet,
1402    has_color_scheme: bool,
1403    seen: &PrecomputedHashSet<&Name>,
1404    references_from_non_custom_properties: &NonCustomReferenceMap<Vec<Name>>,
1405    stylist: &Stylist,
1406    computed_context: &computed::Context,
1407) {
1408    // The cycle dependencies removal in this function is a variant
1409    // of Tarjan's algorithm. It is mostly based on the pseudo-code
1410    // listed in
1411    // https://en.wikipedia.org/w/index.php?
1412    // title=Tarjan%27s_strongly_connected_components_algorithm&oldid=801728495
1413
1414    #[derive(Clone, Eq, PartialEq, Debug)]
1415    enum VarType {
1416        Custom(Name),
1417        NonCustom(SingleNonCustomReference),
1418    }
1419
1420    /// Struct recording necessary information for each variable.
1421    #[derive(Debug)]
1422    struct VarInfo {
1423        /// The name of the variable. It will be taken to save addref
1424        /// when the corresponding variable is popped from the stack.
1425        /// This also serves as a mark for whether the variable is
1426        /// currently in the stack below.
1427        var: Option<VarType>,
1428        /// If the variable is in a dependency cycle, lowlink represents
1429        /// a smaller index which corresponds to a variable in the same
1430        /// strong connected component, which is known to be accessible
1431        /// from this variable. It is not necessarily the root, though.
1432        lowlink: usize,
1433    }
1434    /// Context struct for traversing the variable graph, so that we can
1435    /// avoid referencing all the fields multiple times.
1436    struct Context<'a, 'b: 'a> {
1437        /// Number of variables visited. This is used as the order index
1438        /// when we visit a new unresolved variable.
1439        count: usize,
1440        /// The map from custom property name to its order index.
1441        index_map: PrecomputedHashMap<Name, usize>,
1442        /// Mapping from a non-custom dependency to its order index.
1443        non_custom_index_map: NonCustomReferenceMap<usize>,
1444        /// Information of each variable indexed by the order index.
1445        var_info: SmallVec<[VarInfo; 5]>,
1446        /// The stack of order index of visited variables. It contains
1447        /// all unfinished strong connected components.
1448        stack: SmallVec<[usize; 5]>,
1449        /// References to non-custom properties in this strongly connected component.
1450        non_custom_references: NonCustomReferences,
1451        /// Whether the builder has seen a non-custom color-scheme reference.
1452        has_color_scheme: bool,
1453        /// Whether this strongly connected component contains any custom properties involving
1454        /// value computation.
1455        contains_computed_custom_property: bool,
1456        map: &'a mut ComputedCustomProperties,
1457        /// The stylist is used to get registered properties, and to resolve the environment to
1458        /// substitute `env()` variables.
1459        stylist: &'a Stylist,
1460        /// The computed context is used to get inherited custom
1461        /// properties  and compute registered custom properties.
1462        computed_context: &'a computed::Context<'b>,
1463        /// Longhand IDs that became invalid due to dependency cycle(s).
1464        invalid_non_custom_properties: &'a mut LonghandIdSet,
1465        /// Properties that cannot yet be substituted. Note we store both inherited and
1466        /// non-inherited properties in the same map, since we need to make sure we iterate through
1467        /// them in the right order.
1468        deferred_properties: Option<&'a mut CustomPropertiesMap>,
1469    }
1470
1471    /// This function combines the traversal for cycle removal and value
1472    /// substitution. It returns either a signal None if this variable
1473    /// has been fully resolved (to either having no reference or being
1474    /// marked invalid), or the order index for the given name.
1475    ///
1476    /// When it returns, the variable corresponds to the name would be
1477    /// in one of the following states:
1478    /// * It is still in context.stack, which means it is part of an
1479    ///   potentially incomplete dependency circle.
1480    /// * It has been removed from the map.  It can be either that the
1481    ///   substitution failed, or it is inside a dependency circle.
1482    ///   When this function removes a variable from the map because
1483    ///   of dependency circle, it would put all variables in the same
1484    ///   strong connected component to the set together.
1485    /// * It doesn't have any reference, because either this variable
1486    ///   doesn't have reference at all in specified value, or it has
1487    ///   been completely resolved.
1488    /// * There is no such variable at all.
1489    fn traverse<'a, 'b>(
1490        var: VarType,
1491        non_custom_references: &NonCustomReferenceMap<Vec<Name>>,
1492        context: &mut Context<'a, 'b>,
1493    ) -> Option<usize> {
1494        // Some shortcut checks.
1495        let value = match var {
1496            VarType::Custom(ref name) => {
1497                let registration = context.stylist.get_custom_property_registration(name);
1498                let value = context.map.get(registration, name)?.as_universal()?;
1499                let is_root = context.computed_context.is_root_element();
1500                // We need to keep track of potential non-custom-references even on unregistered
1501                // properties for cycle-detection purposes.
1502                let non_custom_refs = find_non_custom_references(
1503                    registration,
1504                    value,
1505                    context.has_color_scheme,
1506                    is_root,
1507                    /* include_unregistered = */ true,
1508                );
1509                context.non_custom_references |= non_custom_refs.unwrap_or_default();
1510                let has_dependency = value.references.any_var || non_custom_refs.is_some();
1511                // Nothing to resolve.
1512                if !has_dependency {
1513                    debug_assert!(!value.references.any_env, "Should've been handled earlier");
1514                    if !registration.syntax.is_universal() {
1515                        // We might still need to compute the value if this is not an universal
1516                        // registration if we thought this had a dependency before but turned out
1517                        // not to be (due to has_color_scheme, for example). Note that if this was
1518                        // already computed we would've bailed out in the as_universal() check.
1519                        debug_assert!(
1520                            registration
1521                                .syntax
1522                                .dependent_types()
1523                                .intersects(DependentDataTypes::COLOR),
1524                            "How did an unresolved value get here otherwise?",
1525                        );
1526                        let value = value.clone();
1527                        substitute_references_if_needed_and_apply(
1528                            name,
1529                            &value,
1530                            &mut context.map,
1531                            context.stylist,
1532                            context.computed_context,
1533                        );
1534                    }
1535                    return None;
1536                }
1537
1538                // Has this variable been visited?
1539                match context.index_map.entry(name.clone()) {
1540                    Entry::Occupied(entry) => {
1541                        return Some(*entry.get());
1542                    },
1543                    Entry::Vacant(entry) => {
1544                        entry.insert(context.count);
1545                    },
1546                }
1547                context.contains_computed_custom_property |= !registration.syntax.is_universal();
1548
1549                // Hold a strong reference to the value so that we don't
1550                // need to keep reference to context.map.
1551                Some(value.clone())
1552            },
1553            VarType::NonCustom(ref non_custom) => {
1554                let entry = &mut context.non_custom_index_map[*non_custom];
1555                if let Some(v) = entry {
1556                    return Some(*v);
1557                }
1558                *entry = Some(context.count);
1559                None
1560            },
1561        };
1562
1563        // Add new entry to the information table.
1564        let index = context.count;
1565        context.count += 1;
1566        debug_assert_eq!(index, context.var_info.len());
1567        context.var_info.push(VarInfo {
1568            var: Some(var.clone()),
1569            lowlink: index,
1570        });
1571        context.stack.push(index);
1572
1573        let mut self_ref = false;
1574        let mut lowlink = index;
1575        let visit_link =
1576            |var: VarType, context: &mut Context, lowlink: &mut usize, self_ref: &mut bool| {
1577                let next_index = match traverse(var, non_custom_references, context) {
1578                    Some(index) => index,
1579                    // There is nothing to do if the next variable has been
1580                    // fully resolved at this point.
1581                    None => {
1582                        return;
1583                    },
1584                };
1585                let next_info = &context.var_info[next_index];
1586                if next_index > index {
1587                    // The next variable has a larger index than us, so it
1588                    // must be inserted in the recursive call above. We want
1589                    // to get its lowlink.
1590                    *lowlink = cmp::min(*lowlink, next_info.lowlink);
1591                } else if next_index == index {
1592                    *self_ref = true;
1593                } else if next_info.var.is_some() {
1594                    // The next variable has a smaller order index and it is
1595                    // in the stack, so we are at the same component.
1596                    *lowlink = cmp::min(*lowlink, next_index);
1597                }
1598            };
1599        if let Some(ref v) = value.as_ref() {
1600            debug_assert!(
1601                matches!(var, VarType::Custom(_)),
1602                "Non-custom property has references?"
1603            );
1604
1605            // Visit other custom properties...
1606            // FIXME: Maybe avoid visiting the same var twice if not needed?
1607            for next in &v.references.refs {
1608                if !next.is_var {
1609                    continue;
1610                }
1611                visit_link(
1612                    VarType::Custom(next.name.clone()),
1613                    context,
1614                    &mut lowlink,
1615                    &mut self_ref,
1616                );
1617            }
1618
1619            // ... Then non-custom properties.
1620            v.references.non_custom_references.for_each(|r| {
1621                visit_link(VarType::NonCustom(r), context, &mut lowlink, &mut self_ref);
1622            });
1623        } else if let VarType::NonCustom(non_custom) = var {
1624            let entry = &non_custom_references[non_custom];
1625            if let Some(deps) = entry.as_ref() {
1626                for d in deps {
1627                    // Visit any reference from this non-custom property to custom properties.
1628                    visit_link(
1629                        VarType::Custom(d.clone()),
1630                        context,
1631                        &mut lowlink,
1632                        &mut self_ref,
1633                    );
1634                }
1635            }
1636        }
1637
1638        context.var_info[index].lowlink = lowlink;
1639        if lowlink != index {
1640            // This variable is in a loop, but it is not the root of
1641            // this strong connected component. We simply return for
1642            // now, and the root would remove it from the map.
1643            //
1644            // This cannot be removed from the map here, because
1645            // otherwise the shortcut check at the beginning of this
1646            // function would return the wrong value.
1647            return Some(index);
1648        }
1649
1650        // This is the root of a strong-connected component.
1651        let mut in_loop = self_ref;
1652        let name;
1653
1654        let handle_variable_in_loop = |name: &Name, context: &mut Context<'a, 'b>| {
1655            if context.contains_computed_custom_property {
1656                // These non-custom properties can't become invalid-at-compute-time from
1657                // cyclic dependencies purely consisting of non-registered properties.
1658                if context.non_custom_references.intersects(
1659                    NonCustomReferences::FONT_UNITS | NonCustomReferences::ROOT_FONT_UNITS,
1660                ) {
1661                    context
1662                        .invalid_non_custom_properties
1663                        .insert(LonghandId::FontSize);
1664                }
1665                if context
1666                    .non_custom_references
1667                    .intersects(NonCustomReferences::LH_UNITS | NonCustomReferences::ROOT_LH_UNITS)
1668                {
1669                    context
1670                        .invalid_non_custom_properties
1671                        .insert(LonghandId::LineHeight);
1672                }
1673            }
1674            // This variable is in loop. Resolve to invalid.
1675            handle_invalid_at_computed_value_time(name, context.map, context.computed_context);
1676        };
1677        loop {
1678            let var_index = context
1679                .stack
1680                .pop()
1681                .expect("The current variable should still be in stack");
1682            let var_info = &mut context.var_info[var_index];
1683            // We should never visit the variable again, so it's safe
1684            // to take the name away, so that we don't do additional
1685            // reference count.
1686            let var_name = var_info
1687                .var
1688                .take()
1689                .expect("Variable should not be poped from stack twice");
1690            if var_index == index {
1691                name = match var_name {
1692                    VarType::Custom(name) => name,
1693                    // At the root of this component, and it's a non-custom
1694                    // reference - we have nothing to substitute, so
1695                    // it's effectively resolved.
1696                    VarType::NonCustom(..) => return None,
1697                };
1698                break;
1699            }
1700            if let VarType::Custom(name) = var_name {
1701                // Anything here is in a loop which can traverse to the
1702                // variable we are handling, so it's invalid at
1703                // computed-value time.
1704                handle_variable_in_loop(&name, context);
1705            }
1706            in_loop = true;
1707        }
1708        // We've gotten to the root of this strongly connected component, so clear
1709        // whether or not it involved non-custom references.
1710        // It's fine to track it like this, because non-custom properties currently
1711        // being tracked can only participate in any loop only once.
1712        if in_loop {
1713            handle_variable_in_loop(&name, context);
1714            context.non_custom_references = NonCustomReferences::default();
1715            return None;
1716        }
1717
1718        if let Some(ref v) = value {
1719            let registration = context.stylist.get_custom_property_registration(&name);
1720
1721            let mut defer = false;
1722            if let Some(ref mut deferred) = context.deferred_properties {
1723                // We need to defer this property if it has a non-custom property dependency, or
1724                // any variable that it references is already deferred.
1725                defer = find_non_custom_references(
1726                    registration,
1727                    v,
1728                    context.has_color_scheme,
1729                    context.computed_context.is_root_element(),
1730                    /* include_unregistered = */ false,
1731                )
1732                .is_some()
1733                    || v.references.refs.iter().any(|reference| {
1734                        reference.is_var && deferred.get(&reference.name).is_some()
1735                    });
1736
1737                if defer {
1738                    let value = ComputedRegisteredValue::universal(Arc::clone(v));
1739                    deferred.insert(&name, value);
1740                    context.map.remove(registration, &name);
1741                }
1742            }
1743
1744            // If there are no var references we should already be computed and substituted by now.
1745            if !defer && v.references.any_var {
1746                substitute_references_if_needed_and_apply(
1747                    &name,
1748                    v,
1749                    &mut context.map,
1750                    context.stylist,
1751                    context.computed_context,
1752                );
1753            }
1754        }
1755        context.non_custom_references = NonCustomReferences::default();
1756
1757        // All resolved, so return the signal value.
1758        None
1759    }
1760
1761    // Note that `seen` doesn't contain names inherited from our parent, but
1762    // those can't have variable references (since we inherit the computed
1763    // variables) so we don't want to spend cycles traversing them anyway.
1764    for name in seen {
1765        let mut context = Context {
1766            count: 0,
1767            index_map: PrecomputedHashMap::default(),
1768            non_custom_index_map: NonCustomReferenceMap::default(),
1769            stack: SmallVec::new(),
1770            var_info: SmallVec::new(),
1771            map: custom_properties_map,
1772            non_custom_references: NonCustomReferences::default(),
1773            has_color_scheme,
1774            stylist,
1775            computed_context,
1776            invalid_non_custom_properties,
1777            deferred_properties: deferred_properties_map.as_deref_mut(),
1778            contains_computed_custom_property: false,
1779        };
1780        traverse(
1781            VarType::Custom((*name).clone()),
1782            references_from_non_custom_properties,
1783            &mut context,
1784        );
1785    }
1786}
1787
1788// See https://drafts.csswg.org/css-variables-2/#invalid-at-computed-value-time
1789fn handle_invalid_at_computed_value_time(
1790    name: &Name,
1791    custom_properties: &mut ComputedCustomProperties,
1792    computed_context: &computed::Context,
1793) {
1794    let stylist = computed_context.style().stylist.unwrap();
1795    let registration = stylist.get_custom_property_registration(&name);
1796    if !registration.syntax.is_universal() {
1797        // For the root element, inherited maps are empty. We should just
1798        // use the initial value if any, rather than removing the name.
1799        if registration.inherits() && !computed_context.is_root_element() {
1800            let inherited = computed_context.inherited_custom_properties();
1801            if let Some(value) = inherited.get(registration, name) {
1802                custom_properties.insert(registration, name, value.clone());
1803                return;
1804            }
1805        } else if let Some(ref initial_value) = registration.initial_value {
1806            if let Ok(initial_value) = compute_value(
1807                &initial_value.css,
1808                &initial_value.url_data,
1809                registration,
1810                computed_context,
1811            ) {
1812                custom_properties.insert(registration, name, initial_value);
1813                return;
1814            }
1815        }
1816    }
1817    custom_properties.remove(registration, name);
1818}
1819
1820/// Replace `var()` and `env()` functions in a pre-existing variable value.
1821fn substitute_references_if_needed_and_apply(
1822    name: &Name,
1823    value: &Arc<VariableValue>,
1824    custom_properties: &mut ComputedCustomProperties,
1825    stylist: &Stylist,
1826    computed_context: &computed::Context,
1827) {
1828    let registration = stylist.get_custom_property_registration(&name);
1829    if !value.has_references() && registration.syntax.is_universal() {
1830        // Trivial path: no references and no need to compute the value, just apply it directly.
1831        let computed_value = ComputedRegisteredValue::universal(Arc::clone(value));
1832        custom_properties.insert(registration, name, computed_value);
1833        return;
1834    }
1835
1836    let inherited = computed_context.inherited_custom_properties();
1837    let url_data = &value.url_data;
1838    let substitution =
1839        match substitute_internal(value, custom_properties, stylist, computed_context) {
1840            Ok(v) => v,
1841            Err(..) => {
1842                handle_invalid_at_computed_value_time(name, custom_properties, computed_context);
1843                return;
1844            },
1845        };
1846
1847    // If variable fallback results in a wide keyword, deal with it now.
1848    {
1849        let css = &substitution.css;
1850        let css_wide_kw = {
1851            let mut input = ParserInput::new(&css);
1852            let mut input = Parser::new(&mut input);
1853            input.try_parse(CSSWideKeyword::parse)
1854        };
1855
1856        if let Ok(kw) = css_wide_kw {
1857            // TODO: It's unclear what this should do for revert / revert-layer, see
1858            // https://github.com/w3c/csswg-drafts/issues/9131. For now treating as unset
1859            // seems fine?
1860            match (
1861                kw,
1862                registration.inherits(),
1863                computed_context.is_root_element(),
1864            ) {
1865                (CSSWideKeyword::Initial, _, _)
1866                | (CSSWideKeyword::Revert, false, _)
1867                | (CSSWideKeyword::RevertLayer, false, _)
1868                | (CSSWideKeyword::Unset, false, _)
1869                | (CSSWideKeyword::Revert, true, true)
1870                | (CSSWideKeyword::RevertLayer, true, true)
1871                | (CSSWideKeyword::Unset, true, true)
1872                | (CSSWideKeyword::Inherit, _, true) => {
1873                    remove_and_insert_initial_value(name, registration, custom_properties);
1874                },
1875                (CSSWideKeyword::Revert, true, false)
1876                | (CSSWideKeyword::RevertLayer, true, false)
1877                | (CSSWideKeyword::Inherit, _, false)
1878                | (CSSWideKeyword::Unset, true, false) => {
1879                    match inherited.get(registration, name) {
1880                        Some(value) => {
1881                            custom_properties.insert(registration, name, value.clone());
1882                        },
1883                        None => {
1884                            custom_properties.remove(registration, name);
1885                        },
1886                    };
1887                },
1888            }
1889            return;
1890        }
1891    }
1892
1893    let value = match substitution.into_value(url_data, registration, computed_context) {
1894        Ok(v) => v,
1895        Err(()) => {
1896            handle_invalid_at_computed_value_time(name, custom_properties, computed_context);
1897            return;
1898        },
1899    };
1900
1901    custom_properties.insert(registration, name, value);
1902}
1903
1904#[derive(Default)]
1905struct Substitution<'a> {
1906    css: Cow<'a, str>,
1907    first_token_type: TokenSerializationType,
1908    last_token_type: TokenSerializationType,
1909}
1910
1911impl<'a> Substitution<'a> {
1912    fn from_value(v: VariableValue) -> Self {
1913        Substitution {
1914            css: v.css.into(),
1915            first_token_type: v.first_token_type,
1916            last_token_type: v.last_token_type,
1917        }
1918    }
1919
1920    fn into_value(
1921        self,
1922        url_data: &UrlExtraData,
1923        registration: &PropertyRegistrationData,
1924        computed_context: &computed::Context,
1925    ) -> Result<ComputedRegisteredValue, ()> {
1926        if registration.syntax.is_universal() {
1927            return Ok(ComputedRegisteredValue::universal(Arc::new(
1928                VariableValue {
1929                    css: self.css.into_owned(),
1930                    first_token_type: self.first_token_type,
1931                    last_token_type: self.last_token_type,
1932                    url_data: url_data.clone(),
1933                    references: Default::default(),
1934                },
1935            )));
1936        }
1937        compute_value(&self.css, url_data, registration, computed_context)
1938    }
1939
1940    fn new(
1941        css: &'a str,
1942        first_token_type: TokenSerializationType,
1943        last_token_type: TokenSerializationType,
1944    ) -> Self {
1945        Self {
1946            css: Cow::Borrowed(css),
1947            first_token_type,
1948            last_token_type,
1949        }
1950    }
1951}
1952
1953fn compute_value(
1954    css: &str,
1955    url_data: &UrlExtraData,
1956    registration: &PropertyRegistrationData,
1957    computed_context: &computed::Context,
1958) -> Result<ComputedRegisteredValue, ()> {
1959    debug_assert!(!registration.syntax.is_universal());
1960
1961    let mut input = ParserInput::new(&css);
1962    let mut input = Parser::new(&mut input);
1963
1964    SpecifiedRegisteredValue::compute(
1965        &mut input,
1966        registration,
1967        url_data,
1968        computed_context,
1969        AllowComputationallyDependent::Yes,
1970    )
1971}
1972
1973/// Removes the named registered custom property and inserts its uncomputed initial value.
1974fn remove_and_insert_initial_value(
1975    name: &Name,
1976    registration: &PropertyRegistrationData,
1977    custom_properties: &mut ComputedCustomProperties,
1978) {
1979    custom_properties.remove(registration, name);
1980    if let Some(ref initial_value) = registration.initial_value {
1981        let value = ComputedRegisteredValue::universal(Arc::clone(initial_value));
1982        custom_properties.insert(registration, name, value);
1983    }
1984}
1985
1986fn do_substitute_chunk<'a>(
1987    css: &'a str,
1988    start: usize,
1989    end: usize,
1990    first_token_type: TokenSerializationType,
1991    last_token_type: TokenSerializationType,
1992    url_data: &UrlExtraData,
1993    custom_properties: &'a ComputedCustomProperties,
1994    stylist: &Stylist,
1995    computed_context: &computed::Context,
1996    references: &mut std::iter::Peekable<std::slice::Iter<VarOrEnvReference>>,
1997) -> Result<Substitution<'a>, ()> {
1998    if start == end {
1999        // Empty string. Easy.
2000        return Ok(Substitution::default());
2001    }
2002    // Easy case: no references involved.
2003    if references
2004        .peek()
2005        .map_or(true, |reference| reference.end > end)
2006    {
2007        let result = &css[start..end];
2008        return Ok(Substitution::new(result, first_token_type, last_token_type));
2009    }
2010
2011    let mut substituted = ComputedValue::empty(url_data);
2012    let mut next_token_type = first_token_type;
2013    let mut cur_pos = start;
2014    while let Some(reference) = references.next_if(|reference| reference.end <= end) {
2015        if reference.start != cur_pos {
2016            substituted.push(
2017                &css[cur_pos..reference.start],
2018                next_token_type,
2019                reference.prev_token_type,
2020            )?;
2021        }
2022
2023        let substitution = substitute_one_reference(
2024            css,
2025            url_data,
2026            custom_properties,
2027            reference,
2028            stylist,
2029            computed_context,
2030            references,
2031        )?;
2032
2033        // Optimize the property: var(--...) case to avoid allocating at all.
2034        if reference.start == start && reference.end == end {
2035            return Ok(substitution);
2036        }
2037
2038        substituted.push(
2039            &substitution.css,
2040            substitution.first_token_type,
2041            substitution.last_token_type,
2042        )?;
2043        next_token_type = reference.next_token_type;
2044        cur_pos = reference.end;
2045    }
2046    // Push the rest of the value if needed.
2047    if cur_pos != end {
2048        substituted.push(&css[cur_pos..end], next_token_type, last_token_type)?;
2049    }
2050    Ok(Substitution::from_value(substituted))
2051}
2052
2053fn substitute_one_reference<'a>(
2054    css: &'a str,
2055    url_data: &UrlExtraData,
2056    custom_properties: &'a ComputedCustomProperties,
2057    reference: &VarOrEnvReference,
2058    stylist: &Stylist,
2059    computed_context: &computed::Context,
2060    references: &mut std::iter::Peekable<std::slice::Iter<VarOrEnvReference>>,
2061) -> Result<Substitution<'a>, ()> {
2062    if reference.is_var {
2063        let registration = stylist.get_custom_property_registration(&reference.name);
2064        if let Some(v) = custom_properties.get(registration, &reference.name) {
2065            // Skip references that are inside the outer variable (in fallback for example).
2066            while references
2067                .next_if(|next_ref| next_ref.end <= reference.end)
2068                .is_some()
2069            {}
2070            return Ok(Substitution::from_value(v.to_variable_value()));
2071        }
2072    } else {
2073        let device = stylist.device();
2074        if let Some(v) = device.environment().get(&reference.name, device, url_data) {
2075            while references
2076                .next_if(|next_ref| next_ref.end <= reference.end)
2077                .is_some()
2078            {}
2079            return Ok(Substitution::from_value(v));
2080        }
2081    }
2082
2083    let Some(ref fallback) = reference.fallback else {
2084        return Err(());
2085    };
2086
2087    do_substitute_chunk(
2088        css,
2089        fallback.start.get(),
2090        reference.end - 1, // Skip the closing parenthesis of the reference value.
2091        fallback.first_token_type,
2092        fallback.last_token_type,
2093        url_data,
2094        custom_properties,
2095        stylist,
2096        computed_context,
2097        references,
2098    )
2099}
2100
2101/// Replace `var()` and `env()` functions. Return `Err(..)` for invalid at computed time.
2102fn substitute_internal<'a>(
2103    variable_value: &'a VariableValue,
2104    custom_properties: &'a ComputedCustomProperties,
2105    stylist: &Stylist,
2106    computed_context: &computed::Context,
2107) -> Result<Substitution<'a>, ()> {
2108    let mut refs = variable_value.references.refs.iter().peekable();
2109    do_substitute_chunk(
2110        &variable_value.css,
2111        /* start = */ 0,
2112        /* end = */ variable_value.css.len(),
2113        variable_value.first_token_type,
2114        variable_value.last_token_type,
2115        &variable_value.url_data,
2116        custom_properties,
2117        stylist,
2118        computed_context,
2119        &mut refs,
2120    )
2121}
2122
2123/// Replace var() and env() functions, returning the resulting CSS string.
2124pub fn substitute<'a>(
2125    variable_value: &'a VariableValue,
2126    custom_properties: &'a ComputedCustomProperties,
2127    stylist: &Stylist,
2128    computed_context: &computed::Context,
2129) -> Result<Cow<'a, str>, ()> {
2130    debug_assert!(variable_value.has_references());
2131    let v = substitute_internal(variable_value, custom_properties, stylist, computed_context)?;
2132    Ok(v.css)
2133}