- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
The following code produces a segmentation fault when compiled and run with ifx 2024.0.1, but works with gfortran 9,10,11,12,13,14, nagfor 7 and the ifort 2024. A segmentation fault is produced both with a single file, and with separate files, but the segmentation violation happens at different places. Unfortunately, I was not able to reduce this case further. The program defines a string literal, which is then parsed with a parser and lexer written in Fortran and then converted into a syntax tree. This structure seems not to be correctly built with ifx (compared to ifort). The expected literal output from the created syntax tree structure is:
4
Invalid token type code requested by the parser
4
Invalid token type code requested by the parser
Cut expression:
+ SEQUENCE <lexpr> = <lsinglet>
+ SEQUENCE <lsinglet> = <lterm>
| + SEQUENCE <lterm> = <all_fun>
| | + SEQUENCE <all_fun> = all <lexpr> <pargs1>
| | | + KEYWORD all = [keyword] all
| | | + SEQUENCE <lexpr> = <lsinglet>
| | | | + SEQUENCE <lsinglet> = <lterm>
| | | | | + SEQUENCE <lterm> = <compared_expr>
| | | | | | + SEQUENCE <compared_expr> = <expr> <comparison>
| | | | | | | + SEQUENCE <expr> = <term>
| | | | | | | | + SEQUENCE <term> = <factor>
| | | | | | | | | + SEQUENCE <factor> = <variable>
| | | | | | | | | | + IDENTIFIER <variable> = Pt
| | | | | | | + SEQUENCE <comparison> = '>' <expr>
| | | | | | | | + KEYWORD '>' = [keyword] >
| | | | | | | | + SEQUENCE <expr> = <term>
| | | | | | | | | + SEQUENCE <term> = <factor>
| | | | | | | | | | + SEQUENCE <factor> = <integer_value>
| | | | | | | | | | | + SEQUENCE <integer_value> = <integer_literal>
| | | | | | | | | | | | + INTEGER <integer_literal> = 100
| | | + ARGUMENTS <pargs1> = <pexpr>
| | | | + SEQUENCE <pexpr> = <pterm>
| | | | | + SEQUENCE <pterm> = <pexpr_src>
| | | | | | + SEQUENCE <pexpr_src> = <unspecified_prt>
| | | | | | | + SEQUENCE <unspecified_prt> = <cexpr>
| | | | | | | | + SEQUENCE <cexpr> = <variable>
| | | | | | | | | + IDENTIFIER <variable> = s
Link Copied
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi John,
thanks for the code example. Just to make sure: this is an alternative iso_varying string implementation and an implementation of yours for a tree. But it is not directly connected to my code example, right?
Cheers,
JRR (Juergen)
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@Juergen_R_R, thank you for using ifx and reporting this issue. I see it, too, with the latest internal compiler version. I filed a bug report, CMPLRLLVM-55024. I'll let you know its progress to a fix.
I spent some time to reduce the lines of code, too, with no success.
You know that you can mix/match mod files and obj files between ifx and ifort. Maybe that will help you make progress.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi Barbara, thx for filing a report. Here is a much smaller reproducer. The seg fault happens only if the two files are compiled separately:
ifx -c file_1.f90
ifx file_1.o file_2.f90
I addded a reproducer tar ball, please forward it to the development team.
Here is also the code explicitly, which is now less than 300 lines in total.
module iso_varying_string
implicit none
integer, parameter, private :: GET_BUFFER_LEN = 1
type, public :: varying_string
private
character(LEN=1), dimension(:), allocatable :: chars
end type varying_string
end module iso_varying_string
module syntax_rules
use iso_varying_string, string_t => varying_string
implicit none
private
public :: syntax_t
type :: rule_p
private
type(syntax_rule_t), pointer :: p => null ()
end type rule_p
public :: syntax_rule_t
type :: syntax_rule_t
private
integer :: type = 0
logical :: used = .false.
type(string_t) :: keyword
type(string_t) :: separator
type(string_t), dimension(2) :: delimiter
type(rule_p), dimension(:), allocatable :: child
character(1) :: modifier = ""
logical :: opt = .false., rep = .false.
end type syntax_rule_t
type :: syntax_t
private
type(syntax_rule_t), dimension(:), allocatable :: rule
end type syntax_t
end module syntax_rules
module parser
use iso_varying_string, string_t => varying_string
use syntax_rules
implicit none
private
public :: parse_node_t
public :: parse_node_write_rec
public :: parse_node_write
public :: parse_tree_t
type :: token_t
private
integer :: type = 0
logical, pointer :: lval => null ()
integer, pointer :: ival => null ()
real, pointer :: rval => null ()
type(string_t), pointer :: sval => null ()
type(string_t), pointer :: kval => null ()
type(string_t), dimension(:), pointer :: quote => null ()
end type token_t
type :: parse_node_t
private
type(syntax_rule_t), pointer :: rule => null ()
type(token_t) :: token
integer :: n_sub = 0
type(parse_node_t), pointer :: sub_first => null ()
type(parse_node_t), pointer :: sub_last => null ()
type(parse_node_t), pointer :: next => null ()
contains
procedure :: write => parse_node_write_rec
end type parse_node_t
type :: parse_tree_t
private
type(parse_node_t), pointer :: root_node => null ()
contains
procedure :: get_root_ptr => parse_tree_get_root_ptr
end type parse_tree_t
contains
recursive subroutine parse_node_write_rec (node, unit, short, depth)
class(parse_node_t), intent(in), target :: node
integer, intent(in), optional :: unit
logical, intent(in), optional :: short
integer, intent(in), optional :: depth
integer :: u, d
type(parse_node_t), pointer :: current
u = unit
d = 0; if (present (depth)) d = depth
call parse_node_write (node, u, short=short)
current => node%sub_first
do while (associated (current))
call parse_node_write_rec (current, unit, short, d+1)
current => current%next
end do
end subroutine parse_node_write_rec
subroutine parse_node_write (node, unit, short)
class(parse_node_t), intent(in) :: node
integer, intent(in), optional :: unit
logical, intent(in), optional :: short
integer :: u
type(parse_node_t), pointer :: current
u = unit
write (u, "('+ ')", advance = "no")
print *, "inside parse_node_write"
if (associated (node%rule)) then
print *, "rule associated. seg fault happens"
else
write (u, *) "[empty]"
end if
end subroutine parse_node_write
function parse_tree_get_root_ptr (parse_tree) result (node)
class(parse_tree_t), intent(in) :: parse_tree
type(parse_node_t), pointer :: node
node => parse_tree%root_node
end function parse_tree_get_root_ptr
end module parser
module expr_base
implicit none
private
public :: expr_factory_t
type, abstract :: expr_t
end type expr_t
type, abstract :: expr_factory_t
contains
procedure(expr_factory_write), deferred :: write
end type expr_factory_t
abstract interface
subroutine expr_factory_write (expr_factory, unit)
import
class(expr_factory_t), intent(in) :: expr_factory
integer, intent(in), optional :: unit
end subroutine expr_factory_write
end interface
end module expr_base
module eval_trees
use, intrinsic :: iso_c_binding !NODEP!
use syntax_rules
use parser
use expr_base
implicit none
private
public :: eval_tree_factory_t
type, extends (expr_factory_t) :: eval_tree_factory_t
private
type(parse_node_t), pointer :: pn => null ()
contains
procedure :: write => eval_tree_factory_write
procedure :: init => eval_tree_factory_init
end type eval_tree_factory_t
contains
subroutine eval_tree_factory_write (expr_factory, unit)
class(eval_tree_factory_t), intent(in) :: expr_factory
integer, intent(in), optional :: unit
if (associated (expr_factory%pn)) then
call parse_node_write_rec (expr_factory%pn, unit)
end if
end subroutine eval_tree_factory_write
subroutine eval_tree_factory_init (expr_factory, pn)
class(eval_tree_factory_t), intent(out) :: expr_factory
type(parse_node_t), intent(in), pointer :: pn
expr_factory%pn => pn
end subroutine eval_tree_factory_init
end module eval_trees
module process
use expr_base
implicit none
private
public :: process_t
type :: process_t
class(expr_factory_t), allocatable :: ef_cuts
contains
procedure :: write => process_write
procedure :: set_cuts => process_set_cuts
end type process_t
contains
subroutine process_write (process, u)
class(process_t), intent(in) :: process
integer, intent(in) :: u
if (allocated (process%ef_cuts)) then
write (u, "(3x,A)") "Cut expression:"
call process%ef_cuts%write (u)
end if
end subroutine process_write
subroutine process_set_cuts (process, ef_cuts)
class(process_t), intent(inout) :: process
class(expr_factory_t), intent(in) :: ef_cuts
allocate (process%ef_cuts, source = ef_cuts)
end subroutine process_set_cuts
end module process
!!!!!! The following needs to be in a separate file!
module expr_tests_uti
use parser
use eval_trees
use process, only: process_t
implicit none
private
public :: processes_5
contains
subroutine processes_5 (u)
integer, intent(in) :: u
type(parse_tree_t) :: parse_tree
type(eval_tree_factory_t) :: expr_factory
type(process_t), allocatable, target :: process
allocate (process)
call expr_factory%init (parse_tree%get_root_ptr ())
call process%set_cuts (expr_factory)
call process%write (u)
end subroutine processes_5
end module expr_tests_uti
program main_ut
use expr_tests_uti, only: processes_5
implicit none
call processes_5 (6)
end program main_ut
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
@Juergen_R_R, I compiled and ran your code with a preview build of ifx 2024.2.0. No segmentation fault. Output is the same as ifort.
Look for this release in mid-2024.
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page