Anything wrong with this code?

Is there anything wrong with the following code?

module bst_base_mod

   ! Binary Search Tree Module

   implicit none

   public

   integer, parameter :: bst_success   = 0
   integer, parameter :: bst_duplicate = 1
   integer, parameter :: bst_error     = 2

   ! the following data type is intended to be extended with the problem-specific data.

   type, abstract :: bst_base_node_type
      class(bst_base_node_type), allocatable :: left
      class(bst_base_node_type), allocatable :: right
   contains
      procedure (compare_interface), deferred :: compare
      procedure (print_interface),   deferred :: print
   end type bst_base_node_type

   abstract interface
   
      ! these subroutine stubs should be overridden with the appropriate extended node type.

      integer function compare_interface( node1, node2 )
         ! output: -1 means node1 < node2
         !          0 means node1 == node2
         !         +1 means node1 > node2
         !          n means node1 and node2 could not be compared.
         import :: bst_base_node_type
         class(bst_base_node_type), intent(in) :: node1, node2
      end function compare_interface

      subroutine print_interface ( node, level )
         import :: bst_base_node_type
         class(bst_base_node_type), intent(in) :: node
         integer, intent(in)                   :: level
      end subroutine print_interface

   end interface

end module bst_base_mod

When I compile with gfortran, I get the following error.

gfortran: internal compiler error: Segmentation fault: 11 signal terminated program f951
Please submit a full bug report,
with preprocessed source if appropriate.
See <https://github.com/Homebrew/homebrew-core/issues> for instructions.

This is with:

$ gfortran --version
GNU Fortran (Homebrew GCC 11.3.0_2) 11.3.0
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.

Before reporting it, I would like to know if the code itself is alright.

There is that bst_base_node_type which is recursive. It is an abstract type rather than a normal type, and the components are defined with class() rather than type(). I think all that is alright, but I’m not certain.

I could reproduce the internal compiler error on x64-linux for all versions of gfortran from
7 to (including) 12.

ifort 2021.04 and aocc-3.1.0 could compile the code.

(I have just checked whether it was possible to compile the code, not its execution).

2 Likes

I stripped away all of the subroutines and executable statements before I posted. Thanks for checking the other versions of gfortran and also ifort.

1 Like

I just noticed, that while the is an internal compiler error in gfortran,
still a *.mod file is written.

However, I do not know, whether this file is useable.

Further observations:

ifort additionaly produces an *.o file, while flan does not.

While there where no warnings for ifort, flang gave the following warnings:

F90-S-0155-Derived type component must have the POINTER attribute - left (bst_base_mod.f90: 16)
F90-S-0155-Derived type component must have the POINTER attribute - right (bst_base_mod.f90: 17)

The mod files produced by ifort and flang where also consideralbs larger than the one by gfortran (factor 2-4), but I do not know whether this is important.

For whatever it’s worth, I find the code conforms to the current Fortran standard.

The important aspect is you will.need a processor conformant to Fortran 2008 because the feature to allow recursive types with ALLOCATABLE components (also polymorphic) was introduced in that standard revision.

1 Like

To @RonShepard or anyone coming afresh to Fortran who wants to test-drive the Fortran syntax toward working with such recursive types and/or looking to run some unit tests or attach something with support requests with processor implementation teams:

Here is a trivial test case to try.

Click to see code
! Starting with the `bst_base_mod` module in the original post
module i_m
   use bst_base_mod
   type, extends(bst_base_node_type) :: i_t
      integer :: n = 0
   contains
      procedure :: compare => i_compare
      procedure :: print => i_print
   end type
