executor, mostly

This commit is contained in:
2022-11-07 15:15:38 +00:00
parent d9c35c3591
commit 6900d1213a
18 changed files with 444 additions and 61 deletions

View File

@@ -0,0 +1,67 @@
use mappable_rc::Mrc;
use super::super::representations::typed::{Clause, Expr};
pub fn apply_lambda(body: Mrc<Expr>, arg: Mrc<Expr>) -> Mrc<Expr> {
apply_lambda_expr_rec(Mrc::clone(&body), arg, 0)
.unwrap_or(body)
}
fn apply_lambda_expr_rec(
item: Mrc<Expr>, arg: Mrc<Expr>, depth: usize
) -> Option<Mrc<Expr>> {
let Expr(clause, typ) = item.as_ref();
apply_lambda_clause_rec(clause.clone(), arg, depth)
.map(|c| Mrc::new(Expr(c, Mrc::clone(typ))))
}
fn apply_lambda_clause_rec(
clause: Clause, arg: Mrc<Expr>, depth: usize
) -> Option<Clause> {
match clause {
// Only element actually manipulated
Clause::Argument(d) => {
if d == depth {Some(arg.0.clone())} // Resolve reference
// Application eliminates a layer of indirection
else if d > depth {Some(Clause::Argument(d - 1))}
else {None} // Undisturbed ancestry
}
// Traverse, yield Some if either had changed.
Clause::Apply(f, x) => apply_lambda__traverse_call(arg, depth, f, x, Clause::Apply),
Clause::Explicit(f, t) => apply_lambda__traverse_call(arg, depth, f, t, Clause::Explicit),
Clause::Lambda(t, b) => apply_lambda__traverse_param(arg, depth, t, b, Clause::Lambda),
Clause::Auto(t, b) => apply_lambda__traverse_param(arg, depth, t, b, Clause::Auto),
// Leaf nodes
Clause::Atom(_) | Clause::ExternFn(_) | Clause::Literal(_) => None
}
}
fn apply_lambda__traverse_call(
arg: Mrc<Expr>, depth: usize, f: Mrc<Expr>, x: Mrc<Expr>,
wrap: impl Fn(Mrc<Expr>, Mrc<Expr>) -> Clause
) -> Option<Clause> {
let new_f = apply_lambda_expr_rec(Mrc::clone(&f), Mrc::clone(&arg), depth);
let new_x = apply_lambda_expr_rec(Mrc::clone(&x), arg, depth);
match (new_f, new_x) {
(None, None) => None,
(None, Some(x)) => Some(wrap(f, x)),
(Some(f), None) => Some(wrap(f, x)),
(Some(f), Some(x)) => Some(wrap(f, x))
}
}
fn apply_lambda__traverse_param(
arg: Mrc<Expr>, depth: usize, t: Option<Mrc<Clause>>, b: Mrc<Expr>,
wrap: impl Fn(Option<Mrc<Clause>>, Mrc<Expr>) -> Clause
) -> Option<Clause> {
let new_t = t.as_ref().and_then(|t| {
apply_lambda_clause_rec(t.as_ref().clone(), Mrc::clone(&arg), depth)
});
let new_b = apply_lambda_expr_rec(Mrc::clone(&b), arg, depth + 1);
match (new_t, new_b) {
(None, None) => None,
(None, Some(b)) => Some(Clause::Lambda(t, b)),
(Some(t), None) => Some(Clause::Lambda(Some(Mrc::new(t)), b)),
(Some(t), Some(b)) => Some(Clause::Lambda(Some(Mrc::new(t)), b))
}
}

View File

