Skip to content

Commit

Permalink
Merge pull request #635 from Shaikh-Ubaid/wasm_support_funcs_in_any_o…
Browse files Browse the repository at this point in the history
…rder

WASM: Support defining functions in any order
  • Loading branch information
Shaikh-Ubaid committed Aug 19, 2022
2 parents ed07c74 + 6fdfd9f commit 5fc1027
Show file tree
Hide file tree
Showing 19 changed files with 273 additions and 108 deletions.
1 change: 1 addition & 0 deletions integration_tests/CMakeLists.txt
Original file line number Diff line number Diff line change
Expand Up @@ -416,6 +416,7 @@ RUN(NAME types_11 LABELS gfortran)
RUN(NAME types_12 LABELS gfortran llvm)
RUN(NAME types_13 LABELS gfortran)
RUN(NAME types_14 LABELS gfortran llvm)
RUN(NAME types_16 LABELS gfortran llvm wasm)

RUN(NAME complex_01 LABELS gfortran llvm)
RUN(NAME complex_02 LABELS gfortran llvm)
Expand Down
10 changes: 5 additions & 5 deletions tests/wasm_floats.f90 → integration_tests/types_16.f90
Original file line number Diff line number Diff line change
@@ -1,15 +1,15 @@
program wasm_floats
program types_16
implicit none
integer, parameter :: dp = kind(0.d0)

print *, add_floats(-2.3, 5.6)
print *, get_neg_f32()
print *, get_pi()
print *, get_pi_64()
print *, z_computeCircleArea(5.0_dp)
print *, computeCircleArea(5.0_dp)

contains
function a_sqr(x) result(r)
function sqr(x) result(r)
implicit none
real(dp), intent(in):: x
real(dp) :: r
Expand Down Expand Up @@ -42,12 +42,12 @@ function get_neg_f32() result(r)
return
end function

