[Bug fortran/108649] allocation segmentation fault for pointer derive type and ICE for final-binding

2023-02-03 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108649

--- Comment #8 from Scott Boyce  ---
Sorry for sending a second message, my test cases have a workaround already
added to the code for the Finalization, but the code posted has issues with
ALLOCATION of derived types.

[Bug fortran/108649] allocation segmentation fault for pointer derive type and ICE for final-binding

2023-02-03 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108649

--- Comment #7 from Scott Boyce  ---
(In reply to Jerry DeLisle from comment #6)

Thanks that is excellent news about the finalization.
There also is the issue with the ALLOCATION as well.

Another set of test cases are my Batteries Included Fortran Library (its part
of this project under the folder bif_lib).

The full repository for BiF is located at

https://code.usgs.gov/fortran/bif


I was not sure if I should post that code on here as a separate issue (it has
lots of allocation issues as well with gfortran).

[Bug fortran/108651] Array Constructor with [type-spec:: fails to apply to all values, eg x = [integer(int64):: 1,2,3,4]

2023-02-03 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108651

--- Comment #3 from Scott Boyce  ---
No its not correct because the

[integer(int64):: 

in

INTEGER(INT64), dimension(2), parameter:: arr1 = [integer(int64)::
-3300711175878204139, 8258803693257250632]


is the initialization is indicating that all the numbers are int64 and not
int32.
Otherwise, what is the point of adding the type spec within the array
initialization

Second, otherwise you have to do something stupid like this to be compatible
with gfortran:

INTEGER(INT64), dimension(256), parameter:: exp_ipmf= [ &
9223372036854775806_int64,  1623796909450836942_int64, 
2664290944894287536_int64, &
7387971354164062286_int64,  6515064486552725727_int64, 
8840508362680705564_int64, &
6099647593382931854_int64,  7673130333659518959_int64, 
6220332867583442119_int64, &
5045979640552799519_int64,  4075305837223961434_int64, 
3258413672162528204_int64, &
2560664887087755460_int64,  1957224924672901793_int64, 
1429800935350586317_int64, &
 964606309710805398_int64,   551043923599587507_int64,  
180827629096887271_int64, &
-152619738120024135_int64,  -454588624410297994_int64, 
-729385126147771550_int64, &
-980551509819436091_int64, -1211029700667469343_int64,
-1423284293868552853_int64, &
   -1619396356369054015_int64, -1801135830956208679_int64,
-1970018048575620636_int64, &
   -2127348289059702419_int64, -2274257249303686369_int64,
-2411729520096647511_int64, &
   -2540626634159186189_int64, -2661705860113411427_int64,
-2775635634532452931_int64, &
   -2883008316030452685_int64, -2984350790383660344_int64,
-308019198120492_int64, &
   -3170777096303094023_int64, -3256660348483807146_int64,
-3338123885075143810_int64, &
   -3415475560473292784_int64, -3488994201966436213_int64,
-3558932970354465681_int64, &
   -3625522261068040523_int64, -3688972217741992772_int64,
-3749474917563780918_int64, &
   -3807206277531066033_int64, -3862327722496832777_int64,
-3914987649156774371_int64, &
   -3965322714631868789_int64, -4013458973776904711_int64,
-4059512885612775571_int64, &
   -4103592206186240140_int64, -4145796782586126309_int64,
-4186219260694351160_int64, &
   -4224945717447272663_int64, -4262056226866286506_int64,
-4297625367836515404_int64, &
   -4331722680528539029_int64, -4364413077437474043_int64,
-4395757214229410182_int64, &
   -4425811824915126951_int64, -4454630025296931623_int64,
-4482261588141301290_int64, &
   -4508753193105274668_int64, -4534148654077814519_int64,
-4558489126279958535_int64, &
   -4581813295192218010_int64, -4604157549138257917_int64,
-4625556137145252094_int64, &
   -4646041313519107008_int64, -4665643470413307024_int64,
-4684391259530330202_int64, &
   -4702311703971758561_int64, -4719430301145093973_int64,
-4735771117539952483_int64, &
   -4751356876102085678_int64, -4766209036859141945_int64,
-4780347871386006289_int64, &
   -4793792531638886797_int64, -4806561113635134843_int64,
-4818670716409303206_int64, &
   -4830137496634475108_int64, -4840976719260841080_int64,
-4851202804490340302_int64, &
   -4860829371376465578_int64, -4869869278311660680_int64,
-4878334660640769131_int64, &
   -4886236965617420889_int64, -4893586984900801361_int64,
-4900394884772701206_int64, &
   -490667023423961_int64, -4912422031164499511_int64,
-4917658726580128817_int64, &
   -4922388247283526639_int64, -4926618016851058129_int64,
-4930354975163349944_int64, &
   -4933605596540647482_int64, -4936375906575298263_int64,
-4938671497741363402_int64, &
   -4940497543854573923_int64, -4941858813449628344_int64,
-4942759682136115973_int64, &
   -4943204143989096034_int64, -4943195822025520534_int64,
-4942737977813217760_int64, &
   -4941833520255016417_int64, -4940485013586754412_int64,
-4938694684624350782_int64, &
   -4936464429291796994_int64, -4933795818458819764_int64,
-4930690103114058905_int64, &
   -4927148218896869823_int64, -4923170790008281939_int64,
-4918758132519204034_int64, &
   -4913910257091649047_int64, -4908626871126539190_int64,
-4902907380349533220_int64, &
   -4896750889844278395_int64, -4890156204540517421_int64,
-4883121829162564021_int64, &
   -4875645967641788341_int64, -4867726521994914537_int64,
-4859361090668117144_int64, &
   -4850546966345100146_int64, -4841281133215543008_int64,
-4831560263698491528_int64, &
   -4821380714613448338_int64, -4810738522790068329_int64,
-4799629400105478223_int64, &
   -4788048727936306618_int64, -4775991551010520594_int64,
-4763452570642106428_int64, &
   -4750426137329493684_int64, -4736906242696391928_int64,
-4722886510751374910_int64, &
   -4708360188440094804_int64, 

[Bug fortran/108649] allocation segmentation fault for pointer derive type and ICE for final-binding

2023-02-02 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108649

--- Comment #5 from Scott Boyce  ---
Comment on attachment 54395
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=54395
Source Part 1

This is a part 1 of a 3 part zip file created with 7zip

[Bug fortran/108652] New: type-bound procedure that returns integer used to allocate character on stack

2023-02-02 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108652

Bug ID: 108652
   Summary: type-bound procedure that returns integer used to
allocate character on stack
   Product: gcc
   Version: 11.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: Boyce at engineer dot com
  Target Milestone: ---

Created attachment 54400
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=54400=edit
Source code, bash file to compile, and error message

type-bound procedure that returns integer used to allocate character on stack

This is similar to 
Bug 59450 - [OOP] ICE for type-bound-procedure expression in module
procedure interface 

But the error still occurs for the following code:

---
module character_stack_error
implicit none
type char
   character(:), allocatable:: str
contains
   procedure, pass(ch):: char_sub
   procedure, pass(ch):: char_len
end type
!
contains
!
subroutine char_sub(ch, ch2)
  class(char), intent(in):: ch
  character(*), intent(out):: ch2
  character(ch%char_len()):: work   ! ch%char_len() -> internal compiler
error: Segmentation fault
  !character(char_len(ch)):: work   ! This raises: Error: MODULE-PROC
procedure at (1) is already declared as EXTERNAL-PROC procedure 
  !character(len(ch%str)):: work! while not correct, this works fine
  !character(char_len2(ch)):: work  ! this works too
  !character(char_len3(ch)):: work  ! this works too
  work = ch%str
  ch2 = work
end subroutine
!
pure function char_len(ch) result(siz)
  class(char), intent(in):: ch
  integer:: siz
  if(allocated(ch%str)) then
siz = len(ch%str)
  else
  siz = 0
  end if
end function
!
pure function char_len2(ch) result(siz)
  class(char), intent(in):: ch
  integer:: siz
  if(allocated(ch%str)) then
siz = len(ch%str)
  else
  siz = 0
  end if
end function
!
pure function char_len3(ch) result(siz)
  class(char), intent(in):: ch
  integer:: siz
  siz = char_len(ch)
end function
end module

program MAIN
  use character_stack_error
  implicit none
  type(char):: ch1
  character(5):: ch2
  ch1%str = 'abc'
  call ch1%char_sub(ch2)
end program

---

which gives the following error is given:

f951: internal compiler error: Segmentation fault
0xd41627 internal_error(char const*, ...)
???:0
0x14c28f0 gfc_find_derived_vtab(gfc_symbol*)
???:0
0x14f619e gfc_reduce_init_expr(gfc_expr*)
???:0
0x14d0afa gfc_match_char_spec(gfc_typespec*)
???:0
0x14fdc8f gfc_match_decl_type_spec(gfc_typespec*, int)
???:0
0x158cb55 gfc_parse_file()
???:0
Please submit a full bug report,
with preprocessed source if appropriate.
Please include the complete backtrace with any bug report.
See  for instructions.

---

where the error is because ch%char_len() returns an integer used to make work
in:
   character(ch%char_len()):: work


I have in the code commented different versions that will work, but the
original should also.
I tested this code with with 11.3.0 and 12.1.0 

I attached a simple code, the resulting error message, and bash file for
compiling to create the error.

[Bug fortran/108651] New: Array Constructor with [type-spec:: fails to apply to all values, eg x = [integer(int64):: 1,2,3,4]

2023-02-02 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108651

Bug ID: 108651
   Summary: Array Constructor with [type-spec:: fails to apply to
all values, eg x = [integer(int64):: 1,2,3,4]
   Product: gcc
   Version: 11.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: Boyce at engineer dot com
  Target Milestone: ---

Created attachment 54399
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=54399=edit
Source code, bash file to compile, and error message

Array Constructor with type-spec:: failes to convert all values in the array.

This is similar to 
Bug 48478 - Array-constructor with type-spec: reject valid/accept invalid

But the error still occurs for integer arrays.

for example,

   use, intrinsic:: iso_fortran_env, only: int64

   integer(int64), dimension(2), parameter:: arr1 = [integer(int64):: 1, 2]

   ! should be equivalent to

   integer(int64), dimension(2), parameter:: arr2 = [1_int64, 2_int64]

I tested this code with with 11.3.0 and 12.1.0 

I attached a simple code, the resulting error message, and bash file for
compiling to create the error.
This code has the following line:
   INTEGER(INT64), dimension(2), parameter:: arr1 = [integer(int64)::
-3300711175878204139, 8258803693257250632]
which raises:
   Error: Integer too big for its kind at (1). This check can be disabled with
the option ‘-fno-range-check’

[Bug fortran/108650] New: Error: IMPORT statement only permitted in an INTERFACE body | but it should be allowed in any contained routine to control scope

2023-02-02 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108650

Bug ID: 108650
   Summary: Error: IMPORT statement only permitted in an INTERFACE
body | but it should be allowed in any contained
routine to control scope
   Product: gcc
   Version: 11.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: Boyce at engineer dot com
  Target Milestone: ---

Created attachment 54398
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=54398=edit
Source code, bash file to compile, and error message

import should be allowed within contained subroutines to 
control access to global variables from parent routine.

From:
http://armnlib.uqam.ca/PDF/The_New_Features_of_Fortran_2018.pdf 
   The import statement can be used in a contained subprogram or 
   block construct to control host association.

It does not look like import is on the F2018 standard website:
https://gcc.gnu.org/wiki/Fortran2018Status

but it should work within contained routines:
https://www.intel.com/content/www/us/en/develop/documentation/fortran-compiler-oneapi-dev-guide-and-reference/top/language-reference/a-to-z-reference/h-to-i/import.html

I tested this code with with 11.3.0 and 12.1.0 
I attached the following source code:


module test
implicit none
!
save
integer:: a = 0
integer:: b = 0
integer:: c = 0
!
contains
!
subroutine sub1(x)
  import:: a ! raises error that import only allowed in
interface
  real, intent(inout):: x
  a = a + 1
  x = x + 1.0
end subroutine
!
subroutine sub2(x)
  real, intent(inout):: x
  x = x + 1.0
  !
  contains
  !
  function positive(x) result(ans)
import, none ! raises error that import only allowed in
interface
real, intent(in):: x
logical:: ans
ans = x>=0.0
  end function
end subroutine
end module

program MAIN
  use test
  implicit none
  real:: var
  var = 1.0
  call sub1(var)
  call sub2(var)
  ! 
end program



 $ gfortran --version
Copyright (C) 2021 Free Software Foundation, Inc.
This is free software; see the source for copying conditions.  There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.

 $ gfortran-12 main.f90 

   12 |   import:: a  ! raises error that import only alowed in
interface
  | 1
Error: IMPORT statement at (1) only permitted in an INTERFACE body
main.f90:25:15:

   25 | import, none
  |   1
Error: IMPORT statement at (1) only permitted in an INTERFACE body
main.f90:34:7:


---

 $ gfortran-12 --version
GNU Fortran (Ubuntu 12.1.0-2ubuntu1~22.04) 12.1.0
Copyright (C) 2022 Free Software Foundation, Inc.
This is free software; see the source for copying conditions.  There is NO
warranty; not even for MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.

 $ gfortran-12 main.f90 
  25 | import, none
  |   1
Error: IMPORT statement at (1) only permitted in an INTERFACE body

[Bug fortran/108649] allocation segmentation fault for pointer derive type and ICE for final-binding

2023-02-02 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108649

--- Comment #4 from Scott Boyce  ---
Created attachment 54397
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=54397=edit
Source Part 3

[Bug fortran/108649] allocation segmentation fault for pointer derive type and ICE for final-binding

2023-02-02 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108649

--- Comment #3 from Scott Boyce  ---
Created attachment 54396
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=54396=edit
Source Part 2

[Bug fortran/108649] allocation segmentation fault for pointer derive type and ICE for final-binding

2023-02-02 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108649

--- Comment #2 from Scott Boyce  ---
Created attachment 54395
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=54395=edit
Source Part 1

[Bug fortran/108649] allocation segmentation fault for pointer derive type and ICE for final-binding

2023-02-02 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108649

--- Comment #1 from Scott Boyce  ---
Missing attachment in first post

I was unable to compress the source code to 1MB.
So I will make it into a mutlipart zip over the next three posts.

If you want to download a single zip file, it is located at:

https://drive.google.com/file/d/1zFU1jL2f3azwo0eomOu1MW3kebX7v4gm/view?usp=share_link

[Bug fortran/108649] New: allocation segmentation fault for pointer derive type and ICE for final-binding

2023-02-02 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=108649

Bug ID: 108649
   Summary: allocation segmentation fault for pointer derive type
and ICE for final-binding
   Product: gcc
   Version: 11.3.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: Boyce at engineer dot com
  Target Milestone: ---

I was having a very challenging time simplifying the errors from this program
into basic test case. 
I have developed several workarounds for bugs that are currently listed here
(or I posted), but the ones in this post I could not find nor simplify.

This code base is about 30 years old and been under active development the
entire time, so it has code styles ranging from simple F77 to F2018.
Its a simulation software used for understand groundwater availability by
simulating the subsurface, climate conditions, agriculture production, and
river/stream flow.
https://www.usgs.gov/software/modflow-one-water-hydrologic-flow-model-mf-owhm

Unfortunately, this code is too long to post here, so I attached it instead.

Its source is hosted at: 
https://code.usgs.gov/modflow/mf-owhm
which is a gitlab webserver.

Note that the code attached here contains my gfortran workarounds to avoid the
deallocation ICE (first issue discussed below), while the code online does not.

I tested this code with with 
GNU Fortran (Ubuntu 11.3.0-1ubuntu1~22.04) 11.3.0
and
GNU Fortran (Ubuntu 12.1.0-2ubuntu1~22.04) 12.1.0
on LUbuntu 22.04

and on windows with
GNU Fortran (Rev10, Built by MSYS2 project) 12.2.0

There are two issues: 
DEALLOCATE(x)

where x is a derive type with a FINAL (final-binding) subroutine. 

It seems to have the most problems for derive types with complex final
subroutines (usually that call derive type components that have final
subroutines).
For example, in the file wel8.f90, the following code would fail:
  deallocate(gwfweldat(igrid)%welfeed)
  welfeed=>null()

  where in a module are the global variables

  type(line_feed), pointer,save:: welfeed

  and the other is a larger derived data type that has the same record.

  type gwfweltype
!
integer,pointer:: iout
!
type(line_feed), pointer:: welfeed
!
...
end type

How I was able to get the code to compile was:

  welfeed=>gwfweldat(igrid)%welfeed
  gwfweldat(igrid)%welfeed=>null()
  deallocate(welfeed)
  welfeed=>null()


The second issue is that a debug compilation (-O0 -g -w -fbacktrace
-fcheck=all)   raises runtime memory errors that should not happen:
SIGSEGV: Segmentation fault - invalid memory reference
This typically occurs where a global variable pointer is allocated.

The attached zip file has minimum code base and a makefile configured to build
the program with gfortran.

The folder structure is:
  bin  - compiled binary location
  examples - runtime examples for validation
  lib  - any intermediate library files (not used in current setup)
  obj  - object (.o), module (.mod), and submodule (.smod) files are here
  src  - source code

The makefile has instructions in the comment header. 
In short, there are a set of variables set at the start, and based on their
answer setup the makefile.

Here are the important parts:

You can set
F90 := gfortran

to the compiler version you want, such as
F90 := gfortran-12

If set the following is set to YES
STATIC := NO
will add to the compiler directives:
-static -static-libgfortran -static-libgcc  -static-libstdc++

This must remain as YES, as the code is dependent on it.
DBLE := YES

If you want to change any of the compiler flags, they are specified in:
F90FlagsGCC

simply typing "make" should build the code.

Its current setup runs on all the source files:

gfortran -O0 -g -w -fbacktrace -fdefault-double-8 -ffree-line-length-2048
-fmax-errors=10 -ffpe-trap=zero,overflow,underflow -finit-real=nan -fcheck=all
-fdefault-real-8 -J./obj/debug_gfortran   -c  .f90  -o
obj/debug_gfortran/.o


if you want it to run all its test examples, there are a set of bash scripts
located on:
https://code.usgs.gov/modflow/mf-owhm/
in the examples/bash_example_run directory.
(https://code.usgs.gov/modflow/mf-owhm/-/tree/main/examples/bash_example_run)

1_RunValidation.sh will run all the examples and has a set of additional
arguments that can be set.
In particular,
1_RunValidation.sh  debug
will indicate that it should run the debug version (mf-owhm-debug rather than
mf-owhm).


In the attachment I added run_breaking_example0.sh, run_breaking_example1.sh,
and run_breaking_example2.sh
which calls mf-owhm-debug.nix with one of the example problems.

For example, if I run (on 11.3.0) run_breaking_example0.sh the following error
is encountered:
---
Program received signal SIGSEGV: Segmentation fault - invalid 

[Bug fortran/96255] [F2018] Implement optional type spec for index in DO CONCURRENT

2023-02-02 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=96255

Scott Boyce  changed:

   What|Removed |Added

 CC||Boyce at engineer dot com

--- Comment #10 from Scott Boyce  ---
Just wanted to see if there was any change on this. I just was about to post
the same issue (and found this one) for compiling with 11.3.0 and 12.1.0 on
Ubuntu.

I used this feature all the time for routines that don't have any available
integers and it seems silly to create an extra int at the top of a routine just
for a loop index.

Its also nice for keeping the variable isolated from the other parts of a
routine, when its only purpose is to serve as a loop index.

[Bug fortran/99609] Pure Function that has a Variable with Value Attribute that is modified

2021-03-17 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=99609

--- Comment #3 from Scott Boyce  ---
Yeah that is the same bug request. Though it is for version 11, any chance of
back-porting to version 9 and 10?

[Bug fortran/99609] New: Pure Function that has a Variable with Value Attribute that is modified

2021-03-15 Thread Boyce at engineer dot com via Gcc-bugs
https://gcc.gnu.org/bugzilla/show_bug.cgi?id=99609

Bug ID: 99609
   Summary: Pure Function that has a Variable with Value Attribute
that is modified
   Product: gcc
   Version: 10.0
Status: UNCONFIRMED
  Severity: normal
  Priority: P3
 Component: fortran
  Assignee: unassigned at gcc dot gnu.org
  Reporter: Boyce at engineer dot com
  Target Milestone: ---

Created attachment 50392
  --> https://gcc.gnu.org/bugzilla/attachment.cgi?id=50392=edit
Module that replicates the error

This is a problem I found in all versions of gfortran.

The issue is with the value attribute for a pure function raises an error if
the variable is changed. gfortran assumes that the variable has an intent(in),
but with the value attribute the variable is a copy so the original is not
changed.

For example, the following module raises an error for func1, but not func2.
Functionally the two functions are equivalent, but one explicitly declares the
copy of a.

The attachment contains the same code as the following, but with a PROGRAM/END
PROGRAM driver.

MODULE ex_func
  contains
  !
  ! Does not recognize that value makes a copy of "a"
  !
  pure function func1(a) result(x)
integer, value :: a
integer :: x
!
a = a*a
!
x = a
!
  end function
  !
  pure function func2(a) result(x)
integer, intent(in) :: a
integer :: x
integer :: tmp
!
tmp = a
tmp = tmp*tmp
!
x = tmp
!
  end function
END MODULE