[Bug fortran/105170] New: Invalid finalization in intrinsic assignment

2022-04-05 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=105170

Bug ID: 105170
   Summary: Invalid finalization in intrinsic assignment
   Product: gcc
   Version: 11.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: baradi09 at gmail dot com
  Target Milestone: ---

Created attachment 52754
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=52754&action=edit
Minimal working example demonstrating the bug

I have a derived type (TWrapper), which has a component with defined
assignment. The containing derived type itself has no defined assignment. Upon
an assignment between two TWrapper instances, a copy of the RHS seems to get
finalized.

The attached MWE demonstrates the problem.

Expected output (as delivered by current Intel and NAG compilers):

RefCounter_final, id:0
TRefCounter_init: id:42
-> Assignment wrapper2 = wrapper
TRefCounter_final, id:0
TRefCounter_final, id:0
TRefCounter_assign: this%id, other%id: 0 42

GFortran output:

TRefCounter_final, id:0
TRefCounter_init: id:42
-> Assignment wrapper2 = wrapper
TRefCounter_final, id:42
TRefCounter_assign: this%id, other%id: 0 42

One finalization seems to be missing. Additionally, the finalized instance
seems to be a copy of the RHS. (A copy, because after the finalization, the RHS
still seems to have kept its id-value...)

[Bug fortran/106507] New: Invalid structure constructor for extending derive type

2022-08-02 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106507

Bug ID: 106507
   Summary: Invalid structure constructor for extending derive
type
   Product: gcc
   Version: 12.1.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: baradi09 at gmail dot com
  Target Milestone: ---

The following snippet triggers a compilation error

test.f90:17:25:

   17 | inst = type2("test", 1)
  | 1
Error: Too many components in structure constructor at (1)

when compiled with

gfortran -c test.f90

although being standard compliant. The problem seems to be the deferred length
character component. If the component is changed to fixed length (but still has
the allocatable attribute), the compiler happily compiles it.

--> test.f90 <--
module mod2
  implicit none

  type :: type1
character(:), allocatable :: name
  end type type1

  type, extends(type1) :: type2
integer :: data
  end type

contains

  subroutine mysub()

type(type2) :: inst
inst = type2("test", 1)

  end subroutine mysub

end module mod2

[Bug fortran/107362] New: Segfault for recursive class

2022-10-23 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=107362

Bug ID: 107362
   Summary: Segfault for recursive class
   Product: gcc
   Version: 12.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: baradi09 at gmail dot com
  Target Milestone: ---

