Skip to content
Snippets Groups Projects
Commit 6cf5182e authored by Lionel GUEZ's avatar Lionel GUEZ Committed by GUEZ Lionel
Browse files

Transmit `cont_list_proj` from `get_1_outerm`

Transmit `cont_list_proj` from `get_1_outerm` to `set_max_speed`.
parent c05d6230
No related branches found
No related tags found
No related merge requests found
program test_get_1_outerm
! Libraries:
use contour_531, only: polyline
use jumble, only: csvread, deg_to_rad, rad_to_deg
use shapelib, only: shpfileobject, ftdouble, shpt_polygon, shpclose
use shapelib_03, only: shp_create_03, dbf_add_field_03, &
......@@ -57,6 +58,14 @@ program test_get_1_outerm
! order of points in cont_list(i)%polyline (clockwise or
! counter-clockwise) is not specified.
type(polyline) cont_list_proj(n_max_cont)
! Contour list, with points given by projection
! coordinates. Defined only for subscripts 1:n_cont. The contour
! with a given subscript in cont_list_proj corresponds to the
! contour with the same subscript in cont_list. For i <= n_cont,
! the order of points in cont_list_proj(i) (clockwise or
! counter-clockwise) is not specified.
integer n_cont ! number of good contours found and stored in cont_list
TYPE(shpfileobject) hshp_cont_list
namelist /main_nml/ ind_targ_extr, innermost_level, cyclone, date, &
......@@ -83,8 +92,8 @@ program test_get_1_outerm
e%extr%coord_proj = ind_targ_extr
e%extr%coord = corner + (ind_targ_extr - 1) * step
call get_1_outerm(e%out_cont, cont_list, n_cont, cyclone, e%extr%coord, &
innermost_level, outside_points, ssh, corner, step)
call get_1_outerm(e%out_cont, cont_list, cont_list_proj, n_cont, cyclone, &
e%extr%coord, innermost_level, outside_points, ssh, corner, step)
if (e%out_cont%closed) then
e%extr%ssh = ssh(ind_targ_extr(1), ind_targ_extr(2))
......
program test_set_max_speed
! Libraries:
use contour_531, only: convert_to_ind, null_polyline
use contour_531, only: convert_to_ind, null_polyline, polyline
use gpc_f, only: shp_read_pol, polygon
use jumble, only: get_command_arg_dyn, assert, deg_to_rad
use shapelib, only: shpfileobject, shpclose
......@@ -22,7 +22,7 @@ program test_set_max_speed
logical cyclone
logical periodic ! grid is periodic in longitude
integer nlon, nlat, d, eddy_index, n_cont, i, ishape
integer nlon, nlat, d, eddy_index, n_cont, i, j, ishape
real, allocatable:: ssh(:, :) ! (nlon, nlat) sea-surface height, in m
real, allocatable:: u(:, :), v(:, :) ! (nlon, nlat) wind, in m s-1
type(eddy) e
......@@ -49,6 +49,14 @@ program test_set_max_speed
! order of points in cont_list(i)%polyline (clockwise or
! counter-clockwise) is not specified.
type(polyline) cont_list_proj(n_max_cont)
! Contour list, with points given by projection
! coordinates. Defined only for subscripts 1:n_cont. The contour
! with a given subscript in cont_list_proj corresponds to the
! contour with the same subscript in cont_list. For i <= n_cont,
! the order of points in cont_list_proj(i) (clockwise or
! counter-clockwise) is not specified.
TYPE(shpfileobject) hshp
type(polygon) p
......@@ -102,12 +110,18 @@ program test_set_max_speed
call dbf_read_attribute_03(cont_list(i)%ssh, hshp, ifield = 0, &
ishape = ishape)
cont_list_proj(i)%n_points = cont_list(i)%n_points
cont_list_proj(i)%closed = cont_list(i)%closed
allocate(cont_list_proj(i)%points(2, cont_list_proj(i)%n_points))
forall (j = 1:cont_list_proj(i)%n_points) &
cont_list_proj(i)%points(:, j) = (cont_list(i)%points(:, j) &
- corner) / step + 1.
end do
call shpclose(hshp)
call create_cont_list
call set_max_speed(e%speed_cont, e%max_speed, cont_list, n_cont, &
e%extr%coord, ssh(llc(1):urc(1), llc(2):urc(2)), &
call set_max_speed(e%speed_cont, e%max_speed, cont_list, cont_list_proj, &
n_cont, e%extr%coord, ssh(llc(1):urc(1), llc(2):urc(2)), &
u(llc(1):urc(1), llc(2):urc(2)), v(llc(1):urc(1), llc(2):urc(2)), &
corner_window, step)
call close_cont_list
......
......@@ -4,8 +4,9 @@ module get_1_outerm_m
contains
subroutine get_1_outerm(out_cont, cont_list, n_cont, cyclone, coord_extr, &
innermost_level_2, outside_points, ssh, corner, step)
subroutine get_1_outerm(out_cont, cont_list, cont_list_proj, n_cont, &
cyclone, coord_extr, innermost_level_2, outside_points, ssh, corner, &
step)
! This procedure gets one outermost good contour with sufficient
! area, if it can find one. If the procedure cannot find an
......@@ -63,6 +64,15 @@ contains
! order of points in cont_list(i)%polyline (clockwise or
! counter-clockwise) is not specified.
type(polyline), intent(out):: cont_list_proj(:) ! (n_max_cont)
! Contour list, with points given by projection
! coordinates. Defined only for subscripts 1:n_cont. If n_cont >=
! 1, the outermost contour is element with subscript n_cont. The
! contour with a given subscript in cont_list_proj corresponds to
! the contour with the same subscript in cont_list. For i <=
! n_cont, the order of points in cont_list_proj(i) (clockwise or
! counter-clockwise) is not specified.
integer, intent(out):: n_cont
! number of good contours found and stored, 0 <= n_cont <= n_max_cont - 1
......@@ -88,7 +98,6 @@ contains
! longitude and latitude steps, in rad
! Local:
real level_try, level_good, level_bad ! in m
real, parameter:: precision = 5e-4 ! in m
logical mask(size(ssh, 1), size(ssh, 2))
......@@ -97,15 +106,6 @@ contains
real corner_proj(2), coord_extr_proj(2)
real outside_points_proj(2, size(outside_points, 2))
type(polyline) cont_list_proj(size(cont_list)) ! (n_max_cont)
! Contour list, with points given by projection
! coordinates. Defined only for subscripts 1:n_cont. If n_cont >=
! 1, the outermost contour is element with subscript n_cont. The
! contour with a given subscript in cont_list_proj corresponds to
! the contour with the same subscript in cont_list. For i <=
! n_cont, the order of points in cont_list_proj(i) (clockwise or
! counter-clockwise) is not specified.
!-----------------------------------------------------------------
corner_proj = (corner - corner_whole) / step + 1.
......
......@@ -10,7 +10,7 @@ contains
! This procedure sets contours in an eddy.
! Libraries:
use contour_531, only: convert_to_ind
use contour_531, only: convert_to_ind, polyline
use config_m, only: min_amp
use derived_types, only: extremum, ssh_contour
......@@ -73,6 +73,14 @@ contains
! order of points in cont_list(i)%polyline (clockwise or
! counter-clockwise) is not specified.
type(polyline) cont_list_proj(n_max_cont)
! Contour list, with points given by projection
! coordinates. Defined only for subscripts 1:n_cont. The contour
! with a given subscript in cont_list_proj corresponds to the
! contour with the same subscript in cont_list. For i <= n_cont,
! the order of points in cont_list_proj(i) (clockwise or
! counter-clockwise) is not specified.
integer n_cont
! number of good contours found and stored in cont_list, 0 <=
! n_cont <= n_max_cont
......@@ -83,8 +91,8 @@ contains
innermost_level_2 = merge(extr%ssh + merge(min_amp, - min_amp, cyclone), &
innermost_level, abs(extr%ssh - innermost_level) < min_amp)
call get_1_outerm(out_cont, cont_list, n_cont, cyclone, extr%coord, &
innermost_level_2, outside_points, ssh, corner, step)
call get_1_outerm(out_cont, cont_list, cont_list_proj, n_cont, cyclone, &
extr%coord, innermost_level_2, outside_points, ssh, corner, step)
! Done with outermost contour, now let us take care of the
! max-speed contour.
......@@ -104,8 +112,8 @@ contains
! Done restricting field
call set_max_speed(speed_cont, max_speed, cont_list, n_cont, &
extr%coord, ssh(llc(1):urc(1), llc(2):urc(2)), &
call set_max_speed(speed_cont, max_speed, cont_list, cont_list_proj, &
n_cont, extr%coord, ssh(llc(1):urc(1), llc(2):urc(2)), &
u(llc(1):urc(1), llc(2):urc(2)), &
v(llc(1):urc(1), llc(2):urc(2)), corner_window, step)
end if
......
......@@ -4,8 +4,8 @@ module set_max_speed_m
contains
subroutine set_max_speed(speed_cont, max_speed, cont_list, n_cont, &
extr_coord, ssh, u, v, corner, step)
subroutine set_max_speed(speed_cont, max_speed, cont_list, cont_list_proj, &
n_cont, extr_coord, ssh, u, v, corner, step)
! This procedure defines speed_cont and max_speed. On return,
! speed_cont may be a null ssh contour and max_speed may be set to
......@@ -51,6 +51,14 @@ contains
! order of points in the polyline components (clockwise or
! counter-clockwise) is not specified.
type(polyline), intent(inout):: cont_list_proj(:) ! (n_max_cont)
! Contour list, with points given by projection
! coordinates. Defined only for subscripts 1:n_cont. The contour
! with a given subscript in cont_list_proj corresponds to the
! contour with the same subscript in cont_list. For i <= n_cont,
! the order of points in cont_list_proj(i) (clockwise or
! counter-clockwise) is not specified.
integer, intent(inout):: n_cont
! Number of good contours found and stored in cont_list. On entry,
! 1 <= n_cont <= n_max_cont - 1 (not 0 because set_max_speed is
......@@ -72,19 +80,10 @@ contains
real, intent(in):: step(:) ! (2) longitude and latitude steps, in rad
! Local:
real, allocatable:: speed(:) ! (n_cont) speed on the contour
integer i, i_outer, ishape
real corner_proj(2), extr_coord_proj(2)
type(polyline) cont_list_proj(size(cont_list)) ! (n_max_cont)
! Contour list, with points given by projection
! coordinates. Defined only for subscripts 1:n_cont. The contour
! with a given subscript in cont_list_proj corresponds to the
! contour with the same subscript in cont_list. For i <= n_cont,
! the order of points in cont_list_proj(i) (clockwise or
! counter-clockwise) is not specified.
!---------------------------------------------------------------
corner_proj = (corner - corner_whole) / step + 1.
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment