Skip to content
Snippets Groups Projects
  • Lionel GUEZ's avatar
    56150231
    Split arborescence into `Inst_eddies` and Overlap · 56150231
    Lionel GUEZ authored
    Also split the tests, Fortran source files, Python files and JSon
    files. Keep at the top level the files used in both `Inst_eddies` and
    Overlap.
    
    Motivations for the split:
    
    - The top directory contained many files.
    
    - It may be useful to compile only one of the two sub-projects. For
    example, only `Inst_eddies` on Ciclad, where MPI 3 is not available.
    56150231
    History
    Split arborescence into `Inst_eddies` and Overlap
    Lionel GUEZ authored
    Also split the tests, Fortran source files, Python files and JSon
    files. Keep at the top level the files used in both `Inst_eddies` and
    Overlap.
    
    Motivations for the split:
    
    - The top directory contained many files.
    
    - It may be useful to compile only one of the two sub-projects. For
    example, only `Inst_eddies` on Ciclad, where MPI 3 is not available.
get_var.f90 1.60 KiB
module get_var_m

  implicit none

contains

  subroutine get_var(periodic, max_rad_lon, values, ncid, nlon, name, &
       new_fill_value)

    ! Read a NetCDF variable, change the missing value and extend it
    ! in longitude if periodic.

    ! Libraries:
    use netcdf95, only: nf95_inq_varid, nf95_get_var, nf95_get_missing

    logical, intent(in):: periodic ! grid is periodic in longitude
    
    integer, intent(in):: max_rad_lon ! maximum radius of an eddy in
    ! longitude, in number of grid points, used only if periodic

    real, intent(out):: values(1 - merge(max_rad_lon, 0, periodic):, :)
    ! (1 - merge(max_rad_lon, 0, periodic):nlon + merge(max_rad_lon,
    ! 0, periodic), nlat) ssh, u or v. We cannot place this argument
    ! first because the declaration references max_rad_lon and
    ! periodic.

    integer, intent(in):: ncid, nlon
    character(len = *), intent(in):: name ! of NetCDF variable
    real, intent(in):: new_fill_value

    ! Local:
    integer varid
    real Fill_Value

    !-------------------------------------------------------------------------

    call nf95_inq_varid(ncid, name, varid)
    call nf95_get_var(ncid, varid, values(1:nlon, :))
    call nf95_get_missing(ncid, varid, Fill_Value)

    ! Change the missing value:
    where (values(1:nlon, :) == Fill_Value) values(1:nlon, :) = new_fill_value

    if (periodic) then
       ! Extend in longitude:
       values(1 - max_rad_lon:0, :) &
            = values(nlon + 1 - max_rad_lon:nlon, :)
       values(nlon + 1:nlon + max_rad_lon, :) = values(1:max_rad_lon, :)
    end if

  end subroutine get_var

end module get_var_m