scheme_rs/
syntax.rs

1use crate::{
2    ast::{self, FetchVar, Literal, MacroExpansionPoint},
3    compile::{Compile, CompileError},
4    continuation::{CatchContinuationCall, Continuation},
5    env::Env,
6    error::RuntimeError,
7    eval::Eval,
8    gc::{Trace, Gc},
9    lex::{InputSpan, Lexeme, Token},
10    parse::ParseError,
11    proc::Callable,
12    util::RequireOne,
13    value::Value,
14};
15use futures::future::BoxFuture;
16use std::{collections::BTreeSet, fmt, sync::Arc};
17
18#[derive(Debug, Clone, PartialEq, Trace)]
19pub struct Span {
20    pub line: u32,
21    pub column: usize,
22    pub offset: usize,
23    pub file: Arc<String>,
24}
25
26impl fmt::Display for Span {
27    fn fmt(&self, f: &mut fmt::Formatter<'_>) -> fmt::Result {
28        write!(f, "{}:{}:{}", self.file, self.line, self.column)
29    }
30}
31
32impl From<InputSpan<'_>> for Span {
33    fn from(span: InputSpan<'_>) -> Self {
34        Span {
35            line: span.location_line(),
36            column: span.get_column(),
37            offset: span.location_offset(),
38            file: span.extra.clone(),
39        }
40    }
41}
42
43#[derive(Clone, derive_more::Debug, Trace)]
44pub enum Syntax {
45    /// An empty list.
46    Null {
47        #[debug(skip)]
48        span: Span,
49    },
50    /// A nested grouping of pairs. If the expression is a proper list, then the
51    /// last element of expression will be Nil. This vector is guaranteed to contain
52    /// at least two elements.
53    List {
54        list: Vec<Syntax>,
55        #[debug(skip)]
56        span: Span,
57    },
58    Vector {
59        vector: Vec<Syntax>,
60        #[debug(skip)]
61        span: Span,
62    },
63    Literal {
64        literal: Literal,
65        #[debug(skip)]
66        span: Span,
67    },
68    Identifier {
69        ident: Identifier,
70        #[debug(skip)]
71        bound: bool,
72        #[debug(skip)]
73        span: Span,
74    },
75}
76
77impl Syntax {
78    pub fn mark(&mut self, mark: Mark) {
79        match self {
80            Self::List { ref mut list, .. } => {
81                for item in list {
82                    item.mark(mark);
83                }
84            }
85            Self::Vector { ref mut vector, .. } => {
86                for item in vector {
87                    item.mark(mark);
88                }
89            }
90            Self::Identifier { ident, .. } => ident.mark(mark),
91            _ => (),
92        }
93    }
94
95    pub fn normalize(self) -> Self {
96        match self {
97            Self::List { mut list, span } => {
98                if let [Syntax::Null { .. }] = list.as_slice() {
99                    list.pop().unwrap()
100                } else if list.is_empty() {
101                    Syntax::Null { span }
102                } else {
103                    Self::List { list, span }
104                }
105            }
106            x => x,
107        }
108    }
109
110    pub fn resolve_bindings<'a>(&'a mut self, env: &'a Env) -> BoxFuture<'a, ()> {
111        Box::pin(async move {
112            match self {
113                Self::List { ref mut list, .. } => {
114                    for item in list {
115                        item.resolve_bindings(env).await;
116                    }
117                }
118                Self::Vector { ref mut vector, .. } => {
119                    for item in vector {
120                        item.resolve_bindings(env).await;
121                    }
122                }
123                Self::Identifier {
124                    ref ident,
125                    ref mut bound,
126                    ..
127                } => *bound = env.is_bound(ident).await,
128                _ => (),
129            }
130        })
131    }
132
133    async fn apply_transformer(
134        &self,
135        curr_env: &Env,
136        macro_env: Env,
137        cont: &Option<Arc<Continuation>>,
138        transformer: Gc<Value>,
139    ) -> Result<Expansion<'static>, RuntimeError> {
140        // Create a new mark for the expansion context
141        let new_mark = Mark::new();
142        // Apply the new mark to the input
143        // TODO: Figure out a better way to do this without cloning so much
144        let mut input = self.clone();
145        input.resolve_bindings(curr_env).await;
146        input.mark(new_mark);
147        // Call the transformer with the input:
148        let mut output = match &*transformer.read().await {
149            Value::Procedure(proc) => {
150                let output = proc
151                    .call(vec![Gc::new(Value::Syntax(input))], cont)
152                    .await?
153                    .eval(cont)
154                    .await?
155                    .require_one()?;
156                let output = output.read().await;
157                match &*output {
158                    Value::Syntax(syntax) => syntax.clone(),
159                    _ => todo!(),
160                }
161            }
162            Value::Transformer(transformer) => transformer
163                .expand(&input)
164                .ok_or_else(RuntimeError::no_patterns_match)?,
165            x => return Err(RuntimeError::invalid_type("procedure", x.type_name())),
166        };
167        // Apply the new mark to the output
168        output.mark(new_mark);
169        Ok(Expansion::Expanded {
170            mark: new_mark,
171            syntax: output,
172            macro_env,
173        })
174    }
175
176    fn expand<'a>(
177        &'a self,
178        env: &'a Env,
179        cont: &'a Option<Arc<Continuation>>,
180    ) -> BoxFuture<'a, Result<Expansion<'a>, RuntimeError>> {
181        Box::pin(async move {
182            match self {
183                Self::List { list, .. } => {
184                    // If the head is not an identifier, we leave the expression unexpanded
185                    // for now. We will expand it later in the proc call
186                    let ident = match list.first() {
187                        Some(Self::Identifier { ident, .. }) => ident,
188                        _ => return Ok(Expansion::Unexpanded(self)),
189                    };
190                    if let Some((macro_env, transformer)) = env.fetch_macro(ident).await {
191                        return self
192                            .apply_transformer(env, macro_env, cont, transformer)
193                            .await;
194                    }
195                }
196                Self::Identifier { ident, .. } => {
197                    if let Some((macro_env, transformer)) = env.fetch_macro(ident).await {
198                        return self
199                            .apply_transformer(env, macro_env, cont, transformer)
200                            .await;
201                    }
202                }
203                _ => (),
204            }
205            Ok(Expansion::Unexpanded(self))
206        })
207    }
208
209    pub async fn compile_expanded(
210        &self,
211        env: &Env,
212        cont: &Option<Arc<Continuation>>,
213    ) -> Result<Arc<dyn Eval>, CompileError> {
214        match self {
215            Self::Null { span } => Err(CompileError::UnexpectedEmptyList(span.clone())),
216            // Special identifiers:
217            Self::Identifier { ident, .. } if ident == "<undefined>" => {
218                Ok(Arc::new(Value::Undefined))
219            }
220            // Regular identifiers:
221            Self::Identifier { ident, .. } => {
222                Ok(Arc::new(FetchVar::new(ident.clone())) as Arc<dyn Eval>)
223            }
224            Self::Literal { literal, .. } => Ok(Arc::new(literal.clone()) as Arc<dyn Eval>),
225            Self::List { list: exprs, span } => match &exprs[..] {
226                // Function call:
227                [Self::Identifier { ident, .. }, ..] if env.is_bound(ident).await => {
228                    ast::Call::compile_to_expr(exprs, env, cont, span).await
229                }
230                // Special forms:
231                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "quote" => {
232                    ast::Quote::compile_to_expr(tail, env, cont, span).await
233                }
234                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "syntax" => {
235                    ast::SyntaxQuote::compile_to_expr(tail, env, cont, span).await
236                }
237                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "begin" => {
238                    ast::Body::compile_to_expr(tail, env, cont, span).await
239                }
240                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "let" => {
241                    ast::Let::compile_to_expr(tail, env, cont, span).await
242                }
243                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "lambda" => {
244                    ast::Lambda::compile_to_expr(tail, env, cont, span).await
245                }
246                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "if" => {
247                    ast::If::compile_to_expr(tail, env, cont, span).await
248                }
249                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "and" => {
250                    ast::And::compile_to_expr(tail, env, cont, span).await
251                }
252                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "or" => {
253                    ast::Or::compile_to_expr(tail, env, cont, span).await
254                }
255                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "define" => {
256                    ast::Define::compile_to_expr(tail, env, cont, span).await
257                }
258                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "define-syntax" => {
259                    ast::DefineSyntax::compile_to_expr(tail, env, cont, span).await
260                }
261                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "syntax-case" => {
262                    ast::SyntaxCase::compile_to_expr(tail, env, cont, span).await
263                }
264                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "syntax-rules" => {
265                    ast::SyntaxRules::compile_to_expr(tail, env, cont, span).await
266                }
267                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "apply" => {
268                    ast::Apply::compile_to_expr(tail, env, cont, span).await
269                }
270                // Very special form:
271                [Self::Identifier { ident, span, .. }, tail @ ..] if ident == "set!" => {
272                    // Check for a variable transformer
273                    if let Some(Syntax::Identifier { ident, .. }) = tail.first() {
274                        if let Some((macro_env, transformer)) = env.fetch_macro(ident).await {
275                            if !transformer.read().await.is_variable_transformer() {
276                                return Err(CompileError::NotVariableTransformer);
277                            }
278                            return self
279                                .apply_transformer(env, macro_env, cont, transformer)
280                                .await?
281                                .compile(env, cont)
282                                .await;
283                        }
284                    }
285                    ast::Set::compile_to_expr(tail, env, cont, span).await
286                }
287                // Special function call:
288                _ => ast::Call::compile_to_expr(exprs, env, cont, span).await,
289            },
290            Self::Vector { vector, .. } => {
291                let mut vals = Vec::new();
292                for item in vector {
293                    match item {
294                        Self::Null { .. } => vals.push(Arc::new(Value::Null) as Arc<dyn Eval>),
295                        item => vals.push(item.compile(env, cont).await?),
296                    }
297                }
298                Ok(Arc::new(ast::Vector { vals }) as Arc<dyn Eval>)
299            }
300        }
301    }
302
303    pub async fn compile(
304        &self,
305        env: &Env,
306        cont: &Option<Arc<Continuation>>,
307    ) -> Result<Arc<dyn Eval>, CompileError> {
308        self.expand(env, cont).await?.compile(env, cont).await
309    }
310}
311
312pub enum Expansion<'a> {
313    /// Syntax remained unchanged after expansion
314    Unexpanded(&'a Syntax),
315    /// Syntax was expanded, producing a new expansion context
316    Expanded {
317        mark: Mark,
318        macro_env: Env,
319        syntax: Syntax,
320    },
321}
322
323impl Expansion<'_> {
324    pub fn is_expanded(&self) -> bool {
325        matches!(self, Self::Expanded { .. })
326    }
327
328    pub fn is_unexpanded(&self) -> bool {
329        matches!(self, Self::Unexpanded(_))
330    }
331}
332
333impl<'a> Expansion<'a> {
334    pub fn compile(
335        self,
336        env: &'a Env,
337        cont: &'a Option<Arc<Continuation>>,
338    ) -> BoxFuture<'a, Result<Arc<dyn Eval>, CompileError>> {
339        Box::pin(async move {
340            match self {
341                Self::Unexpanded(syntax) => syntax.compile_expanded(env, cont).await,
342                Self::Expanded {
343                    mark,
344                    syntax,
345                    macro_env,
346                } => {
347                    // If the expression has been expanded, we may need to expand it again, but
348                    // it must be done in a new expansion context.
349                    let env =
350                        Env::Expansion(Gc::new(env.new_expansion_context(mark, macro_env.clone())));
351                    Ok(Arc::new(MacroExpansionPoint::new(
352                        mark,
353                        macro_env,
354                        syntax.expand(&env, cont).await?.compile(&env, cont).await?,
355                    )) as Arc<dyn Eval>)
356                }
357            }
358        })
359    }
360}
361
362#[derive(Debug)]
363pub struct ParsedSyntax {
364    pub doc_comment: Option<String>,
365    syntax: Syntax,
366}
367
368impl ParsedSyntax {
369    fn parse_fragment<'a, 'b>(
370        i: &'b [Token<'a>],
371    ) -> Result<(&'b [Token<'a>], Self), ParseError<'a>> {
372        let (doc_comment, remaining) = if let Token {
373            lexeme: Lexeme::DocComment(ref doc_comment),
374            ..
375        } = i[0]
376        {
377            (Some(doc_comment.clone()), &i[1..])
378        } else {
379            (None, i)
380        };
381        let (remaining, syntax) = crate::parse::expression(remaining)?;
382        Ok((
383            remaining,
384            Self {
385                doc_comment,
386                syntax,
387            },
388        ))
389    }
390
391    pub fn parse<'a>(mut i: &[Token<'a>]) -> Result<Vec<Self>, ParseError<'a>> {
392        let mut output = Vec::new();
393        while !i.is_empty() {
394            let (remaining, expr) = Self::parse_fragment(i)?;
395            output.push(expr);
396            i = remaining
397        }
398        Ok(output)
399    }
400
401    pub async fn compile(
402        &self,
403        env: &Env,
404        cont: &Option<Arc<Continuation>>,
405    ) -> Result<Arc<dyn Eval>, CompileError> {
406        Ok(Arc::new(CatchContinuationCall::new(
407            self.syntax.compile(env, cont).await?,
408        )))
409    }
410}
411
412#[derive(Copy, Clone, Debug, Hash, PartialEq, Eq, PartialOrd, Ord, Trace)]
413pub struct Mark(u64);
414
415impl Mark {
416    pub fn new() -> Self {
417        Self(rand::random())
418    }
419}
420
421impl Default for Mark {
422    fn default() -> Self {
423        Self::new()
424    }
425}
426
427#[derive(Clone, Hash, PartialEq, Eq, Trace)]
428pub struct Identifier {
429    pub name: String,
430    pub marks: BTreeSet<Mark>,
431}
432
433impl fmt::Debug for Identifier {
434    fn fmt(&self, f: &mut fmt::Formatter<'_>) -> fmt::Result {
435        write!(f, "{}", self.name)
436    }
437}
438
439impl Identifier {
440    pub fn new(name: String) -> Self {
441        Self {
442            name,
443            marks: BTreeSet::default(),
444        }
445    }
446
447    pub fn mark(&mut self, mark: Mark) {
448        if self.marks.contains(&mark) {
449            self.marks.remove(&mark);
450        } else {
451            self.marks.insert(mark);
452        }
453    }
454}
455
456impl PartialEq<str> for Identifier {
457    fn eq(&self, rhs: &str) -> bool {
458        self.name == rhs
459    }
460}
461
462impl Syntax {
463    pub fn span(&self) -> &Span {
464        match self {
465            Self::Null { span } => span,
466            Self::List { span, .. } => span,
467            Self::Vector { span, .. } => span,
468            Self::Literal { span, .. } => span,
469            Self::Identifier { span, .. } => span,
470        }
471    }
472
473    // There's got to be a better way:
474
475    pub fn new_null(span: impl Into<Span>) -> Self {
476        Self::Null { span: span.into() }
477    }
478
479    pub fn is_null(&self) -> bool {
480        matches!(self, Self::Null { .. })
481    }
482
483    pub fn new_list(list: Vec<Syntax>, span: impl Into<Span>) -> Self {
484        Self::List {
485            list,
486            span: span.into(),
487        }
488    }
489
490    pub fn is_list(&self) -> bool {
491        matches!(self, Self::List { .. })
492    }
493
494    pub fn new_vector(vector: Vec<Syntax>, span: impl Into<Span>) -> Self {
495        Self::Vector {
496            vector,
497            span: span.into(),
498        }
499    }
500
501    pub fn is_vector(&self) -> bool {
502        matches!(self, Self::Vector { .. })
503    }
504
505    pub fn new_literal(literal: Literal, span: impl Into<Span>) -> Self {
506        Self::Literal {
507            literal,
508            span: span.into(),
509        }
510    }
511
512    pub fn is_literal(&self) -> bool {
513        matches!(self, Self::Literal { .. })
514    }
515
516    pub fn new_identifier(name: &str, span: impl Into<Span>) -> Self {
517        Self::Identifier {
518            ident: Identifier::new(name.to_string()),
519            span: span.into(),
520            bound: false,
521        }
522    }
523
524    pub fn is_identifier(&self) -> bool {
525        matches!(self, Self::Identifier { .. })
526    }
527}