contains
   integer function i_compare( node1, node2 )
      class(i_t), intent(in) :: node1
      class(bst_base_node_type), intent(in) :: node2
      i_compare = 2
      select type ( node2 )
         type is ( i_t )
            if ( node1%n < node2%n ) then
               i_compare = -1
            else if ( node1%n > node2%n ) then
               i_compare = 1
            else
               i_compare = 0
            end if
         class default
            ! error handling elided 
      end select
   end function
   subroutine i_print ( node, level ) !<-- recursive per Fortran 2018
      class(i_t), intent(in) :: node
      integer, intent(in)    :: level
      integer :: this_level
      if ( level == 1 ) then
         if ( allocated(node%left) ) then
            select type ( ln => node%left )
               type is ( i_t )
                  print *, ln%n
               class default
                  ! error handling elided
            end select
         end if 
         if ( allocated(node%right) ) then
            select type ( rn => node%right )
               type is ( i_t )
                  print *, rn%n
               class default
                  ! error handling elided
            end select
         end if
         return
       end if
       this_level = level - 1
      if ( allocated(node%left) ) then
         call node%left%print( this_level )
      end if 
      if ( allocated(node%right) ) then
         call node%right%print( this_level )
      end if
   end subroutine i_print
end module
! A unit test for `i_t`   
   use i_m, only : i_t
   type(i_t) :: foo
   allocate( foo%left, source=i_t( n=-13 ) )
   allocate( foo%right, source=i_t( n=13 ) )
   allocate( foo%left%left, source=i_t( n=-42 ) )
   allocate( foo%left%right, source=i_t( n=42 ) )

   associate ( ln => foo%left%left, rn => foo%left%right )
      print *, "compare(ln, rn): ", ln%compare( rn ), "; expected is -1" 
   end associate

   print *, "level 2 nodes: expected are -42 and 42"
   call foo%print( level=2 )

end
  • Build and execution using Intel oneAPI IFORT compiler:

C:\temp>ifort /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.6.0 Build 20220226_000000
Copyright (C) 1985-2022 Intel Corporation. All rights reserved.

Microsoft (R) Incremental Linker Version 14.30.30706.0
Copyright (C) Microsoft Corporation. All rights reserved.

-out:p.exe
-subsystem:console
p.obj

C:\temp>p.exe
compare(ln, rn): -1 ; expected is -1
level 2 nodes: expected are -42 and 42
-42
42

1 Like

This looks similar to the rest of my code which I eliminated in my post in order to keep the post short. One difference is the way that you test that the two nodes are the same extended type (as shown above). I use the same_type_as() intrinsic, but I still need the select_type() block, so it is still a run time test.

Are there any proposals to fortran that would simplify this process? What I would really like as a programmer is to be able to require the types of the two arguments to be the same in the dummy argument declaration statements, and for the compiler to catch the cases where they mismatch at compile time rather than run time. I would like to somehow eliminate the select_type() blocks when referencing these arguments too, but that is just a minor inconvenience in this case since I only need to test for one extended type. The compile-time rather than run-time test for matching arguments would be a big improvement to the language though.

As pointed out by FortranFan, this code requires one of the recent fortran standards, f2008 or later I think. Does flang have an option to allow allocatable components here?

I do not know. However, flang (in this case the aocc Version of flang) rather tends to lack behind ifort and gfortran with respect to its support for new Fortran standards.

1 Like

From the comments here, it looks like the code itself is alright, so I went ahead and reported it to gcc bugzilla.

I have added the observation, that the problem occurs at least in the gfortran versions between 7 and 12 as a comment to your bugzilla report.

1 Like

Not in the current standard. See this thread re: some extension in the next revision, Fortran 2023.

Ultimately, Fortran coders will realize the situations that require the use of SELECT TYPE in codes often imply the need of generics more than OO. That also may mean the development of the application(s) in question, especially in the scientific domains with the need to describe a lot of physical phenomena and natural behavior, do require a lot of thought and analyses and even premeditation that needs to be followed by careful design in pseudocode prior to commencement of the programming.

