Struggling to get VS Code linter to recognize f2008 standard

My Environment:

I’m developing a personal project in a WSL Ubunutu distribution. I’m using VS Code in WSL:Ubuntu and I’ve installed fortls within a virtual environment in my project’s root folder. My compiler is gfortran.

My settings.json for vscode looks like the following.

{

// Fortran language server settings

"fortran.fortls.path": "utils/bin/fortls",

"fortran.fortls.extraArgs": \["-std=f2008"\],

"fortran.fortls.directories": \[

    "./\*\*"

\],

// Modern Fortran Linter settings

"fortran.linter.compiler": "gfortran",

"fortran.linter.extraArgs": \["-std=f2008"\],

"fortran.linter.includePaths": \[

    "./\*\*"

\]

}

I’m trying to use the fortran 2008 standard to get access to features like SUBMODULES (for code tidiness) and allowing the TARGET attribute for members declared in a TYPE block.

I’ve consulted multiple online sources, tried multiple formats of the “-std"=f2008” argument, and changed the file extensions to .f08, but no matter what the syntax I mentioned does not get recognized. I tested my gfortran and it can compile f2008 so I’m pretty sure the issue is with the linter.

Has anyone encountered this issue before?

1 Like

Can you give an example of this? Your description sounds suspicious.

You can stick to the .f90 extension for free-form source files —There’s at least one compiler vendor that doesn’t support having a new, different extension every time a Fortran standard is published.

(And there’s also some inconsistency in that, e.g., some compiler vendors support the .f95, .f03 and .f08 extensions, but not .f18 or .f23, and still support the F2018 and F2023 standards.)

Yeah that’s fair let me see if I can describe the issue I was facing. I’m trying to make a basic particle-in-cell program to practice Fortran and this error came up when I was making my electric field class.

My approach is to have a base Field3 class which handles the basic array allocations and other data management ops. Then the electric field just extends that class by having members that point to the

MODULE fields_mod

Implicit none
TYPE :: Field3
    !! The linter says “Attribute at (1) is not allowed in a TYPE definition”
    real, allocatable, target :: dataX(:,:,:)
END TYPE Field3

TYPE, EXTENDS(Field3) :: ElectricField
    real, pointer :: Ex(:,:,:)

END TYPE ElectricField

CONTAINS

SUBROUTINE alloc_ef()
    !! Point the pointer member to the underlying data
    this%Ex => this%dataX

END SUBROUTINE alloc_ef

END MODULE fields_mod

I know not all my syntax is correct here I’m just trying to illustrate the main components. My idea was for the ElectricField to just wrap around data’s and give it a more intuitive name like “Ex.” Then it will have its own EF-specific member subroutines of course. I read online that the f2008 standard does allow the TARGET attribute in the declaration above.

Obviously the quick solution to this that I took was to just make this%Ex = this%dataX rather than trying to use pointers. That worked, and then shortly after I tried to put the electric field module into its own file rather than cramming all of its code on fields_mod.f08. However even though I include fileds_mod in electric_field_mod.f08, my linter says “symbol fields3 at (1) has not been previously defined.” That’s how I learned about submodules and ended back at trying to get f2008 to work again.

I’m still new to Fortran so I’m open to criticism of my approach and learning better ones if it turns out that’s the fundamental issue. I appreciate y’all’s help.

EDIT: realized I didn’t have Ex declared as a pointer in my code snippet

That usage is wrong. Only PUBLIC, PRIVATE, ALLOCATABLE, POINTER, DIMENSION, CODIMENSION and CONTIGUOUS are allowed as attributes for data components of a derived type.

The TARGET attribute must be applied to instances of the whole derived type (using the POINTER attribute on instances of the whole derived type may also work).

Yes I see your point. I came back after stepping away and it looks like f2008 is being enforced by my linter. My SUBMODULE syntax was incorrect and works now after a quick fix. However I must have misunderstood what I read about the TARGET attribute.

I’m going to chew on this and think of alternative design patterns. Thanks for the help!

1 Like

One possible pattern may be like this…?

field_mod.f90:

module field_mod
    implicit none

    type Field3
        integer :: ndims(3), nsize
        real, allocatable :: data(:,:,:)
    contains
        procedure :: init, show
    end type

contains

subroutine init(this, ndims)
    class(Field3), target :: this
    integer, intent(in) :: ndims(3)

    this% ndims(:) = ndims(:)
    this% nsize = product( ndims )

    allocate( this% data( ndims(1), ndims(2), ndims(3) ) )
end subroutine