When trying to build Fortuno (https://github.com/aradi/fortuno), our new
Fortran unit testing system, I encounter a segfault with GFortran. The problem
can be reduced to the following MWE:

[details: failureinfo.f90]
module fortuno_failureinfo
  implicit none

  type :: failure_info
class(failure_info), allocatable :: previous
  end type failure_info

end module fortuno_failureinfo
[/details]

> gfortran -freport-bug -c failureinfo.f90 
gfortran: internal compiler error: Segmentation fault signal terminated program
f951
Please submit a full bug report, with preprocessed source.
See 
for instructions.

Apparently, the problem is the "class(failure_info)" field within the derived
type. Turning it into "type(failure_info)" allows compilation.

I use GNU Fortran (conda-forge gcc 12.2.0-18) 12.2.0 on x86_64/Linux.

Thanks a lot for having a look at it in advance!

[Bug fortran/104036] New: Derived type assigment to allocatable with dynamic type

2022-01-14 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=104036

Bug ID: 104036
   Summary: Derived type assigment to allocatable with dynamic
type
   Product: gcc
   Version: 11.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: baradi09 at gmail dot com
  Target Milestone: ---

Created attachment 52196
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=52196&action=edit
Demonstration code

Dear developers,

the behaviour of the GNU compiler is probably not standard conforming, when
assigning a derived type without user defined assignment, which contains a
derived type component with user defined assignment, to an allocatable variable
with dynamic type.

Some discussion about the topic can be found here:

https://fortran-lang.discourse.group/t/intrinsic-assigment-of-derived-types-containing-components-with-user-defined-assignment/2595

I have also attached the demonstration program, where I would expect the user
defined assignment be triggered when line 41 is executed, which does not
happen. (On line 39 it does, as expected.)

Best regards,

Bálint

[Bug fortran/103418] New: random_number() does not accept pointer, intent(in) array argument

2021-11-24 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103418

Bug ID: 103418
   Summary: random_number() does not accept pointer, intent(in)
array argument
   Product: gcc
   Version: 10.1.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: baradi09 at gmail dot com
  Target Milestone: ---

The following module is, at least according to the discussion on
fortran-lang.discourse
(https://fortran-lang.discourse.group/t/meaning-of-the-intent-for-pointer-dummy-arguments/2328/11)
is standard complying, but gfortran stops with an error message when compiling
it. Someone in that topic also posted a gcc-patch, which may fix the issue.

Code:

module m
contains
   subroutine s1(a)
  real, pointer, intent(in) :: a
  call s2(a )   !<-- Ok with gfortran
  call random_number(a) !<-- but not this
   end subroutine
   subroutine s2(x)
  real, intent(out) :: x
  call random_number(x)
   end subroutine
end module

Error message:

bug3.f90:6:25:

6 |   call random_number(a) !<-- but not this
  | 1
Error: ‘harvest’ argument of ‘random_number’ intrinsic at (1) cannot be
INTENT(IN)

[Bug fortran/103434] New: Pointer subobject does not show to correct memory location

2021-11-25 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103434

Bug ID: 103434
   Summary: Pointer subobject does not show to correct memory
location
   Product: gcc
   Version: 10.1.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: baradi09 at gmail dot com
  Target Milestone: ---

Based on the discussion on FD
(https://fortran-lang.discourse.group/t/is-the-section-of-a-pointer-to-an-array-a-valid-pointer/2331),
I'd assume, that the following code is standard conforming. However, the result
with gfortran seems to be incorrect.

*** Code:

module test
  implicit none

  type :: pointer_wrapper
real, pointer :: ptr(:) => null()
  end type pointer_wrapper

contains

  subroutine store_pointer(wrapper, ptr)
type(pointer_wrapper), intent(out) :: wrapper
real, pointer, intent(in) :: ptr(:)
wrapper%ptr => ptr
  end subroutine store_pointer


  subroutine use_pointer(wrapper)
type(pointer_wrapper), intent(inout) :: wrapper
wrapper%ptr(:) = wrapper%ptr + 1.0
  end subroutine use_pointer

end module test


program testprog
  use test
  implicit none

  real, allocatable, target :: data(:,:)
  real, pointer :: ptr(:,:)

  type(pointer_wrapper) :: wrapper
  integer :: ii

  allocate(data(4, 2))
  ptr => data(:,:)
  data(:,:) = 0.0
  do ii = 1, size(data, dim=2)
print *, "#", ii
print *, "BEFORE ", ii, maxval(ptr(:,ii))
call store_pointer(wrapper, ptr(:,ii))
print *, "BETWEEN", ii, maxval(ptr(:,ii))
call use_pointer(wrapper)
print *, "AFTER  ", ii, maxval(ptr(:,ii))
  end do

end program testprog

*** Output:

 #   1
 BEFORE1   0.
 BETWEEN   1   0.
 AFTER 1   1.
 #   2
 BEFORE2   1.
 BETWEEN   2   1.
 AFTER 2   1.

*** Expected output:

 #   1
 BEFORE1   0.
 BETWEEN   1   0.
 AFTER 1   1.
 #   2
 BEFORE2   0.
 BETWEEN   2   0.
 AFTER 2   1.

It seems, as if store_pointer would point to a memory location larger as it
should be, so that also data outside of the actual stride is modified. Intel
and NAG deliver the expected output.

[Bug fortran/107362] Internal compiler error for recursive class

2022-10-31 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=107362

--- Comment #3 from Bálint Aradi  ---
> I'm getting the same issue on a recursive tree structure, I will post my
> testcase here instead of opening a new bug. 

I am not sure, whether the two bugs are identical. If I understand correctly,
you can compile the code and obtain the segfault during execution. In the case
demonstrated above, the compiler itself generates an ICE during the
compilation, so no executable code is generated at all. (I have changed the
title of the bug report to pronounce that more.)

[Bug fortran/116679] New: Memory leak when creating derived type instance with allocatable component within array expression

2024-09-11 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=116679

Bug ID: 116679
   Summary: Memory leak when creating derived type instance with
allocatable component within array expression
   Product: gcc
   Version: 14.1.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: baradi09 at gmail dot com
  Target Milestone: ---

Issue:

GIVEN a derived type with an allocatable component
WHEN  an instance of this type is created within an array expression
THEN  the allocatable component is not deallocated when the instance goes out
of scope

Minimal working example:

program testprog
  implicit none

  type :: wrapper
integer, allocatable :: val
  end type wrapper

  block
type(wrapper) :: items(1)
items = [wrapper(1)]
  end block

end program testprog

Compiling:

gfortran -Og -g3 -fsanitize=address memoryleak.f90

Obtained result:

When the executable finishes, AddressSanitizer reports unallocated memory

./a.out   

=
==104059==ERROR: LeakSanitizer: detected memory leaks

Direct leak of 4 byte(s) in 1 object(s) allocated from:
#0 0x7f012e4b1cbc in malloc
../../../../libsanitizer/asan/asan_malloc_linux.cpp:69
#1 0x55717df5c307 in testprog
/home/aradi/ramdisk/BUILD/fortuno/memoryleak.f90:10
#2 0x7f012e11d14a in __libc_start_main_alias_1 (/lib64/libc.so.6+0x2a14a)
(BuildId: 77c77fee058b19c6f001cf2cb0371ce3b8341211)
#3 0x55717df5c14d in _start
(/media/aradi/ramdisk/BUILD/fortuno/a.out+0x114d)

SUMMARY: AddressSanitizer: 4 byte(s) leaked in 1 allocation(s).

Expected result:

Memory should be properly deallocated at the end of the "block" construct.


Note: This is an extracted minimal working example of the issue reported for
the Fortuno unit testing system
(https://github.com/fortuno-repos/fortuno/issues/22)

[Bug fortran/116706] New: Unable to fill allocatable array component of a derived type instance in a pointer array within a derived type

2024-09-13 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=116706

Bug ID: 116706
   Summary: Unable to fill allocatable array component of a
derived type instance in a pointer array within a
derived type
   Product: gcc
   Version: 14.1.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: baradi09 at gmail dot com
  Target Milestone: ---

* Issue:

GIVEN
a derived type containing a pointer array of a derived type with an allocatable
array component

WHEN
the pointer array is allocated and an array is assigned to the allocatable
array component of the first element

THEN
the program segfaults (or gives a dubious error message when compiled in debug
mode)


* Minimal working example

program testprog
  implicit none

  type :: data_node
integer, allocatable :: data(:)
  end type data_node

  type :: data_list
type(data_node), pointer :: nodes(:) => null()
  end type data_list

  type(data_list) :: datalist
  allocate(datalist%nodes(3))
  datalist%nodes(1)%data = [1, 2, 3]

end program testprog


* Compiling

gfortran -Og -g3 -fbounds-check ~/ramdisk/bugdemo.f90


* Observed behavior

> ./a.out
At line 14 of file [...]/bugdemo.f90
Fortran runtime error: Array bound mismatch for dimension 1 of array 'datalist'
(1/3)

Error termination. Backtrace:
#0  0x55e596dc0344 in testprog
at [...]/bugdemo.f90:14
#1  0x55e596dc0371 in main
at [...]/bugdemo.f90:16


* Expected behavior

Code should run through without problems


* Notes

- when the allocatable component data is a scalar, and not an array (and the
assignment is changed accordingly), the program runs as expected

- when the array "nodes(:)" is turned into an allocatable array, the program
runs as expected.

- when an array similar to "nodes(:)" is created outside of a derived type as a
stand-alone array, the program runs as expected.

[Bug fortran/109358] New: Wrong formatting with T-descriptor during stream output

2023-03-31 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109358

Bug ID: 109358
   Summary: Wrong formatting with T-descriptor during stream
output
   Product: gcc
   Version: 12.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: baradi09 at gmail dot com
  Target Milestone: ---

This is a very minor bug, but probably easy to fix. It seems, that the T data
edit descriptor handling is non-standard conforming when using formatted stream
I/O:

Given the following MWE:

program tabformat
  implicit none

  integer :: fd

  open(newunit=fd, file="test.stream.txt", access="stream", form="formatted")  
  write(fd, "(a)") "1234567890123"
  write(fd, "(a, t10, a)") "1234", "0123"  ! A-descriptor, file positioning
allowed 
  write(fd, "(i4, t10, i4.4)") 1234, 0123  !  I-descriptor, file positioning
not allowed   
  close(fd)

end program tabformat

The resulting file contains

1234567890123
1234 0123   # 9 spaces between blocks
1234 0123   # 9 spaces between blocks

Apparently, a file positioning takes place during the execution of the write
statement. 

However, if I understand 13.7.1 §1 correctly, file positioning may only happen
with the A-descriptor (and it is optional even there). So the standard
conforming output would be either (if file positioning happens after the
A-descriptor)

1234567890123
1234 0123# 9 spaces
1234 0123# 5 spaces

or (if no file positioning happens after the A-descriptor)

1234567890123
1234 0123# 5 spaces
1234 0123# 5 spaces

I personally would prefer latter, and it would be also equivalent to the
behavior of the Intel and NAG compilers.

[Bug fortran/109358] Wrong formatting with T-descriptor during stream output

2023-04-16 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109358

--- Comment #5 from Bálint Aradi  ---
I also think that by allowing for explicit EORs caused by achar(10) characters
in the variable being written or by explicit new_line() calls, the standard
made the formatted stream output probably more complicated then it is worth of.
And the fact that apparently none of the widely used compilers handle those
cases correctly, also indicates over-complication.

However, I still think, that formatted stream output has its justification, as
it allows you to become independent from record length limits, which are set up
when a file is opened and which can not be adapted afterwards. We had been hit
by run-time errors a few times, when the character variable being written
turned out to be too big. (Of course, one could do unformatted stream output
instead, but then one always have to think about adding the newlines manually
at the end of each line...)

[Bug fortran/67740] Wrong association status of allocatable character pointer in derived types

2023-10-26 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=67740

--- Comment #14 from Bálint Aradi  ---
Thanks a lot for fixing it!

[Bug fortran/105170] Invalid finalization in intrinsic assignment

2023-12-08 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=105170

--- Comment #2 from Bálint Aradi  ---
Thanks, with 13.2.0, it seems to behave correctly.

[Bug fortran/113118] New: ICE on assignment of derived types with allocatable class component

2023-12-22 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113118

Bug ID: 113118
   Summary: ICE on assignment of derived types with allocatable
class component
   Product: gcc
   Version: 13.2.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: baradi09 at gmail dot com
  Target Milestone: ---

I get an internal compiler error with the following demo code. As far, as I can
judge, the code is standard conforming.

module bugdemo
  implicit none

  type :: base_type
character(:), allocatable :: name
  end type base_type

  type :: base_type_item
class(base_type), allocatable :: item
  end type base_type_item

  type, extends(base_type) :: derived_type
integer :: val = 0
  end type derived_type

contains

  function derived_type_as_item(name, val) result(item)
character(*), intent(in) :: name
integer, intent(in) :: val
type(base_type_item), allocatable :: item

item = base_type_item(derived_type(name=name, val=val))

  end function derived_type_as_item

end module bugdemo

Compiling it with

gfortran -c bugdemo.f90

results in

   23 | item = base_type_item(derived_type(name=name, val=val)) 
  |   1 
internal compiler error: in fold_convert_loc, at fold-const.cc:2627 
0x69f6fa fold_convert_loc(unsigned int, tree_node*, tree_node*) 
../.././gcc/fold-const.cc:2627  
0x824e17 gfc_trans_subcomponent_assign 
../.././gcc/fortran/trans-expr.cc:9027 
0x825a22 gfc_trans_structure_assign(tree_node*, gfc_expr*, bool, bool) 
../.././gcc/fortran/trans-expr.cc:9265
0x826808 gfc_conv_structure(gfc_se*, gfc_expr*, int)   
../.././gcc/fortran/trans-expr.cc:9332 
0x81d6fc gfc_conv_expr(gfc_se*, gfc_expr*) 
../.././gcc/fortran/trans-expr.cc:9500 
0x829ab5 gfc_trans_assignment_1
../.././gcc/fortran/trans-expr.cc:11877
0x7e0f77 trans_code
../.././gcc/fortran/trans.cc:2229  
0x80f1e9 gfc_generate_function_code(gfc_namespace*)
../.././gcc/fortran/trans-decl.cc:7715 
0x7e5641 gfc_generate_module_code(gfc_namespace*)  
../.././gcc/fortran/trans.cc:2649  
0x785d35 translate_all_program_units   
../.././gcc/fortran/parse.cc:6707  
0x785d35 gfc_parse_file()  
../.././gcc/fortran/parse.cc:7026  
0x7dde4f gfc_be_parse_file 
../.././gcc/fortran/f95-lang.cc:229
Please submit a full bug report, with preprocessed source. 
Please include the complete backtrace with any bug report. 
See  for instructions.

[Bug fortran/113118] ICE on assignment of derived types with allocatable class component

2023-12-22 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113118

--- Comment #1 from Bálint Aradi  ---
Just a further note, if I leave away dummy argument names, I do not get an ICE
any more, but the program still does not compile:


   24 | item = base_type_item(derived_type(name, val))
  | 1
Error: Too many components in structure constructor at (1)

Apparently, the fields of the base type are not considered, when the structure
constructor of the derived type is called.

[Bug fortran/113118] ICE on assignment of derived types with allocatable class component

2023-12-22 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113118

--- Comment #2 from Bálint Aradi  ---
Last note: replacing the problematic line with

allocate(item)
item%item = derived_type(name=name, val=val)

seems to compile (but I did not check, whether the compiled code behaves
correctly).

[Bug fortran/116679] Memory leak when creating derived type instance with allocatable component within array expression

2024-09-20 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=116679

--- Comment #1 from Bálint Aradi  ---
# An even simpler, but probably strongly related scenario also causes a
leakage:

program bugdemo_app
  use bugdemo
  implicit none

  type :: wrapper
integer, allocatable :: item
  end type wrapper

  type(wrapper), pointer :: array(:)
  allocate(array(1))
  array(1)%item = 42
  deallocate(array)

end program bugdemo_app


# Compiling

gfortran -Og -g3 -fsanitize=address ~/ramdisk/bugdemo.f90

# Obtained result

> ./a.out
Direct leak of 4 byte(s) in 1 object(s) allocated from:
#0 0x7f069cab1cbc in malloc
../../../../libsanitizer/asan/asan_malloc_linux.cpp:69
#1 0x560390af559d in bugdemo_app [...]/bugdemo.f90:18

SUMMARY: AddressSanitizer: 4 byte(s) leaked in 1 allocation(s).

[Bug fortran/107362] Internal compiler error for recursive class

2024-11-16 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=107362

--- Comment #5 from Bálint Aradi  ---
Checked with gfortran 14.1, the example still gives a segfault.

[Bug fortran/106507] Invalid structure constructor for extending derive type

2024-11-16 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=106507

--- Comment #1 from Bálint Aradi  ---
Tested with gfortran 14.1, the issue is still present, the example still can
not be compiled and triggers the same (false) error message.

[Bug fortran/68778] [F03] Missing default initialization of finalized derived types type(C_PTR) component in subroutines

2024-11-16 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=68778

Bálint Aradi  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #8 from Bálint Aradi  ---
Just tested, it works with GFortran 14.1, so we can close the issue.

[Bug fortran/104036] Derived type assigment to allocatable with dynamic type

2024-11-16 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=104036

Bálint Aradi  changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution|--- |FIXED

--- Comment #2 from Bálint Aradi  ---
OK, this seems to deliver consistent results in both cases with gfortran 14.1,
closing issue.

[Bug fortran/113118] ICE on assignment of derived types with allocatable class component

2024-11-16 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=113118

Bálint Aradi  changed:

   What|Removed |Added

 Status|UNCONFIRMED |RESOLVED
 Resolution|--- |FIXED

--- Comment #4 from Bálint Aradi  ---
I can compile the code with GFortran 14.1 without any problems, so we might
close the issue.

[Bug libfortran/114618] Format produces incorrect output when contains 1x, ok when uses " "

2024-11-16 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=114618
Bug 114618 depends on bug 109358, which changed state.

Bug 109358 Summary: Wrong formatting with T-descriptor during stream output
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109358

   What|Removed |Added

 Status|REOPENED|RESOLVED
 Resolution|--- |FIXED

[Bug fortran/78942] Incorrect error message for preprocessed source

2024-11-16 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=78942

Bálint Aradi  changed:

   What|Removed |Added

 Status|NEW |RESOLVED
 Resolution|--- |FIXED

--- Comment #3 from Bálint Aradi  ---
Checked with gfortran 14.1, results are consistent now, so closing the issue.

[Bug fortran/103434] Pointer subobject does not show to correct memory location

2024-11-16 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=103434

Bálint Aradi  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|WAITING |RESOLVED

--- Comment #2 from Bálint Aradi  ---
Seems to work with gfortran 14.1, closing.

[Bug fortran/105170] Invalid finalization in intrinsic assignment

2024-11-16 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=105170

Bálint Aradi  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|WAITING |RESOLVED

--- Comment #3 from Bálint Aradi  ---
Tested with gfortran 14.1, works as supposed.

[Bug libfortran/109358] Wrong formatting with T-descriptor during stream output

2024-11-16 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=109358

Bálint Aradi  changed:

   What|Removed |Added

 Resolution|--- |FIXED
 Status|REOPENED|RESOLVED

--- Comment #17 from Bálint Aradi  ---
Checked with gfortran 14.1, the file created is the same as with the other
compilers (and which is the standard conforming behavior IMO). Issue can be
closed.

[Bug fortran/120163] New: Can not import module containig call to pure routine via abstract interface

2025-05-07 Thread baradi09 at gmail dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=120163

Bug ID: 120163
   Summary: Can not import module containig call to pure routine
via abstract interface
   Product: gcc
   Version: 15.1.1
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: baradi09 at gmail dot com
  Target Milestone: ---

GIVEN:
* A module defines an abstract interface for a pure subroutine
(callback_interface).
* Within the same module, a routine declares a dummy argument of the type
procedure(callback_interface).
* This routine internally calls the dummy procedure argument.
* The flag -Wall is turned on during compilation

WHEN:
* This module is imported into another module using a USE statement.

THEN:
* Compilation of the importing module fails with cryptic error message.

MINIMAL WORKING EXAMPLE:

File: test.f90
module mod1
  implicit none

  abstract interface
pure subroutine callback_interface(a)
  real, intent(in) :: a
end subroutine callback_interface
  end interface

contains

  subroutine caller(callback)
procedure(callback_interface) :: callback
real :: a
call callback(a)
  end subroutine caller

end module mod1


module mod2
  use mod1
end module mod2


Compiling the code with

gfortran -c -Wall test.f90

EXPECTED BEHAVIOR

Code compiles without any warnings.

OBSERVED BEHAVIOR

Compilation aborts due to error message:

test.f90:22:6:

   22 |   use mod1
  |  1
Error: Argument ‘_formal_0’ of pure subroutine ‘callback’ at (1) must have its
INTENT specified or have the VALUE attribute
test.f90:22:6:

   22 |   use mod1
  |  1
Error: Argument ‘_formal_0’ of pure subroutine ‘callback’ at (1) must have its
INTENT specified or have the VALUE attribute