Skip to content

Commit 175d66c

Browse files
kaadambryanpkc
authored andcommitted
Fix the dllimport code generation for opaque type
Added test cases to verify the 'dllimport' usage in LLVM IR. Fixes: #1407
1 parent 762e596 commit 175d66c

File tree

3 files changed

+71
-4
lines changed

3 files changed

+71
-4
lines changed
Lines changed: 24 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,24 @@
1+
! Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
2+
! See https://llvm.org/LICENSE.txt for license information.
3+
! SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
4+
!
5+
! https://github.com/flang-compiler/flang/issues/320
6+
! https://github.com/flang-compiler/flang/issues/1407
7+
!
8+
! The dllimport_test.f90 relies on 'dllimport_test.f90_mod.f90' external module
9+
! to test the presence of 'dllimport' storage class in LLVM IR
10+
! for external module and opaque type.
11+
!
12+
! REQUIRES: system-windows
13+
!
14+
! RUN: %flang -S -emit-llvm -S -emit-llvm %s_mod.f90 %s
15+
! RUN: cat dllimport_test.ll | FileCheck %s
16+
! CHECK: %structdllimport_module__t_type__td_ = type opaque
17+
! CHECK: @_dllimport_module_10_ = external dllimport global
18+
! CHECK: @dllimport_module__t_type__td_ = external dllimport global
19+
program h_main
20+
use dllimport_module
21+
implicit none
22+
23+
call foobar(array)
24+
end program
Lines changed: 33 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,33 @@
1+
!
2+
! Part of the LLVM Project, under the Apache License v2.0 with LLVM Exceptions.
3+
! See https://llvm.org/LICENSE.txt for license information.
4+
! SPDX-License-Identifier: Apache-2.0 WITH LLVM-exception
5+
!
6+
! This file is compiled with other test dllimport_test.f90.
7+
! The dllimport_test.f90 relies on 'dllimport_test.f90_mod.f90' external module
8+
! to test the presence of 'dllimport' storage class in LLVM IR
9+
! for external module and opaque type.
10+
!
11+
! REQUIRES: system-windows
12+
! RUN: true
13+
14+
module dllimport_module
15+
implicit none
16+
17+
type t_type
18+
private
19+
integer :: a, b
20+
end type
21+
22+
type(t_type), parameter :: array(2) = (/t_type(1, 1), t_type(1, 0)/)
23+
24+
interface foobar
25+
module procedure test
26+
end interface
27+
28+
contains
29+
subroutine test(a)
30+
type(t_type), dimension(:) :: a
31+
return
32+
end subroutine
33+
end module

tools/flang2/flang2exe/llassem.cpp

Lines changed: 14 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1202,8 +1202,13 @@ assemble_end(void)
12021202
for (gblsym = ag_global; gblsym; gblsym = AG_SYMLK(gblsym)) {
12031203
if (AG_TYPEDESC(gblsym) && !AG_DEFD(gblsym)) {
12041204
fprintf(ASMFIL, "%%%s = type opaque\n", AG_TYPENAME(gblsym));
1205-
fprintf(ASMFIL, "@%s = external global %%%s\n", AG_NAME(gblsym),
1206-
AG_TYPENAME(gblsym));
1205+
if (strstr(cpu_llvm_module->target_triple, "windows-msvc") != NULL) {
1206+
fprintf(ASMFIL, "@%s = external dllimport global %%%s\n", AG_NAME(gblsym),
1207+
AG_TYPENAME(gblsym));
1208+
} else {
1209+
fprintf(ASMFIL, "@%s = external global %%%s\n", AG_NAME(gblsym),
1210+
AG_TYPENAME(gblsym));
1211+
}
12071212
}
12081213
}
12091214
for (gblsym = ag_typedef; gblsym; gblsym = AG_SYMLK(gblsym)) {
@@ -1212,8 +1217,13 @@ assemble_end(void)
12121217
AG_TYPENAME(gblsym));
12131218
else if (AG_TYPEDESC(gblsym) && !AG_DEFD(gblsym)) {
12141219
fprintf(ASMFIL, "%%%s = type opaque\n", AG_TYPENAME(gblsym));
1215-
fprintf(ASMFIL, "@%s = external global %%%s\n", AG_NAME(gblsym),
1216-
AG_TYPENAME(gblsym));
1220+
if (strstr(cpu_llvm_module->target_triple, "windows-msvc") != NULL) {
1221+
fprintf(ASMFIL, "@%s = external dllimport global %%%s\n", AG_NAME(gblsym),
1222+
AG_TYPENAME(gblsym));
1223+
} else {
1224+
fprintf(ASMFIL, "@%s = external global %%%s\n", AG_NAME(gblsym),
1225+
AG_TYPENAME(gblsym));
1226+
}
12171227
}
12181228
}
12191229
for (gblsym = ag_other; gblsym; gblsym = AG_SYMLK(gblsym)) {

0 commit comments

Comments
 (0)