Toward the case in the original post, a consideration can be the use of some sorting of hashing toward the comparer function and having a deferred procedure only for the subclasses to dispatch suitable hashes that the abstract “base” class utilizes: this can help simplify the subclassed implementations and avoid the SELECT TYPE.

   ..
   type, abstract :: bst_base_node_type
      class(bst_base_node_type), allocatable :: left
      class(bst_base_node_type), allocatable :: right
   contains
      procedure(Ihash), deferred :: hash
      procedure(print_interface), deferred :: print
      procedure :: compare => base_node_compare
   end type bst_base_node_type

   abstract interface
      elemental function Ihash( node ) result(hash)
      ! return a hash for the instance
         import :: bst_base_node_type
         class(bst_base_node_type), intent(in) :: node
         integer(kind=K) :: hash ! where K is a suitable kind, 64-bit integer?
      end function Ihash
      ..
   ..
contains
   elemental function base_node_compare( node1, node2 ) result(r)
      class(bst_base_node_type), intent(in) :: node1, node2
      integer :: r
      r = 2
      if ( same_type_as( node1, node2 ) ) then
         associate ( lh => node1%hash(), rh => node2%hash() ) 
            if ( lh < rh ) then
               r = -1
            else if ( lh > rh ) then
               r = 1
            else
               r = 0
            end if
         end associate
      end if
   end function
   ..

Separately, note the “school of thought” currently is to not employ OO as a substitute for Generics. Eventually as Generics makes into the language, conceivably one can apply Generics on top of certain concrete class hierarchy(ies) toward certain needs. But generally the language extension appears to take the position to not support an enmeshing of the two paradigms, at least in the first revision.

What I was told years ago is that an internal compiler error should always be reported. It doesn’t matter whether the program is valid or not. In the first case it should have been compiled. In the second the error should have been pointed out by the compiler, either at compile time or at run time depending on what made the program invalid.

2 Likes

I do use hashes in my actual application. I store the hash values along with the data, so they only need to be computed once. The comparison starts with the hash values, which makes the < and > comparisons quick. When the hashes compare equal, then I must go into the data itself to determine <, >, or =. This step depends on the data, which in my case includes integer arrays whose length vary from case to case, but are all the same within a case. I never need to compare data objects with arrays of different length. The use of the hash values in the comparisons also helps to keep the binary search tree balanced. Otherwise, I would need to balance the tree fairly frequently because of the way the nodes are added to the tree.

As for the OO aspects of this application, what I really would like to do is to simply declare the nodes to be the extended type, not as a class of that type (or of the base type). Then the compiler could check at compile time that my actual arguments match, and within the comparison function itself, I would not need select_type or same_type_as() or anything like that for the dummy arguments. I think this should be a good match for OO programming. Much of the effort associated with my extended type can be implemented using just the base type information. It is only a few things such as the comparison function and the print function that depends on the data within the extended type. But the current fortran does not let me do any of that in a simple way. It requires these class() declarations, and select_type() and all of that stuff that seems to me to just get in the way of what I really want to do.

 

With the two class…allocatable statements commented out, the code compiles without errors.

This is BASH 5.1- DISPLAY on :0

Sun 21 Aug 2022 06:35:33 AEST
(06:35 ian@ian-HP-Stream-Laptop-11-y0XX ~) > cat model.f
       module bst_base_mod

       ! Binary Search Tree Module

       implicit none

      public

       integer, parameter :: bst_success   = 0
       integer, parameter :: bst_duplicate = 1
       integer, parameter :: bst_error     = 2

      ! the following data type is intended to be extended with the problem-specific data.

        type, abstract :: bst_base_node_type
       !  class(bst_base_node_type), allocatable :: left
      !  class(bst_base_node_type), allocatable :: right
        contains
        procedure (compare_interface), deferred :: compare
        procedure (print_interface),   deferred :: print
        end type bst_base_node_type

      abstract interface
   
  !      these subroutine stubs should be overridden with the appropriate extended node type.

         integer function compare_interface( node1, node2 )
         ! output: -1 means node1 < node2
         !          0 means node1 == node2
         !         +1 means node1 > node2
         !          n means node1 and node2 could not be compared.
          import :: bst_base_node_type
          class(bst_base_node_type), intent(in) :: node1, node2
          end function compare_interface

        subroutine print_interface ( node, level )
        import :: bst_base_node_type
         class(bst_base_node_type), intent(in) :: node
         integer, intent(in)                   :: level
       end subroutine print_interface

        end interface

        end module bst_base_mod
 

