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