subroutine show(this)
    class(Field3), intent(in) :: this
    integer :: i3

    print *, "Field values:"
    do i3 = 1, this% ndims(3)
        print "(a,i0,a,*(2x,g0))", "  val(:,:,",i3,") =", this% data(:,:,i3)
    end do
end subroutine

end module

elec_field_mod.f90:

module elec_field_mod
    use field_mod, only: Field3
    implicit none

    type, extends(Field3) :: ElecField
        real, pointer, contiguous :: Ex(:,:,:)   !! Cartesian array view
        real, pointer, contiguous :: Ex_lin(:)   !! linear array view
    contains
        procedure :: init => EF_init
    end type

contains

subroutine EF_init(this, ndims)
    class(ElecField), target :: this
    integer, intent(in) :: ndims(3)

    call this% Field3% init( ndims=ndims )

    this% Ex => this% data   !! Cartesian access
    this% Ex_lin( 1 : this%nsize ) => this% data   !! linear access
end subroutine

end module

main.f90:

program main
    use elec_field_mod, only: ElecField
    implicit none
    type(ElecField), target :: ef
    integer :: i, n

    n = 2
    call ef% init( ndims=[n,n,n] )

    print *, "shape( ef% Ex )     = ", shape( ef% Ex )
    print *, "shape( ef% Ex_lin ) = ", shape( ef% Ex_lin )

    ef% Ex_lin(:) = [(i, i = 1, n**3)]

    call ef% show()
end program

build.sh:

comp="gfortran -fcheck=all -Wall -Wextra"
# comp="flang -pedantic"

echo "comp = ${comp}"

${comp} field_mod.f90 elec_field_mod.f90 main.f90
# ${comp} field_mod.f90 elec_field_compo_mod.f90 main.f90

Results (on macOS 15.6):

!! gfortran-15.1
 shape( ef% Ex )     =            2           2           2
 shape( ef% Ex_lin ) =            8
 Field values:
  val(:,:,1) =  1.00000000  2.00000000  3.00000000  4.00000000
  val(:,:,2) =  5.00000000  6.00000000  7.00000000  8.00000000

!! flang-21.1
 shape( ef% Ex )     =  2 2 2
 shape( ef% Ex_lin ) =  8
 Field values:
  val(:,:,1) =  1.  2.  3.  4.
  val(:,:,2) =  5.  6.  7.  8.

Actually, I guess “composition” might be more flexible (though depending on cases…). In that case the next version might be more convenient (which gives the same result as elec_field_mod.f90).

elec_field_compo_mod.f90:

module elec_field_mod
    use field_mod, only: Field3
    implicit none

    type :: ElecField
        type(Field3) :: field
        real, pointer, contiguous :: Ex(:,:,:)   !! Cartesian array view
        real, pointer, contiguous :: Ex_lin(:)   !! linear array view
    contains
        procedure :: init, show
    end type

contains

subroutine init(this, ndims)
    class(ElecField), target :: this
    integer, intent(in) :: ndims(3)

    call this% field% init( ndims=ndims )

    this% Ex => this% field% data   !! Cartesian access
    this% Ex_lin( 1 : this% field% nsize ) => this% field% data   !! linear access
end subroutine

subroutine show(this)
    class(ElecField), intent(in) :: this
    call this% field% show()  !! forwarding
end subroutine

end module

Indeed, I hope that future Fortran will provide an “alias” like feature for defining alternative name access for type components (rather than using pointers, like above…), so as to avoid various pitfalls of pointers (eg, it may be necessary to define custom assignment). So something like…

    type :: ElecField
        type(Field3) :: field
        alias :: Ex => field% data
        !! or
        forwarding :: Ex => field% data, show => field% show
        !! etc
    end type

I think such a feature will also be convenient for gradual “refactoring” (renaming of components).

1 Like

Look at ASSOCIATE.

I have been using ASSOCIATE for almost every routine to extract type components, and it is quite redundant and lengthy. It does not provde an equivalent functionality to the right-hand side of =>, either (e.g., it drops the ALLOCATABLE attribute).

1 Like

The problem with ASSOCIATE is it can get extremely unwieldy. If you have a lot of variables you want to “alias” a shorter name to. I would have prefered a special kind of pointer or variable attribute (namely ALIAS) that just aliases a shorter name to a variable in a safe way that doesn’t impact performance. The compiler should know its just a second name for an already defined variable and can’t be reassociated or aliased to another variable like a pointer can. Something like.

real, alias :: a
integer, alias :: b

type (a_type) :: at

a => at%a_real
b => at%an_int

I’ve done similar things with pointers in the past and found the code (at least in my eyes) to be more reable than 10 lines of ASSOCIATE assignments. Unfortunately, you pay a price for using pointers in this way.

1 Like