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