Why am I getting a warning about "Variable x masks variable in parent scope"?

I have a short bit of code that is reading in a CSV file. The CSV file is very simple, just an array of floating point numbers. There is no header and each column has the same type of information, so I don’t need to do any sort of FORMAT statement for the read. I have pasted the entire code at the end of this message.

I use Visual Studio Code (vscode) as an editor/IDE. This includes using the Modern Fortran extension (version 3.2.0) provided by https://fortran-lang.org.

Here’s the problem, of sorts. With the Modern Fortran extension running, the extension gives me a warning for two of my variables (max_rows and max_cols, see the code below). Here’s what the warning looks like:

Variable “max_rows” masks variable in parent scope
Variable “max_cols” masks variable in parent scope

Note: it is true that for this code example, I don’t need to pass these variables into the subroutine. However, my plans to add to this code are such that it is better to first introduce these variables a tthe program level (e.g., I will use these same variables in other subroutines).

Why am I getting this warning?

After searching the web, I haven’t found a clear explanation (particularly for a non-CS person like myself). I use an intent(in) when declaring the variables in the subroutine, which I thought would help avoid issure like this.

(I should note that the code/program works. I am just trying to understand the warning.)

If anyone has any insight or an explanation, I would appreciate it. Or just point me to a good explanation.

Thanks!

Here’s the code:

   program main
    
    ! The unkillable implicit statement.
    implicit none
    
    ! The naming scheme for variables in this program:
    !   tp  = titanpool
    !   vap = vapor
    !   cp  = heat capacity
    !   liq = liquid
    !   den = density
    
    character(len=100) ::   &
        ! File with N2 saturation vaporization values from TitanPOOL.
        tp_n2_sat_vap_file, &
        ! File with the N2 heat capacity (cp) values from TitanPOOL.
        tp_n2_sat_cp_file,  &
        ! File with the N2 saturation liquidization values from TitanPOOL.
        tp_n2_sat_liq_file, &
        ! File with the values for the density of liquid(?) N2 at saturation.
        tp_n2_sat_den_file

    ! Define the maximum size of the matrix
    integer :: max_rows
    integer :: max_cols        
    
    ! Define the matrices to store the data.
    real, dimension(1000,1000) :: tp_n2_sat_comp_vap
    real, dimension(1000,1000) :: tp_n2_sat_comp_cp
    real, dimension(1000,1000) :: tp_n2_sat_comp_liq
    real, dimension(1000,1000) :: tp_n2_sat_comp_den    
    
    ! Assign the file names
    tp_n2_sat_vap_file = "Titan_N2_saturation_comp_vap.csv"
    tp_n2_sat_cp_file = "Titan_N2_saturation_comp_Cp.csv"
    tp_n2_sat_liq_file = "Titan_N2_saturation_comp_liq.csv"
    tp_n2_sat_den_file = "Titan_N2_saturation_comp_den.csv"
    
    ! Set the value of the maximum size of the matrix.
    max_rows = 42
    max_cols = 64
       
    ! Read the input files
    call read_input_file(tp_n2_sat_vap_file, tp_n2_sat_comp_vap, &
        max_rows, max_cols)
    
    call read_inputfile(tp_n2_sat_cp_file, tp_n2_sat_comp_cp, &
         max_rows, max_cols)
        
    call read_inputfile(tp_n2_sat_liq_file, tp_n2_sat_comp_liq, &
        max_rows, max_cols)
    
    call read_inputfile(tp_n2_sat_den_file, tp_n2_sat_comp_den, &
        max_rows, max_cols)
        
    contains
    
    subroutine read_input_file(file_path, data_matrix, max_rows, max_cols)
        
        character(len=*), intent(in) :: file_path
        
        integer             :: i
        integer, intent(in) :: max_rows
        integer, intent(in) :: max_cols
                
        real, dimension(max_rows,max_cols), intent(inout) :: data_matrix

        ! Open the input file
        open(unit=10, file=file_path, status='old', action='read')
                
        ! Read the data into the matrix
        do i = 1, max_rows
            read(10, *) data_matrix(i,:)
            !write(*,*) data_matrix(i,:)
        end do
        
        ! Close the input file
        close(10)
    end subroutine read_input_file

end program main

Your code is valid Fortran (if you correct it to spell read_input_file consistently). The compiler is warning you because sometimes masking a variable is unintentional. I rarely use internal procedures because they inherit variables from the host and therefore do not create modularity. If you put the subroutine in a module, giving the code below, there are no warnings with gfortran -Wall -Wextra or ifort /check:uninit /warn:all /warn:unused /gen-interfaces /warn:interfaces. On a different topic, don’t hard code unit numbers in a procedure, since those unit numbers may already be in use. Use open(newunit=myunit, ...) to get an available unit.

