add hex constants and data segments

This commit is contained in:
2021-11-12 22:08:53 +01:00
parent 51cf8a8d28
commit e4bf292e47
14 changed files with 355 additions and 84 deletions

View File

@@ -1,13 +1,13 @@
import "env.memory" memory(4);
import "math.sin" fn sin(f32) -> f32;
import "math.cos" fn cos(f32) -> f32;
import "env.sin" fn sin(f32) -> f32;
import "env.cos" fn cos(f32) -> f32;
export fn tic(time: i32) {
let i: i32;
loop screen {
let defer x = (i % 320) as f32 / 48 as f32;
let defer y = (i / 320) as f32 / 48 as f32;
let defer t = time as f32 / 200 as f32;
let lazy x = (i % 320) as f32 / 48 as f32;
let lazy y = (i / 320) as f32 / 48 as f32;
let lazy t = time as f32 / 200 as f32;
i?120 = ((sin(x + sin(y - t / 4 as f32) * 3 as f32 + t / 5 as f32) + sin(y + sin(x - t / 3 as f32) + t / 6 as f32)) * 63 as f32) as i32 + 128;

View File

@@ -12,7 +12,7 @@ fn random64() -> i64 {
state := randomState ^ (randomState #>> 12i64)
) ^ (state << 25i64)
) ^ (state #>> 27i64);
randomState * 2685821657736338717i64
randomState * 0x2545f4914f6cdd1di64
}
fn randomf() -> f32 {

View File

@@ -5,16 +5,16 @@ import "env.atan2" fn atan2(f32, f32) -> f32;
export fn tic(time: i32) {
let i: i32;
loop screen {
let defer t = time as f32 / 2000 as f32;
let defer o = sin(t) * 0.8;
let defer q = (i % 320) as f32 - 160.1;
let defer w = (i / 320 - 128) as f32;
let defer r = sqrt(q*q + w*w);
let defer z = q / r;
let defer s = z * o + sqrt(z * z * o * o + 1 as f32 - o * o);
let defer q2 = (z * s - o) * 10 as f32 + t;
let defer w2 = w / r * s * 10 as f32 + t;
let defer s2 = s * 50 as f32 / r;
let lazy t = time as f32 / 2000 as f32;
let lazy o = sin(t) * 0.8;
let lazy q = (i % 320) as f32 - 160.1;
let lazy w = (i / 320 - 128) as f32;
let lazy r = sqrt(q*q + w*w);
let lazy z = q / r;
let lazy s = z * o + sqrt(z * z * o * o + 1 as f32 - o * o);
let lazy q2 = (z * s - o) * 10 as f32 + t;
let lazy w2 = w / r * s * 10 as f32 + t;
let lazy s2 = s * 50 as f32 / r;
i?120 = max(
0 as f32,
((q2 as i32 ^ w2 as i32 & ((s2 + t) * 20 as f32) as i32) & 5) as f32 *

View File

@@ -2,16 +2,16 @@ import "env.memory" memory(2);
export fn tic(time: i32) {
let i: i32;
let defer t = time as f32 / 1000 as f32;
let lazy t = time as f32 / 1000 as f32;
loop pixels {
let defer x = (i % 320 - 160) as f32;
let defer y = (i / 320) as f32 - 128.5;
let defer z = t + 20 as f32 / sqrt(x*x + y*y);
let defer z_int = z as i32;
let defer q = select(z_int % 9 >= 6, z, (z_int - z_int % 9 + 6) as f32);
let defer w = 9 as f32 / y + t;
let defer s = q - t;
let defer m = x * s / 50 as f32;
let lazy x = (i % 320 - 160) as f32;
let lazy y = (i / 320) as f32 - 128.5;
let lazy z = t + 20 as f32 / sqrt(x*x + y*y);
let lazy z_int = z as i32;
let lazy q = select(z_int % 9 >= 6, z, (z_int - z_int % 9 + 6) as f32);
let lazy w = 9 as f32 / y + t;
let lazy s = q - t;
let lazy m = x * s / 50 as f32;
i?120 = select(y > 0 as f32 & w < q,
select(abs(x * (w - t)) < 9 as f32, 15, 7) - w as i32 % 2,

View File

@@ -4,9 +4,9 @@ import "env.atan2" fn atan2(f32, f32) -> f32;
export fn tic(time: i32) {
let i: i32;
loop screen {
let defer t = time as f32 / 10 as f32;
let defer x = (i % 320) as f32 - 160.1;
let defer y = (i / 320 - 128) as f32;
let lazy t = time as f32 / 10 as f32;
let lazy x = (i % 320) as f32 - 160.1;
let lazy y = (i / 320 - 128) as f32;
i?120 = ((20000 as f32 / sqrt(x * x + y * y) + t) as i32 ^ (atan2(x, y) * 512 as f32 / 3.141 + t) as i32);
branch_if (i := i + 1) < 320*256: screen

View File

@@ -3,10 +3,10 @@ import "env.memory" memory(2);
export fn tic(time: i32) {
let i: i32;
loop pixels {
let defer x = (i % 320) as f32 - 160.1;
let defer y = (i / 320 - 128) as f32;
let defer dist = 10000.0 / (x*x + y*y);
let defer t = time as f32 / 20 as f32;
let lazy x = (i % 320) as f32 - 160.1;
let lazy y = (i / 320 - 128) as f32;
let lazy dist = 10000.0 / (x*x + y*y);
let lazy t = time as f32 / 20 as f32;
i?120 = (x * dist + t) as i32 ^ (y * dist + t) as i32;

10
examples/wasm4/hello.cwa Normal file
View File

@@ -0,0 +1,10 @@
import "env.memory" memory(1);
import "env.text" fn text(i32, i32, i32);
export fn update() {
text(0x3f, 8, 8);
}
data 0x3f {
"Hello, World!"
}

View File

@@ -25,22 +25,22 @@ fn set_color(color: i32) -> i32 {
export fn update() {
let y: i32;
let score = pz;
let defer pad = ?22;
let defer zero = 0.0;
let lazy pad = ?22;
let lazy zero = 0.0;
let defer control_speed = 0.03;
let lazy control_speed = 0.03;
s = s + 0.1 - (f + control_speed) * (pad & 1) as f32;
f = f * 0.7;
loop lines {
?(8003-y) = (score := score / 10) % 10 + 48;
let defer z = (4000 / (y := y + 1) + pz) / 20;
let defer x = (rng(rng(rng(rng(z)))) >> 30) as f32 - px;
let defer w = 9 as f32 / sqrt(z as f32);
let defer rx = 80 + (y as f32 * x) as i32;
let defer rw = (y as f32 * w) as i32;
let lazy z = (4000 / (y := y + 1) + pz) / 20;
let lazy x = (rng(rng(rng(rng(z)))) >> 30) as f32 - px;
let lazy w = 9 as f32 / sqrt(z as f32);
let lazy rx = 80 + (y as f32 * x) as i32;
let lazy rw = (y as f32 * w) as i32;
let defer c = ((z & 1) + 2) * 17;
let lazy c = ((z & 1) + 2) * 17;
rect(rx, y, rw, y / set_color(c + 17));
text(8000, set_color(c) <| rect(rx, y, rw, 1), set_color(4));
@@ -61,7 +61,7 @@ export fn update() {
branch_if y < 160: lines;
}
let defer sy = 114 - 11 + py as i32;
let lazy sy = 114 - 11 + py as i32;
oval(80 - 6, sy + 5, (set_color(50) <| oval(80 - 11, sy, 22, 22)), set_color(17));
px = px + (!(pad & 16) - !(pad & 32)) as f32 * control_speed;

View File

@@ -7,6 +7,7 @@ pub struct Script {
pub imports: Vec<Import>,
pub global_vars: Vec<GlobalVar>,
pub functions: Vec<Function>,
pub data: Vec<Data>,
}
#[derive(Debug)]
@@ -14,6 +15,7 @@ pub enum TopLevelItem {
Import(Import),
GlobalVar(GlobalVar),
Function(Function),
Data(Data),
}
#[derive(Debug)]
@@ -57,6 +59,31 @@ pub struct Function {
pub body: Expression,
}
#[derive(Debug)]
pub struct Data {
pub offset: Box<Expression>,
pub data: Vec<DataValues>,
}
#[derive(Debug)]
pub enum DataValues {
Array {
type_: DataType,
values: Vec<Expression>,
},
String(String),
}
#[derive(Debug, Clone)]
pub enum DataType {
I8,
I16,
I32,
I64,
F32,
F64,
}
#[derive(Debug)]
pub struct MemoryLocation {
pub span: Span,
@@ -72,6 +99,36 @@ pub struct Expression {
pub span: Span,
}
impl Expression {
pub fn const_i32(&self) -> i32 {
match self.expr {
Expr::I32Const(v) => v,
_ => panic!("Expected I32Const")
}
}
pub fn const_i64(&self) -> i64 {
match self.expr {
Expr::I64Const(v) => v,
_ => panic!("Expected I64Const")
}
}
pub fn const_f32(&self) -> f32 {
match self.expr {
Expr::F32Const(v) => v,
_ => panic!("Expected F32Const")
}
}
pub fn const_f64(&self) -> f64 {
match self.expr {
Expr::F64Const(v) => v,
_ => panic!("Expected F64Const")
}
}
}
#[derive(Debug)]
pub enum Expr {
Block {
@@ -87,7 +144,7 @@ pub enum Expr {
name: String,
type_: Option<Type>,
value: Option<Box<Expression>>,
defer: bool,
let_type: LetType,
},
Poke {
mem_location: MemoryLocation,
@@ -143,7 +200,7 @@ pub enum Expr {
},
First {
value: Box<Expression>,
drop: Box<Expression>
drop: Box<Expression>,
},
Error,
}
@@ -158,6 +215,13 @@ impl Expr {
}
}
#[derive(Debug, Clone, Copy)]
pub enum LetType {
Normal,
Lazy,
Inline,
}
#[derive(Debug, Clone, Copy)]
pub enum UnaryOp {
Negate,

View File

@@ -8,6 +8,20 @@ pub fn fold_script(script: &mut ast::Script) {
for func in &mut script.functions {
fold_expr(&mut func.body);
}
for data in &mut script.data {
fold_expr(&mut data.offset);
for values in &mut data.data {
match values {
ast::DataValues::Array { values, .. } => {
for value in values {
fold_expr(value);
}
}
ast::DataValues::String(_) => (),
}
}
}
}
fn fold_mem_location(mem_location: &mut ast::MemoryLocation) {

View File

@@ -1,9 +1,9 @@
use std::collections::HashMap;
use wasm_encoder::{
BlockType, CodeSection, EntityType, Export, ExportSection, Function, FunctionSection,
GlobalSection, GlobalType, ImportSection, Instruction, MemArg, MemoryType, Module, TypeSection,
ValType,
BlockType, CodeSection, DataSection, EntityType, Export, ExportSection, Function,
FunctionSection, GlobalSection, GlobalType, ImportSection, Instruction, MemArg, MemoryType,
Module, TypeSection, ValType,
};
use crate::{ast, intrinsics::Intrinsics};
@@ -121,6 +121,60 @@ pub fn emit(script: &ast::Script) -> Vec<u8> {
module.section(&code);
}
if !script.data.is_empty() {
let mut data_section = DataSection::new();
for data in &script.data {
let mut segment_data: Vec<u8> = vec![];
for values in &data.data {
match values {
ast::DataValues::Array { type_, values } => {
let width = match *type_ {
ast::DataType::I8 => 1,
ast::DataType::I16 => 2,
ast::DataType::I32 => 4,
ast::DataType::I64 => 8,
ast::DataType::F32 => 4,
ast::DataType::F64 => 8,
};
while segment_data.len() % width != 0 {
segment_data.push(0);
}
for value in values {
match *type_ {
ast::DataType::I8 => segment_data.push(value.const_i32() as u8),
ast::DataType::I16 => segment_data
.extend_from_slice(&(value.const_i32() as u16).to_le_bytes()),
ast::DataType::I32 => segment_data
.extend_from_slice(&(value.const_i32() as u32).to_le_bytes()),
ast::DataType::I64 => segment_data
.extend_from_slice(&(value.const_i64() as u64).to_le_bytes()),
ast::DataType::F32 => {
segment_data.extend_from_slice(&value.const_f32().to_le_bytes())
}
ast::DataType::F64 => {
segment_data.extend_from_slice(&value.const_f64().to_le_bytes())
}
}
}
}
ast::DataValues::String(s) => {
for c in s.chars() {
segment_data.push(c as u8);
}
}
}
}
data_section.active(
0,
&wasm_encoder::Instruction::I32Const(data.offset.const_i32()),
segment_data,
);
}
module.section(&data_section);
}
module.finish()
}
@@ -172,7 +226,7 @@ struct FunctionContext<'a> {
functions: &'a HashMap<String, u32>,
locals: &'a HashMap<String, u32>,
labels: Vec<String>,
deferred_inits: HashMap<&'a str, &'a ast::Expression>,
let_values: HashMap<&'a str, (&'a ast::Expression, ast::LetType)>,
intrinsics: &'a Intrinsics,
}
@@ -204,7 +258,7 @@ fn emit_function(
functions,
locals: &local_map,
labels: vec![],
deferred_inits: HashMap::new(),
let_values: HashMap::new(),
intrinsics,
};
@@ -336,15 +390,21 @@ fn emit_expression<'a>(ctx: &mut FunctionContext<'a>, expr: &'a ast::Expression)
}
}
ast::Expr::Let {
value, name, defer, ..
value,
name,
let_type,
..
} => {
if let Some(ref val) = value {
if *defer {
ctx.deferred_inits.insert(name, val);
} else {
emit_expression(ctx, val);
ctx.function
.instruction(&Instruction::LocalSet(*ctx.locals.get(name).unwrap()));
if let Some(ref value) = value {
match let_type {
ast::LetType::Normal => {
emit_expression(ctx, value);
ctx.function
.instruction(&Instruction::LocalSet(*ctx.locals.get(name).unwrap()));
}
ast::LetType::Lazy | ast::LetType::Inline => {
ctx.let_values.insert(name, (value, *let_type));
}
}
}
}
@@ -552,9 +612,19 @@ fn emit_expression<'a>(ctx: &mut FunctionContext<'a>, expr: &'a ast::Expression)
}
ast::Expr::Variable(name) => {
if let Some(index) = ctx.locals.get(name) {
if let Some(expr) = ctx.deferred_inits.remove(name.as_str()) {
emit_expression(ctx, expr);
ctx.function.instruction(&Instruction::LocalTee(*index));
if let Some((expr, let_type)) = ctx.let_values.get(name.as_str()) {
match let_type {
ast::LetType::Lazy => {
let expr = ctx.let_values.remove(name.as_str()).unwrap().0;
emit_expression(ctx, expr);
ctx.function.instruction(&Instruction::LocalTee(*index));
}
ast::LetType::Inline => {
let expr = *expr;
emit_expression(ctx, expr);
}
_ => unreachable!(),
}
} else {
ctx.function.instruction(&Instruction::LocalGet(*index));
}

View File

@@ -16,12 +16,14 @@ enum Token {
Loop,
Branch,
BranchIf,
Defer,
Lazy,
Inline,
As,
Select,
If,
Else,
Return,
Data,
Ident(String),
Str(String),
Int(i32),
@@ -45,12 +47,14 @@ impl fmt::Display for Token {
Token::Loop => write!(f, "loop"),
Token::Branch => write!(f, "branch"),
Token::BranchIf => write!(f, "branch_if"),
Token::Defer => write!(f, "defer"),
Token::Lazy => write!(f, "lazy"),
Token::Inline => write!(f, "inline"),
Token::As => write!(f, "as"),
Token::Select => write!(f, "select"),
Token::If => write!(f, "if"),
Token::Else => write!(f, "else"),
Token::Return => write!(f, "return"),
Token::Data => write!(f, "data"),
Token::Ident(s) => write!(f, "{}", s),
Token::Str(s) => write!(f, "{:?}", s),
Token::Int(v) => write!(f, "{}", v),
@@ -179,12 +183,26 @@ fn lexer() -> impl Parser<char, Vec<(Token, Span)>, Error = Simple<char>> {
.collect::<String>()
.map(Token::Float);
// TODO: support hex numbers
let int64 = text::int(10)
.then_ignore(seq::<_, _, Simple<char>>("i64".chars()))
.map(|s: String| Token::Int64(s.parse::<u64>().unwrap() as i64));
let integer = seq::<_, _, Simple<char>>("0x".chars())
.ignore_then(text::int(16))
.try_map(|n, span| {
u64::from_str_radix(&n, 16).map_err(|err| Simple::custom(span, err.to_string()))
})
.or(text::int(10).try_map(|n: String, span: Span| {
u64::from_str_radix(&n, 10).map_err(|err| Simple::custom(span, err.to_string()))
}))
.boxed();
let int = text::int(10).map(|s: String| Token::Int(s.parse::<u32>().unwrap() as i32));
let int64 = integer
.clone()
.then_ignore(seq::<_, _, Simple<char>>("i64".chars()))
.map(|n| Token::Int64(n as i64));
let int = integer.try_map(|n, span| {
u32::try_from(n)
.map(|n| Token::Int(n as i32))
.map_err(|err| Simple::custom(span, err.to_string()))
});
let str_ = just('"')
.ignore_then(filter(|c| *c != '"').repeated())
@@ -221,12 +239,14 @@ fn lexer() -> impl Parser<char, Vec<(Token, Span)>, Error = Simple<char>> {
"loop" => Token::Loop,
"branch" => Token::Branch,
"branch_if" => Token::BranchIf,
"defer" => Token::Defer,
"lazy" => Token::Lazy,
"inline" => Token::Inline,
"as" => Token::As,
"select" => Token::Select,
"if" => Token::If,
"else" => Token::Else,
"return" => Token::Return,
"data" => Token::Data,
_ => Token::Ident(ident),
});
@@ -364,7 +384,12 @@ fn script_parser() -> impl Parser<Token, ast::Script, Error = Simple<Token>> + C
.boxed();
let let_ = just(Token::Let)
.ignore_then(just(Token::Defer).or_not())
.ignore_then(
(just(Token::Lazy)
.to(ast::LetType::Lazy)
.or(just(Token::Inline).to(ast::LetType::Inline)))
.or_not(),
)
.then(identifier.clone())
.then(just(Token::Ctrl(':')).ignore_then(type_parser()).or_not())
.then(
@@ -372,11 +397,11 @@ fn script_parser() -> impl Parser<Token, ast::Script, Error = Simple<Token>> + C
.ignore_then(expression.clone())
.or_not(),
)
.map(|(((defer, name), type_), value)| ast::Expr::Let {
.map(|(((let_type, name), type_), value)| ast::Expr::Let {
name,
type_,
value: value.map(Box::new),
defer: defer.is_some(),
let_type: let_type.unwrap_or(ast::LetType::Normal),
})
.boxed();
@@ -545,7 +570,7 @@ fn script_parser() -> impl Parser<Token, ast::Script, Error = Simple<Token>> + C
} else {
make_memory_op(left, vec![(size, right)], None)
}
});
}).clone();
let memory_op = op_cast
.clone()
@@ -681,12 +706,22 @@ fn script_parser() -> impl Parser<Token, ast::Script, Error = Simple<Token>> + C
})
.boxed();
let op_first = op_bit.clone().then(
just(Token::Op("<|".to_string())).ignore_then(op_bit).repeated()
).foldl(|left, right| {
let span = left.span.start..right.span.end;
ast::Expr::First { value: Box::new(left), drop: Box::new(right) }.with_span(span)
}).boxed();
let op_first = op_bit
.clone()
.then(
just(Token::Op("<|".to_string()))
.ignore_then(op_bit)
.repeated(),
)
.foldl(|left, right| {
let span = left.span.start..right.span.end;
ast::Expr::First {
value: Box::new(left),
drop: Box::new(right),
}
.with_span(span)
})
.boxed();
op_first
});
@@ -707,14 +742,18 @@ fn script_parser() -> impl Parser<Token, ast::Script, Error = Simple<Token>> + C
final_expression: final_expression.map(|e| Box::new(e)),
}
.with_span(span)
})
}).boxed()
});
let expression = expression_out.unwrap();
let top_level_item = {
let import_memory = just(Token::Memory)
.ignore_then(integer.delimited_by(Token::Ctrl('('), Token::Ctrl(')')))
.ignore_then(
integer
.clone()
.delimited_by(Token::Ctrl('('), Token::Ctrl(')')),
)
.map(|min_size| ast::ImportType::Memory(min_size as u32))
.boxed();
@@ -750,7 +789,7 @@ fn script_parser() -> impl Parser<Token, ast::Script, Error = Simple<Token>> + C
.boxed();
let import = just(Token::Import)
.ignore_then(string)
.ignore_then(string.clone())
.then(import_memory.or(import_global).or(import_function))
.then_ignore(just(Token::Ctrl(';')))
.map_with_span(|(import, type_), span| {
@@ -813,9 +852,41 @@ fn script_parser() -> impl Parser<Token, ast::Script, Error = Simple<Token>> + C
mutable: mutable.is_some(),
span,
})
});
}).boxed();
import.or(function).or(global).boxed()
let data_i8 = just(Token::Ident("i8".to_string()))
.to(ast::DataType::I8)
.or(just(Token::Ident("i16".to_string())).to(ast::DataType::I16))
.or(just(Token::Ident("i32".to_string())).to(ast::DataType::I32))
.or(just(Token::Ident("i64".to_string())).to(ast::DataType::I64))
.or(just(Token::Ident("f32".to_string())).to(ast::DataType::F32))
.or(just(Token::Ident("f64".to_string())).to(ast::DataType::F64))
.then(
expression.clone()
.separated_by(just(Token::Ctrl(',')))
.delimited_by(Token::Ctrl('('), Token::Ctrl(')')),
)
.map(|(type_, values)| ast::DataValues::Array { type_, values });
let data_string = string.map(|s| ast::DataValues::String(s));
let data = just(Token::Data)
.ignore_then(expression.clone())
.then(
data_i8
.or(data_string)
.repeated()
.delimited_by(Token::Ctrl('{'), Token::Ctrl('}')),
)
.map(|(offset, data)| {
ast::TopLevelItem::Data(ast::Data {
offset: Box::new(offset),
data,
})
})
.boxed();
import.or(function).or(global).or(data).boxed()
};
top_level_item.repeated().then_ignore(end()).map(|items| {
@@ -823,12 +894,14 @@ fn script_parser() -> impl Parser<Token, ast::Script, Error = Simple<Token>> + C
imports: Vec::new(),
global_vars: Vec::new(),
functions: Vec::new(),
data: Vec::new(),
};
for item in items {
match item {
ast::TopLevelItem::Import(i) => script.imports.push(i),
ast::TopLevelItem::GlobalVar(v) => script.global_vars.push(v),
ast::TopLevelItem::Function(f) => script.functions.push(f),
ast::TopLevelItem::Data(d) => script.data.push(d),
}
}
script

View File

@@ -150,6 +150,46 @@ pub fn tc_script(script: &mut ast::Script, source: &str) -> Result<()> {
}
}
for data in &mut script.data {
tc_const(&mut data.offset, source)?;
if data.offset.type_ != Some(I32) {
result = type_mismatch(
Some(I32),
&data.offset.span,
data.offset.type_,
&data.offset.span,
source,
);
}
for values in &mut data.data {
match values {
ast::DataValues::Array { type_, values } => {
let needed_type = match type_ {
ast::DataType::I8 | ast::DataType::I16 | ast::DataType::I32 => {
ast::Type::I32
}
ast::DataType::I64 => ast::Type::I64,
ast::DataType::F32 => ast::Type::F32,
ast::DataType::F64 => ast::Type::F64,
};
for value in values {
tc_const(value, source)?;
if value.type_ != Some(needed_type) {
result = type_mismatch(
Some(needed_type),
&value.span,
value.type_,
&value.span,
source,
);
}
}
}
ast::DataValues::String(_) => (),
}
}
}
result
}