Skip to content

Commit

Permalink
Fix the dllimport code generation for opaque type
Browse files Browse the repository at this point in the history
Added test cases to verify the 'dllimport' usage in LLVM IR.

Fixes: #1407
  • Loading branch information
kaadam committed Oct 5, 2023
1 parent 762e596 commit 37ae97a
Show file tree
Hide file tree
Showing 3 changed files with 62 additions and 4 deletions.
20 changes: 20 additions & 0 deletions test/llvm_ir_correct/dllimport_test.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,20 @@
! Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
! See https://llvm.org/LICENSE.txt for license information.
! SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
!
! https://github.com/flang-compiler/flang/issues/320
! https://github.com/flang-compiler/flang/issues/1407
!
! REQUIRES: system-windows
!
! RUN: %flang -S -emit-llvm -S -emit-llvm %s_mod.f90 %s
! RUN: cat dllimport_test.ll | FileCheck %s
! CHECK: %structdllimport_module__t_type__td_ = type opaque
! CHECK: @_dllimport_module_10_ = external dllimport global
! CHECK: @dllimport_module__t_type__td_ = external dllimport global
program h_main
use dllimport_module
implicit none

call foobar(array)
end program
28 changes: 28 additions & 0 deletions test/llvm_ir_correct/dllimport_test.f90_mod.f90
Original file line number Diff line number Diff line change
@@ -0,0 +1,28 @@
!
! Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
! See https://llvm.org/LICENSE.txt for license information.
! SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
!
! REQUIRES: system-windows
! RUN: true

module dllimport_module
implicit none

type t_type
private
integer :: a, b
end type

type(t_type), parameter :: array(2) = (/t_type(1, 1), t_type(1, 0)/)

interface foobar
module procedure test
end interface

contains
subroutine test(a)
type(t_type), dimension(:) :: a
return
end subroutine
end module
18 changes: 14 additions & 4 deletions tools/flang2/flang2exe/llassem.cpp
Original file line number Diff line number Diff line change
Expand Up @@ -1202,8 +1202,13 @@ assemble_end(void)
for (gblsym = ag_global; gblsym; gblsym = AG_SYMLK(gblsym)) {
if (AG_TYPEDESC(gblsym) && !AG_DEFD(gblsym)) {
fprintf(ASMFIL, "%%%s = type opaque\n", AG_TYPENAME(gblsym));
fprintf(ASMFIL, "@%s = external global %%%s\n", AG_NAME(gblsym),
AG_TYPENAME(gblsym));
if (strstr(cpu_llvm_module->target_triple, "windows-msvc") != NULL) {
fprintf(ASMFIL, "@%s = external dllimport global %%%s\n", AG_NAME(gblsym),
AG_TYPENAME(gblsym));
} else {
fprintf(ASMFIL, "@%s = external global %%%s\n", AG_NAME(gblsym),
AG_TYPENAME(gblsym));
}
}
}
for (gblsym = ag_typedef; gblsym; gblsym = AG_SYMLK(gblsym)) {
Expand All @@ -1212,8 +1217,13 @@ assemble_end(void)
AG_TYPENAME(gblsym));
else if (AG_TYPEDESC(gblsym) && !AG_DEFD(gblsym)) {
fprintf(ASMFIL, "%%%s = type opaque\n", AG_TYPENAME(gblsym));
fprintf(ASMFIL, "@%s = external global %%%s\n", AG_NAME(gblsym),
AG_TYPENAME(gblsym));
if (strstr(cpu_llvm_module->target_triple, "windows-msvc") != NULL) {
fprintf(ASMFIL, "@%s = external dllimport global %%%s\n", AG_NAME(gblsym),
AG_TYPENAME(gblsym));
} else {
fprintf(ASMFIL, "@%s = external global %%%s\n", AG_NAME(gblsym),
AG_TYPENAME(gblsym));
}
}
}
for (gblsym = ag_other; gblsym; gblsym = AG_SYMLK(gblsym)) {
Expand Down

0 comments on commit 37ae97a

Please sign in to comment.