(06:35 ian@ian-HP-Stream-Laptop-11-y0XX ~) > gfortran model.f -c
(06:35 ian@ian-HP-Stream-Laptop-11-y0XX ~) > cd sdl-tut03


Runs with and without class…allocatable statements commented out.
Sun 21 Aug 2022 07:21:17 AEST
(07:21 ian@ian-HP-Stream-Laptop-11-y0XX ~) > gfortran -v -save-temps model.f -c
Using built-in specs.
COLLECT_GCC=gfortran
OFFLOAD_TARGET_NAMES=nvptx-none:amdgcn-amdhsa
OFFLOAD_TARGET_DEFAULT=1
Target: x86_64-linux-gnu
Configured with: …/src/configure -v --with-pkgversion=‘Ubuntu 11.2.0-19ubuntu1’ --with-bugurl=file:///usr/share/doc/gcc-11/README.Bugs --enable-languages=c,ada,c++,go,brig,d,fortran,objc,obj-c++,m2 --prefix=/usr --with-gcc-major-version-only --program-suffix=-11 --program-prefix=x86_64-linux-gnu- --enable-shared --enable-linker-build-id --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix --libdir=/usr/lib --enable-nls --enable-bootstrap --enable-clocale=gnu --enable-libstdcxx-debug --enable-libstdcxx-time=yes --with-default-libstdcxx-abi=new --enable-gnu-unique-object --disable-vtable-verify --enable-plugin --enable-default-pie --with-system-zlib --enable-libphobos-checking=release --with-target-system-zlib=auto --enable-objc-gc=auto --enable-multiarch --disable-werror --enable-cet --with-arch-32=i686 --with-abi=m64 --with-multilib-list=m32,m64,mx32 --enable-multilib --with-tune=generic --enable-offload-targets=nvptx-none=/build/gcc-11-gBFGDP/gcc-11-11.2.0/debian/tmp-nvptx/usr,amdgcn-amdhsa=/build/gcc-11-gBFGDP/gcc-11-11.2.0/debian/tmp-gcn/usr --without-cuda-driver --enable-checking=release --build=x86_64-linux-gnu --host=x86_64-linux-gnu --target=x86_64-linux-gnu --with-build-config=bootstrap-lto-lean --enable-link-serialization=2
Thread model: posix
Supported LTO compression algorithms: zlib zstd
gcc version 11.2.0 (Ubuntu 11.2.0-19ubuntu1)
COLLECT_GCC_OPTIONS=‘-v’ ‘-save-temps’ ‘-c’ ‘-mtune=generic’ ‘-march=x86-64’
/usr/lib/gcc/x86_64-linux-gnu/11/f951 model.f -ffixed-form -quiet -dumpbase model.f -dumpbase-ext .f -mtune=generic -march=x86-64 -version -fintrinsic-modules-path /usr/lib/gcc/x86_64-linux-gnu/11/finclude -fpre-include=/usr/include/finclude/math-vector-fortran.h -o model.s
GNU Fortran (Ubuntu 11.2.0-19ubuntu1) version 11.2.0 (x86_64-linux-gnu)
compiled by GNU C version 11.2.0, GMP version 6.2.1, MPFR version 4.1.0, MPC version 1.2.1, isl version isl-0.24-GMP

GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
GNU Fortran2008 (Ubuntu 11.2.0-19ubuntu1) version 11.2.0 (x86_64-linux-gnu)
compiled by GNU C version 11.2.0, GMP version 6.2.1, MPFR version 4.1.0, MPC version 1.2.1, isl version isl-0.24-GMP

GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
COLLECT_GCC_OPTIONS=‘-v’ ‘-save-temps’ ‘-c’ ‘-mtune=generic’ ‘-march=x86-64’
as -v --64 -o model.o model.s
GNU assembler version 2.38 (x86_64-linux-gnu) using BFD version (GNU Binutils for Ubuntu) 2.38
COMPILER_PATH=/usr/lib/gcc/x86_64-linux-gnu/11/:/usr/lib/gcc/x86_64-linux-gnu/11/:/usr/lib/gcc/x86_64-linux-gnu/:/usr/lib/gcc/x86_64-linux-gnu/11/:/usr/lib/gcc/x86_64-linux-gnu/
LIBRARY_PATH=/usr/lib/gcc/x86_64-linux-gnu/11/:/usr/lib/gcc/x86_64-linux-gnu/11/…/…/…/x86_64-linux-gnu/:/usr/lib/gcc/x86_64-linux-gnu/11/…/…/…/…/lib/:/lib/x86_64-linux-gnu/:/lib/…/lib/:/usr/lib/x86_64-linux-gnu/:/usr/lib/…/lib/:/usr/lib/gcc/x86_64-linux-gnu/11/…/…/…/:/lib/:/usr/lib/
COLLECT_GCC_OPTIONS=‘-v’ ‘-save-temps’ ‘-c’ ‘-mtune=generic’ ‘-march=x86-64’
(07:22 ian@ian-HP-Stream-Laptop-11-y0XX ~) > cat model.f
module bst_base_mod

   ! Binary Search Tree Module

   implicit none

  public

   integer, parameter :: bst_success   = 0
   integer, parameter :: bst_duplicate = 1
   integer, parameter :: bst_error     = 2

  ! the following data type is intended to be extended with the problem-specific data.

    type, abstract :: bst_base_node_type
    class(bst_base_node_type), allocatable :: left
    class(bst_base_node_type), allocatable :: right
    contains
    procedure (compare_interface), deferred :: compare
    procedure (print_interface),   deferred :: print
    end type bst_base_node_type

  abstract interface

! these subroutine stubs should be overridden with the appropriate extended node type.

     integer function compare_interface( node1, node2 )
     ! output: -1 means node1 < node2
     !          0 means node1 == node2
     !         +1 means node1 > node2
     !          n means node1 and node2 could not be compared.
      import :: bst_base_node_type
      class(bst_base_node_type), intent(in) :: node1, node2
      end function compare_interface

    subroutine print_interface ( node, level )
    import :: bst_base_node_type
     class(bst_base_node_type), intent(in) :: node
     integer, intent(in)                   :: level
   end subroutine print_interface

    end interface

    end module bst_base_mod

(07:33 ian@ian-HP-Stream-Laptop-11-y0XX ~) > cat model2.f
module bst_base_mod

   ! Binary Search Tree Module

   implicit none

  public

   integer, parameter :: bst_success   = 0
   integer, parameter :: bst_duplicate = 1
   integer, parameter :: bst_error     = 2

  ! the following data type is intended to be extended with the problem-specific data.

    type, abstract :: bst_base_node_type

! class(bst_base_node_type), allocatable :: left
! class(bst_base_node_type), allocatable :: right
contains
procedure (compare_interface), deferred :: compare
procedure (print_interface), deferred :: print
end type bst_base_node_type

  abstract interface

! these subroutine stubs should be overridden with the appropriate extended node type.

     integer function compare_interface( node1, node2 )
     ! output: -1 means node1 < node2
     !          0 means node1 == node2
     !         +1 means node1 > node2
     !          n means node1 and node2 could not be compared.
      import :: bst_base_node_type
      class(bst_base_node_type), intent(in) :: node1, node2
      end function compare_interface

    subroutine print_interface ( node, level )
    import :: bst_base_node_type
     class(bst_base_node_type), intent(in) :: node
     integer, intent(in)                   :: level
   end subroutine print_interface

    end interface

    end module bst_base_mod

(07:34 ian@ian-HP-Stream-Laptop-11-y0XX ~) > gfortran -v -save-temps model.f -c
Using built-in specs.
COLLECT_GCC=gfortran
OFFLOAD_TARGET_NAMES=nvptx-none:amdgcn-amdhsa
OFFLOAD_TARGET_DEFAULT=1
Target: x86_64-linux-gnu
Configured with: …/src/configure -v --with-pkgversion=‘Ubuntu 11.2.0-19ubuntu1’ --with-bugurl=file:///usr/share/doc/gcc-11/README.Bugs --enable-languages=c,ada,c++,go,brig,d,fortran,objc,obj-c++,m2 --prefix=/usr --with-gcc-major-version-only --program-suffix=-11 --program-prefix=x86_64-linux-gnu- --enable-shared --enable-linker-build-id --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix --libdir=/usr/lib --enable-nls --enable-bootstrap --enable-clocale=gnu --enable-libstdcxx-debug --enable-libstdcxx-time=yes --with-default-libstdcxx-abi=new --enable-gnu-unique-object --disable-vtable-verify --enable-plugin --enable-default-pie --with-system-zlib --enable-libphobos-checking=release --with-target-system-zlib=auto --enable-objc-gc=auto --enable-multiarch --disable-werror --enable-cet --with-arch-32=i686 --with-abi=m64 --with-multilib-list=m32,m64,mx32 --enable-multilib --with-tune=generic --enable-offload-targets=nvptx-none=/build/gcc-11-gBFGDP/gcc-11-11.2.0/debian/tmp-nvptx/usr,amdgcn-amdhsa=/build/gcc-11-gBFGDP/gcc-11-11.2.0/debian/tmp-gcn/usr --without-cuda-driver --enable-checking=release --build=x86_64-linux-gnu --host=x86_64-linux-gnu --target=x86_64-linux-gnu --with-build-config=bootstrap-lto-lean --enable-link-serialization=2
Thread model: posix
Supported LTO compression algorithms: zlib zstd
gcc version 11.2.0 (Ubuntu 11.2.0-19ubuntu1)
COLLECT_GCC_OPTIONS=‘-v’ ‘-save-temps’ ‘-c’ ‘-mtune=generic’ ‘-march=x86-64’
/usr/lib/gcc/x86_64-linux-gnu/11/f951 model.f -ffixed-form -quiet -dumpbase model.f -dumpbase-ext .f -mtune=generic -march=x86-64 -version -fintrinsic-modules-path /usr/lib/gcc/x86_64-linux-gnu/11/finclude -fpre-include=/usr/include/finclude/math-vector-fortran.h -o model.s
GNU Fortran (Ubuntu 11.2.0-19ubuntu1) version 11.2.0 (x86_64-linux-gnu)
compiled by GNU C version 11.2.0, GMP version 6.2.1, MPFR version 4.1.0, MPC version 1.2.1, isl version isl-0.24-GMP

GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
GNU Fortran2008 (Ubuntu 11.2.0-19ubuntu1) version 11.2.0 (x86_64-linux-gnu)
compiled by GNU C version 11.2.0, GMP version 6.2.1, MPFR version 4.1.0, MPC version 1.2.1, isl version isl-0.24-GMP

GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
gfortran: internal compiler error: Segmentation fault signal terminated program f951
Please submit a full bug report,
with preprocessed source if appropriate.
See <file:///usr/share/doc/gcc-11/README.Bugs> for instructions.
(07:36 ian@ian-HP-Stream-Laptop-11-y0XX ~) > gfortran -v -save-temps model2.f -c
Using built-in specs.
COLLECT_GCC=gfortran
OFFLOAD_TARGET_NAMES=nvptx-none:amdgcn-amdhsa
OFFLOAD_TARGET_DEFAULT=1
Target: x86_64-linux-gnu
Configured with: …/src/configure -v --with-pkgversion=‘Ubuntu 11.2.0-19ubuntu1’ --with-bugurl=file:///usr/share/doc/gcc-11/README.Bugs --enable-languages=c,ada,c++,go,brig,d,fortran,objc,obj-c++,m2 --prefix=/usr --with-gcc-major-version-only --program-suffix=-11 --program-prefix=x86_64-linux-gnu- --enable-shared --enable-linker-build-id --libexecdir=/usr/lib --without-included-gettext --enable-threads=posix --libdir=/usr/lib --enable-nls --enable-bootstrap --enable-clocale=gnu --enable-libstdcxx-debug --enable-libstdcxx-time=yes --with-default-libstdcxx-abi=new --enable-gnu-unique-object --disable-vtable-verify --enable-plugin --enable-default-pie --with-system-zlib --enable-libphobos-checking=release --with-target-system-zlib=auto --enable-objc-gc=auto --enable-multiarch --disable-werror --enable-cet --with-arch-32=i686 --with-abi=m64 --with-multilib-list=m32,m64,mx32 --enable-multilib --with-tune=generic --enable-offload-targets=nvptx-none=/build/gcc-11-gBFGDP/gcc-11-11.2.0/debian/tmp-nvptx/usr,amdgcn-amdhsa=/build/gcc-11-gBFGDP/gcc-11-11.2.0/debian/tmp-gcn/usr --without-cuda-driver --enable-checking=release --build=x86_64-linux-gnu --host=x86_64-linux-gnu --target=x86_64-linux-gnu --with-build-config=bootstrap-lto-lean --enable-link-serialization=2
Thread model: posix
Supported LTO compression algorithms: zlib zstd
gcc version 11.2.0 (Ubuntu 11.2.0-19ubuntu1)
COLLECT_GCC_OPTIONS=‘-v’ ‘-save-temps’ ‘-c’ ‘-mtune=generic’ ‘-march=x86-64’
/usr/lib/gcc/x86_64-linux-gnu/11/f951 model2.f -ffixed-form -quiet -dumpbase model2.f -dumpbase-ext .f -mtune=generic -march=x86-64 -version -fintrinsic-modules-path /usr/lib/gcc/x86_64-linux-gnu/11/finclude -fpre-include=/usr/include/finclude/math-vector-fortran.h -o model2.s
GNU Fortran (Ubuntu 11.2.0-19ubuntu1) version 11.2.0 (x86_64-linux-gnu)
compiled by GNU C version 11.2.0, GMP version 6.2.1, MPFR version 4.1.0, MPC version 1.2.1, isl version isl-0.24-GMP

GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
GNU Fortran2008 (Ubuntu 11.2.0-19ubuntu1) version 11.2.0 (x86_64-linux-gnu)
compiled by GNU C version 11.2.0, GMP version 6.2.1, MPFR version 4.1.0, MPC version 1.2.1, isl version isl-0.24-GMP

GGC heuristics: --param ggc-min-expand=100 --param ggc-min-heapsize=131072
COLLECT_GCC_OPTIONS=‘-v’ ‘-save-temps’ ‘-c’ ‘-mtune=generic’ ‘-march=x86-64’
as -v --64 -o model2.o model2.s
GNU assembler version 2.38 (x86_64-linux-gnu) using BFD version (GNU Binutils for Ubuntu) 2.38
COMPILER_PATH=/usr/lib/gcc/x86_64-linux-gnu/11/:/usr/lib/gcc/x86_64-linux-gnu/11/:/usr/lib/gcc/x86_64-linux-gnu/:/usr/lib/gcc/x86_64-linux-gnu/11/:/usr/lib/gcc/x86_64-linux-gnu/
LIBRARY_PATH=/usr/lib/gcc/x86_64-linux-gnu/11/:/usr/lib/gcc/x86_64-linux-gnu/11/…/…/…/x86_64-linux-gnu/:/usr/lib/gcc/x86_64-linux-gnu/11/…/…/…/…/lib/:/lib/x86_64-linux-gnu/:/lib/…/lib/:/usr/lib/x86_64-linux-gnu/:/usr/lib/…/lib/:/usr/lib/gcc/x86_64-linux-gnu/11/…/…/…/:/lib/:/usr/lib/
COLLECT_GCC_OPTIONS=‘-v’ ‘-save-temps’ ‘-c’ ‘-mtune=generic’ ‘-march=x86-64’
(07:36 ian@ian-HP-Stream-Laptop-11-y0XX ~) > gfortran -v -save-temps model.f -c

type or paste code here