-
GUEZ Lionel authored
In the case of non-uniform longitude-latitude grid: we read the whole coordinate arrays from the NetCDF file; we have a different way of inverting the projection, in `invert_proj`; the program `eddy_graph` does not use `corner_whole` and step, which are not defined, it uses instead the shapefile `extr_proj`.
GUEZ Lionel authoredIn the case of non-uniform longitude-latitude grid: we read the whole coordinate arrays from the NetCDF file; we have a different way of inverting the projection, in `invert_proj`; the program `eddy_graph` does not use `corner_whole` and step, which are not defined, it uses instead the shapefile `extr_proj`.
invert_proj.f90 1.65 KiB
module invert_proj_m
use input_ssh_m, only: uniform_lon_lat, corner_whole, step, longitude, &
latitude
implicit none
interface invert_proj
! Invert projection: convert from projection coordinates x, y to
! longitude and latitude.
module procedure invert_proj_int, invert_proj_pol
end interface invert_proj
private
public invert_proj
contains
pure function invert_proj_int(ind)
real invert_proj_int(2)
integer, intent(in):: ind(:) ! (2)
!-------------------------------------------------------
if (uniform_lon_lat) then
invert_proj_int = corner_whole + (ind - 1.) * step
else
invert_proj_int = [longitude(ind(1)), latitude(ind(2))]
end if
end function invert_proj_int
!**************************************************************************
pure type(polyline) function invert_proj_pol(ind)
use contour_531, only: polyline, convert_to_reg_coord
use input_ssh_m, only: lon_steps, lat_steps
type(polyline), intent(in):: ind
! Local
integer i, k(2)
!-------------------------------------------------------
if (uniform_lon_lat) then
invert_proj_pol = convert_to_reg_coord(ind, corner_whole, step)
else
invert_proj_pol%n_points = ind%n_points
invert_proj_pol%closed = ind%closed
allocate(invert_proj_pol%points(2, ind%n_points))
do i = 1, ind%n_points
k = floor(ind%points(:, i))
invert_proj_pol%points(:, i) = [longitude(k(1)), latitude(k(2))] &
+ (ind%points(:, i) - k) * [lon_steps(k(1)), lat_steps(k(2))]
end do
end if
end function invert_proj_pol
end module invert_proj_m