@@ -10,7 +10,6 @@ pub trait ExternError: Display {}
/// Represents an externally defined function from the perspective of the executor
/// Since Orchid lacks basic numerical operations, these are also external functions.
#[derive(Eq)]
pub struct ExternFn {
name: String, param: Mrc<Expr>, rttype: Mrc<Expr>,
function: Mrc<dyn Fn(Clause) -> Result<Clause, Mrc<dyn ExternError>>>
@@ -27,8 +26,8 @@ impl ExternFn {
})
}
}
fn name(&self) -> &str {&self.name}
fn apply(&self, arg: Clause) -> Result<Clause, Mrc<dyn ExternError>> {(self.function)(arg)}
pub fn name(&self) -> &str {&self.name}
pub fn apply(&self, arg: Clause) -> Result<Clause, Mrc<dyn ExternError>> {(self.function)(arg)}
}
impl Clone for ExternFn { fn clone(&self) -> Self { Self {
@@ -37,7 +36,10 @@ impl Clone for ExternFn { fn clone(&self) -> Self { Self {
rttype: Mrc::clone(&self.rttype),
function: Mrc::clone(&self.function)
}}}
impl PartialEq for ExternFn { fn eq(&self, other: &Self) -> bool { self.name() == other.name() }}
impl Eq for ExternFn {}
impl PartialEq for ExternFn {
fn eq(&self, other: &Self) -> bool { self.name() == other.name() }
}
impl Hash for ExternFn {
fn hash<H: std::hash::Hasher>(&self, state: &mut H) { self.name.hash(state) }
}
@@ -58,7 +60,6 @@ pub trait Atomic: Any + Debug where Self: 'static {
/// information in the universe of types or kinds such as the type of signed integers or
/// the kind of types. Ad absurdum it can also be just a number, although Literal is
/// preferable for types it's defined on.
#[derive(Eq)]
pub struct Atom {
typ: Mrc<Expr>,
data: Mrc<dyn Atomic>
@@ -95,6 +96,7 @@ impl Debug for Atom {
write!(f, "##ATOM[{:?}]:{:?}##", self.data(), self.typ)
}
}
impl Eq for Atom {}
impl PartialEq for Atom {
fn eq(&self, other: &Self) -> bool {
self.data().definitely_eq(other.data().as_any())

View File

@@ -1,3 +1,7 @@
mod foreign;
// mod normalize;
mod partial_hash;
mod reduction_tree;
mod apply_lambda;
pub use foreign::ExternFn;
pub use foreign::Atom;

30
src/executor/normalize.rs Normal file
View File

@@ -0,0 +1,30 @@
use mappable_rc::Mrc;
use crate::utils::collect_to_mrc;
use super::super::representations::typed::{Clause, Expr};
fn normalize(Expr(clause, typ): Expr) -> Expr {
todo!()
}
fn collect_autos(
Expr(clause, typ): Expr,
arg_types: Vec<Mrc<[Clause]>>,
indirect_argt_trees: Vec<Mrc<[Clause]>>,
sunk_types: &mut dyn Iterator<Item = Clause>
) -> (Vec<Mrc<[Clause]>>, Expr) {
if let Clause::Auto(argt, body) = clause {
}
else {(
arg_types,
Expr(
clause,
collect_to_mrc(
typ.iter().cloned()
.chain(sunk_types)
)
)
)}
}

View File

@@ -0,0 +1,38 @@
use std::hash::{Hasher, Hash};
use super::super::representations::typed::{Clause, Expr};
use super::super::utils::Stackframe;
/// Hash the parts of an expression that are required to be equal for syntactic equality.
pub fn partial_hash_rec<H: Hasher>(Expr(clause, _): &Expr, state: &mut H, is_auto: Stackframe<bool>) {
match clause {
// Skip autos and explicits
Clause::Auto(_, body) => partial_hash_rec(body, state, is_auto.push(true)),
Clause::Explicit(f, _) => partial_hash_rec(f, state, is_auto),
// Annotate everything else with a prefix
// - Recurse into the tree of lambdas and calls - classic lambda calc
Clause::Lambda(_, body) => {
state.write_u8(0);
partial_hash_rec(body, state, is_auto.push(false))
}
Clause::Apply(f, x) => {
state.write_u8(1);
partial_hash_rec(f, state, is_auto);
partial_hash_rec(x, state, is_auto);
}
// - Only recognize the depth of an argument if it refers to a non-auto parameter
Clause::Argument(depth) => {
// If the argument references an auto, acknowledge its existence
if *is_auto.iter().nth(*depth).unwrap_or(&false) {
state.write_u8(2)
} else {
state.write_u8(3);
state.write_usize(*depth)
}
}
// - Hash leaves like normal
Clause::Literal(lit) => { state.write_u8(4); lit.hash(state) }
Clause::Atom(at) => { state.write_u8(5); at.hash(state) }
Clause::ExternFn(f) => { state.write_u8(6); f.hash(state) }
}
}

View File

@@ -0,0 +1,102 @@
use mappable_rc::Mrc;
use crate::box_chain;
use crate::utils::BoxedIter;
use crate::utils::iter::{box_once, box_empty};
use super::apply_lambda::apply_lambda;
use super::super::representations::typed::{Clause, Expr};
/// Call the function with the first Expression that isn't an Auto,
/// wrap all elements in the returned iterator back in the original sequence of Autos.
fn skip_autos<'a,
F: 'a + FnOnce(Mrc<Expr>, usize) -> I,
I: Iterator<Item = Mrc<Expr>> + 'static
>(
depth: usize, expr: Mrc<Expr>, function: F
) -> BoxedIter<'static, Mrc<Expr>> {
match expr.as_ref() {
Expr(Clause::Auto(arg, body), typ) => {
return Box::new(skip_autos(depth + 1, Mrc::clone(body), function).map({
let arg = arg.as_ref().map(Mrc::clone);
let typ = Mrc::clone(typ);
move |body| {
Mrc::new(Expr(Clause::Auto(
arg.as_ref().map(Mrc::clone),
body
), Mrc::clone(&typ)))
}
})) as BoxedIter<'static, Mrc<Expr>>
}
Expr(Clause::Explicit(expr, targ), typ) => {
return Box::new(skip_autos(depth, Mrc::clone(expr), function).map({
let (targ, typ) = (Mrc::clone(targ), Mrc::clone(typ));
move |expr| {
Mrc::new(Expr(Clause::Explicit(expr, Mrc::clone(&targ)), Mrc::clone(&typ)))
}
})) as BoxedIter<'static, Mrc<Expr>>
}
_ => ()
}
Box::new(function(expr, depth))
}
/// Produces an iterator of every expression that can be produced from this one through B-reduction.
fn direct_reductions(ex: Mrc<Expr>) -> impl Iterator<Item = Mrc<Expr>> {
skip_autos(0, ex, |mexpr, _| {
let Expr(clause, typ_ref) = mexpr.as_ref();
match clause {
Clause::Apply(f, x) => box_chain!(
skip_autos(0, Mrc::clone(f), |mexpr, _| {
let Expr(f, _) = mexpr.as_ref();
match f {
Clause::Lambda(_, body) => box_once(
apply_lambda(Mrc::clone(body), Mrc::clone(x))
),
Clause::ExternFn(xfn) => {
let Expr(xval, xtyp) = x.as_ref();
xfn.apply(xval.clone())
.map(|ret| box_once(Mrc::new(Expr(ret, Mrc::clone(xtyp)))))
.unwrap_or(box_empty())
},
// Parametric newtypes are atoms of function type
Clause::Atom(..) | Clause::Argument(..) | Clause::Apply(..) => box_empty(),
Clause::Literal(lit) =>
panic!("Literal expression {lit:?} can't be applied as function"),
Clause::Auto(..) | Clause::Explicit(..) =>
unreachable!("skip_autos should have filtered these"),
}
}),
direct_reductions(Mrc::clone(f)).map({
let typ = Mrc::clone(typ_ref);
let x = Mrc::clone(x);
move |f| Mrc::new(Expr(Clause::Apply(
f,
Mrc::clone(&x)
), Mrc::clone(&typ)))
}),
direct_reductions(Mrc::clone(x)).map({
let typ = Mrc::clone(typ_ref);
let f = Mrc::clone(f);
move |x| Mrc::new(Expr(Clause::Apply(
Mrc::clone(&f),
x
), Mrc::clone(&typ)))
})
),
Clause::Lambda(argt, body) => Box::new(direct_reductions(Mrc::clone(body)).map({
let typ = Mrc::clone(typ_ref);
let argt = argt.as_ref().map(Mrc::clone);
move |body| Mrc::new(Expr(Clause::Lambda(
argt.as_ref().map(Mrc::clone),
body
), Mrc::clone(&typ)))
})),
Clause::Literal(..) | Clause::ExternFn(..) | Clause::Atom(..) | Clause::Argument(..) =>
box_empty(),
Clause::Auto(..) | Clause::Explicit(..) =>
unreachable!("skip_autos should have filtered these"),
}
})
}

41
src/executor/syntax_eq.rs Normal file
View File

@@ -0,0 +1,41 @@
use std::hash::{Hasher, Hash};
use super::super::representations::typed::{Clause, Expr};
use super::super::utils::Stackframe;
/// Hash the parts of an expression that are required to be equal for syntactic equality.
pub fn syntax_eq_rec<H: Hasher>(
ex1: &Expr, ex1_stack: Stackframe<bool>,
ex2: &Expr, ex2_stack: Stackframe<bool>
) -> bool {
match clause {
// Skip autos and explicits
Clause::Auto(_, body) => partial_hash_rec(body, state, is_auto.push(true)),
Clause::Explicit(f, _) => partial_hash_rec(f, state, is_auto),
// Annotate everything else with a prefix
// - Recurse into the tree of lambdas and calls - classic lambda calc
Clause::Lambda(_, body) => {
state.write_u8(0);
partial_hash_rec(body, state, is_auto.push(false))
}
Clause::Apply(f, x) => {
state.write_u8(1);
partial_hash_rec(f, state, is_auto);
partial_hash_rec(x, state, is_auto);
}
// - Only recognize the depth of an argument if it refers to a non-auto parameter
Clause::Argument(depth) => {
// If the argument references an auto, acknowledge its existence
if *is_auto.iter().nth(*depth).unwrap_or(&false) {
state.write_u8(2)
} else {
state.write_u8(3);
state.write_usize(*depth)
}
}
// - Hash leaves like normal
Clause::Literal(lit) => { state.write_u8(4); lit.hash(state) }
Clause::Atom(at) => { state.write_u8(5); at.hash(state) }
Clause::ExternFn(f) => { state.write_u8(6); f.hash(state) }
}
}