function z_computeCircleArea(radius) result(area)
function computeCircleArea(radius) result(area)
implicit none
real(dp), intent(in):: radius
real(dp) :: PI, area
PI = get_pi_64()
area = PI * a_sqr(radius)
area = PI * sqr(radius)
return
end function
end program
81 changes: 57 additions & 24 deletions src/libasr/codegen/asr_to_wasm.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -81,6 +81,7 @@ class ASRToWASMVisitor : public ASR::BaseVisitor<ASRToWASMVisitor> {
SymbolFuncInfo* cur_sym_info;
uint32_t nesting_level;
uint32_t cur_loop_nesting_level;
bool is_prototype_only;

Vec<uint8_t> m_type_section;
Vec<uint8_t> m_import_section;
Expand All @@ -106,6 +107,7 @@ class ASRToWASMVisitor : public ASR::BaseVisitor<ASRToWASMVisitor> {
public:
ASRToWASMVisitor(Allocator &al, diag::Diagnostics &diagnostics): m_al(al), diag(diagnostics) {
intrinsic_module = false;
is_prototype_only = false;
nesting_level = 0;
cur_loop_nesting_level = 0;
no_of_types = 0;
Expand Down Expand Up @@ -149,12 +151,6 @@ class ASRToWASMVisitor : public ASR::BaseVisitor<ASRToWASMVisitor> {
return nullptr;
}

void add_func_to_imports(const ASR::Function_t &x) {
wasm::emit_import_fn(m_import_section, m_al, "js", x.m_name, no_of_types);
emit_function_prototype(x);
no_of_imports++;
}

void import_function(ImportFunc &import_func) {
Vec<ASR::expr_t*> params;
params.reserve(m_al, import_func.param_types.size());
Expand Down Expand Up @@ -210,6 +206,37 @@ class ASRToWASMVisitor : public ASR::BaseVisitor<ASRToWASMVisitor> {

emit_imports();

{
// Pre-declare all functions first, then generate code
// Otherwise some function might not be found.
is_prototype_only = true;
{
// Process intrinsic modules in the right order
std::vector<std::string> build_order
= ASRUtils::determine_module_dependencies(x);
for (auto &item : build_order) {
LFORTRAN_ASSERT(x.m_global_scope->get_scope().find(item)
!= x.m_global_scope->get_scope().end());
if (startswith(item, "lfortran_intrinsic")) {
ASR::symbol_t *mod = x.m_global_scope->get_symbol(item);
if (ASR::is_a<ASR::Module_t>(*mod)) {
ASR::Module_t *m = ASR::down_cast<ASR::Module_t>(mod);
declare_all_functions(*(m->m_symtab));
}
}
}

// then the main program:
for (auto &item : x.m_global_scope->get_scope()) {
if (ASR::is_a<ASR::Program_t>(*item.second)) {
ASR::Program_t *p = ASR::down_cast<ASR::Program_t>(item.second);
declare_all_functions(*(p->m_symtab));
}
}
}
is_prototype_only = false;
}

{
// Process intrinsic modules in the right order
std::vector<std::string> build_order
Expand Down Expand Up @@ -254,39 +281,38 @@ class ASRToWASMVisitor : public ASR::BaseVisitor<ASRToWASMVisitor> {
}
}

void declare_all_functions(const SymbolTable &symtab) {
for (auto &item : symtab.get_scope()) {
if (ASR::is_a<ASR::Function_t>(*item.second)) {
ASR::Function_t *s = ASR::down_cast<ASR::Function_t>(item.second);
this->visit_Function(*s);
}
}
}

void visit_Module(const ASR::Module_t &x) {
if (startswith(x.m_name, "lfortran_intrinsic_")) {
intrinsic_module = true;
} else {
intrinsic_module = false;
}

std::string contains;

// Generate the bodies of subroutines
for (auto &item : x.m_symtab->get_scope()) {
if (ASR::is_a<ASR::Function_t>(*item.second)) {
ASR::Function_t *s = ASR::down_cast<ASR::Function_t>(item.second);
this->visit_Function(*s);
}
}
// Generate the bodies of functions and subroutines
declare_all_functions(*x.m_symtab);
intrinsic_module = false;
}

void visit_Program(const ASR::Program_t &x) {

for (auto &item : x.m_symtab->get_scope()) {
if (ASR::is_a<ASR::Function_t>(*item.second)) {
ASR::Function_t *s = ASR::down_cast<ASR::Function_t>(item.second);
visit_Function(*s);
}
}
// Generate the bodies of functions and subroutines
declare_all_functions(*x.m_symtab);

// Generate main program code
auto main_func = ASR::make_Function_t(m_al, x.base.base.loc, x.m_symtab, s2c(m_al, "_lcompilers_main"),
nullptr, 0, nullptr, 0, x.m_body, x.n_body, nullptr, ASR::abiType::Source, ASR::accessType::Public,
ASR::deftypeType::Implementation, nullptr, false, false, false);
this->visit_Function(*((ASR::Function_t *)main_func));
emit_function_prototype(*((ASR::Function_t *)main_func));
emit_function_body(*((ASR::Function_t *)main_func));
}

void emit_var_type(Vec<uint8_t> &code, ASR::Variable_t *v){
Expand Down Expand Up @@ -533,11 +559,18 @@ class ASRToWASMVisitor : public ASR::BaseVisitor<ASRToWASMVisitor> {
if (is_unsupported_function(x)) {
return;
}
if (is_prototype_only) {
if (x.m_abi == ASR::abiType::BindC && x.m_deftype == ASR::deftypeType::Interface) {
wasm::emit_import_fn(m_import_section, m_al, "js", x.m_name, no_of_types);
no_of_imports++;
}
emit_function_prototype(x);
return;
}
if (x.m_abi == ASR::abiType::BindC && x.m_deftype == ASR::deftypeType::Interface) {
add_func_to_imports(x);
/* functions of abiType BindC and are Interfaces are already handled */
return;
}
emit_function_prototype(x);
emit_function_body(x);
}

Expand Down
2 changes: 1 addition & 1 deletion tests/reference/wat-abs_01-0c0b4df.json
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,6 @@
"stdout": "wat-abs_01-0c0b4df.stdout",
"stdout_hash": "a8d791fdc77bcad3592c377efdeed54d7118e14f762510ac354c749c",
"stderr": "wat-abs_01-0c0b4df.stderr",
"stderr_hash": "f2b163e63b728d7b597553ecad8b4ed09f32b3087fa26b918052875d",
"stderr_hash": "63260848012027025fefe1a5cef7dcd73f9eadd0bd6cec31e1eeda69",
"returncode": 0
}
42 changes: 42 additions & 0 deletions tests/reference/wat-abs_01-0c0b4df.stderr
Original file line number Diff line number Diff line change
Expand Up @@ -39,3 +39,45 @@ warning: WASM: Calls to C Intrinsic Functions are not yet supported
|
1 | program abs_01
| ^ Function: calls c_sp_rand_num

warning: Function with no body
--> tests/../integration_tests/abs_01.f90:1:1
|
1 | program abs_01
| ^ char

warning: Function with no body
--> tests/../integration_tests/abs_01.f90:1:1
|
1 | program abs_01
| ^ move_alloc

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/abs_01.f90:1:1
|
1 | program abs_01
| ^ Function: calls c_cpu_time

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/abs_01.f90:1:1
|
1 | program abs_01
| ^ Function: calls c_dp_rand_num

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/abs_01.f90:1:1
|
1 | program abs_01
| ^ Function: calls c_i32sys_clock

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/abs_01.f90:1:1
|
1 | program abs_01
| ^ Function: calls c_i64sys_clock

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/abs_01.f90:1:1
|
1 | program abs_01
| ^ Function: calls c_sp_rand_num
2 changes: 1 addition & 1 deletion tests/reference/wat-abs_03-5d62cca.json
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,6 @@
"stdout": "wat-abs_03-5d62cca.stdout",
"stdout_hash": "6875418e19ce82512d22ac8d144d43e34739fcb97daeabca7468f37a",
"stderr": "wat-abs_03-5d62cca.stderr",
"stderr_hash": "a3b3803f2f65f0cb25a63c2fd4396e3ac04e05a53aa55bfa526d2db8",
"stderr_hash": "baf67a6eeab0e9e39079ee4e43e6279dcd0b08dedbf6176c2c9fb9a9",
"returncode": 0
}
42 changes: 42 additions & 0 deletions tests/reference/wat-abs_03-5d62cca.stderr
Original file line number Diff line number Diff line change
Expand Up @@ -39,3 +39,45 @@ warning: WASM: Calls to C Intrinsic Functions are not yet supported
|
1 | program abs_03
| ^ Function: calls c_sp_rand_num

warning: Function with no body
--> tests/../integration_tests/abs_03.f90:1:1
|
1 | program abs_03
| ^ char

warning: Function with no body
--> tests/../integration_tests/abs_03.f90:1:1
|
1 | program abs_03
| ^ move_alloc

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/abs_03.f90:1:1
|
1 | program abs_03
| ^ Function: calls c_cpu_time

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/abs_03.f90:1:1
|
1 | program abs_03
| ^ Function: calls c_dp_rand_num

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/abs_03.f90:1:1
|
1 | program abs_03
| ^ Function: calls c_i32sys_clock

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/abs_03.f90:1:1
|
1 | program abs_03
| ^ Function: calls c_i64sys_clock

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/abs_03.f90:1:1
|
1 | program abs_03
| ^ Function: calls c_sp_rand_num
2 changes: 1 addition & 1 deletion tests/reference/wat-expr_08-74f99b7.json
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,6 @@
"stdout": "wat-expr_08-74f99b7.stdout",
"stdout_hash": "efb3846f7453045336ef6309bdd4165311671884504b3045c5f2e78c",
"stderr": "wat-expr_08-74f99b7.stderr",
"stderr_hash": "25356a52554e79e4544883910172de15b66ecc764c6695baa9bd5fbb",
"stderr_hash": "736727c1be0fe9da2bacde9f98c5979108d913c8d9d3f363a0d4e06c",
"returncode": 0
}
42 changes: 42 additions & 0 deletions tests/reference/wat-expr_08-74f99b7.stderr
Original file line number Diff line number Diff line change
Expand Up @@ -39,3 +39,45 @@ warning: WASM: Calls to C Intrinsic Functions are not yet supported
|
1 | program expr_08
| ^ Function: calls c_sp_rand_num

warning: Function with no body
--> tests/../integration_tests/expr_08.f90:1:1
|
1 | program expr_08
| ^ char

warning: Function with no body
--> tests/../integration_tests/expr_08.f90:1:1
|
1 | program expr_08
| ^ move_alloc

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/expr_08.f90:1:1
|
1 | program expr_08
| ^ Function: calls c_cpu_time

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/expr_08.f90:1:1
|
1 | program expr_08
| ^ Function: calls c_dp_rand_num

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/expr_08.f90:1:1
|
1 | program expr_08
| ^ Function: calls c_i32sys_clock

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/expr_08.f90:1:1
|
1 | program expr_08
| ^ Function: calls c_i64sys_clock

warning: WASM: Calls to C Intrinsic Functions are not yet supported
--> tests/../integration_tests/expr_08.f90:1:1
|
1 | program expr_08
| ^ Function: calls c_sp_rand_num
13 changes: 13 additions & 0 deletions tests/reference/wat-types_16-57fa580.json
Original file line number Diff line number Diff line change
@@ -0,0 +1,13 @@
{
"basename": "wat-types_16-57fa580",
"cmd": "lfortran --no-color --show-wat {infile}",
"infile": "tests/../integration_tests/types_16.f90",
"infile_hash": "c130af47594694449f9ae111b8985bb8567fd26e86979d127d34257b",
"outfile": null,
"outfile_hash": null,
"stdout": "wat-types_16-57fa580.stdout",
"stdout_hash": "688a51e31e2b34c7771f03a8fe0c185655e7abfe8a04fc0bfe3430d5",
"stderr": null,
"stderr_hash": null,
"returncode": 0
}
Loading

0 comments on commit 5fc1027

Please sign in to comment.