module m
implicit none
    private
    public :: read_input_file
    contains
    
    subroutine read_input_file(file_path, data_matrix, max_rows, max_cols)
        
        character(len=*), intent(in) :: file_path
        
        integer             :: i
        integer, intent(in) :: max_rows
        integer, intent(in) :: max_cols
                
        real, dimension(max_rows,max_cols), intent(inout) :: data_matrix

        ! Open the input file
        open(unit=10, file=file_path, status='old', action='read')
                
        ! Read the data into the matrix
        do i = 1, max_rows
            read(10, *) data_matrix(i,:)
            !write(*,*) data_matrix(i,:)
        end do
        
        ! Close the input file
        close(10)
    end subroutine read_input_file
end module m
!
   program main
    use m    
    ! The unkillable implicit statement.
    implicit none
    
    ! The naming scheme for variables in this program:
    !   tp  = titanpool
    !   vap = vapor
    !   cp  = heat capacity
    !   liq = liquid
    !   den = density
    
    character(len=100) ::   &
        ! File with N2 saturation vaporization values from TitanPOOL.
        tp_n2_sat_vap_file, &
        ! File with the N2 heat capacity (cp) values from TitanPOOL.
        tp_n2_sat_cp_file,  &
        ! File with the N2 saturation liquidization values from TitanPOOL.
        tp_n2_sat_liq_file, &
        ! File with the values for the density of liquid(?) N2 at saturation.
        tp_n2_sat_den_file

    ! Define the maximum size of the matrix
    integer :: max_rows
    integer :: max_cols        
    
    ! Define the matrices to store the data.
    real, dimension(1000,1000) :: tp_n2_sat_comp_vap
    real, dimension(1000,1000) :: tp_n2_sat_comp_cp
    real, dimension(1000,1000) :: tp_n2_sat_comp_liq
    real, dimension(1000,1000) :: tp_n2_sat_comp_den    
    
    ! Assign the file names
    tp_n2_sat_vap_file = "Titan_N2_saturation_comp_vap.csv"
    tp_n2_sat_cp_file = "Titan_N2_saturation_comp_Cp.csv"
    tp_n2_sat_liq_file = "Titan_N2_saturation_comp_liq.csv"
    tp_n2_sat_den_file = "Titan_N2_saturation_comp_den.csv"
    
    ! Set the value of the maximum size of the matrix.
    max_rows = 42
    max_cols = 64
       
    ! Read the input files
    call read_input_file(tp_n2_sat_vap_file, tp_n2_sat_comp_vap, &
        max_rows, max_cols)
    
    call read_input_file(tp_n2_sat_cp_file, tp_n2_sat_comp_cp, &
         max_rows, max_cols)
        
    call read_input_file(tp_n2_sat_liq_file, tp_n2_sat_comp_liq, &
        max_rows, max_cols)
    
    call read_input_file(tp_n2_sat_den_file, tp_n2_sat_comp_den, &
        max_rows, max_cols)
end program main
1 Like

Another term for this is variable shadowing. I first learned the concept under that terminology with SML. When I got the first warning about masking in Fortran I was confused by the wording.

1 Like

@Beliavsky Thanks for the reply. It’s very helpful.

Well, I am learning a lot from this. I had no knowledge of internal procedures vs external procedures, at least not with that terminology. This gives me something to search on and learn from.

I was planning already to put this code in a module, since it’s destined for a larger, pre-existing code, but I thought making it a standalone program would help with debugging. It’s good to know the code is fine and that it’s fine to move it to a module.

With the exception of . . .

This is what I get for sharing code I hadn’t totally tested. I had the later read_inputfile lines commented out during testing, so I hadn’t caught that error yet. Thanks!

Finally . . .

Good suggestion. Thanks!

1 Like

@blametroi Thanks for this. I started looking up variable shadowing, and you are right, the explanations for that are helping me understand the original warning. With @Beliavsky’s help and your help, I think I can put this one to bed. Thanks!

I don’t think a compiler is required to warn you, but it is a good thing that it does. One potential problem is that the programmer might modify the dummy argument, thinking that he is modifying the module variable with the same name, so the compiler warning is telling the programmer to beware of that mistake. But there are other potential problems too. When a module variable is passed as an argument, the programmer is allowed to change the value only through the dummy argument, and after that change, references to the module variable are no longer allowed. This restriction is to allow the compiler to cache the dummy argument in a register or something. If the programmer changes the value through the module (say by calling some lower level subprogram that USEs that module), then this is an error. It is the type of error that a compiler is unlikely to detect or warn you about, and it could result in a long debugging session to track down the problem. In your case, the dummy argument is intent(in), so you can’t change its value in a straightforward way, but of course there are many ways to change an intent(in) variable such that the compiler cannot catch the mistake. So there are lots of potential mistakes the programmer can make, and that compiler warning is trying to help you avoid them.