diff --git a/Common/derived_types.f90 b/Common/derived_types.f90 index 75b142d25802aa645adf03eb93d58d56197361a2..ff2edafd1d1a9547ab6820cc0a34883153c0da71 100644 --- a/Common/derived_types.f90 +++ b/Common/derived_types.f90 @@ -37,8 +37,6 @@ module derived_types ! is not a null ssh contour then max_speed is the speed on ! speed_cont. - logical valid ! valid out_cont found: not a null contour - integer:: delta_in = huge(0) ! Minimum difference in time subscript where there is a direct ! predecessor. Huge means there is no direct predecessor. @@ -50,7 +48,7 @@ module derived_types integer radius4 ! extr%coord_proj + radius4 - 1 in all four directions is inside outermost ! contour, extr%coord_proj + radius4 is outside. - ! radius4 /= 0 .eqv. valid + ! radius4 /= 0 .eqv. out_cont%closed end type eddy type snapshot diff --git a/Inst_eddies/Tests/test_get_1_outerm.f90 b/Inst_eddies/Tests/test_get_1_outerm.f90 index effd0871efbcd2a4a01417b77e1a6293904c4da1..e20e7f94b4fc9cd4692741fe00c89b3370cd516d 100644 --- a/Inst_eddies/Tests/test_get_1_outerm.f90 +++ b/Inst_eddies/Tests/test_get_1_outerm.f90 @@ -87,7 +87,6 @@ program test_get_1_outerm e%speed_cont = null_ssh_contour() e%max_speed = missing_speed e%radius4 = - 1 - e%valid = .true. call shpc_create(hshp, shpc_dir = "SHPC", cyclone = cyclone, slice = 0, & grid_lon_lat = grid_lon_lat) call write_eddy(e, hshp, date, i = 1) diff --git a/Inst_eddies/inst_eddies.f90 b/Inst_eddies/inst_eddies.f90 index f03dc1ddf706bb51f6f6ef6aed168821e5ea5208..d6728a5ac1c6e9b3ea4accf2d1d4c90f117e11d7 100644 --- a/Inst_eddies/inst_eddies.f90 +++ b/Inst_eddies/inst_eddies.f90 @@ -109,7 +109,7 @@ program inst_eddies do i = 1, s%number_extr associate (e => s%list(i)) - if (e%valid) then + if (e%out_cont%closed) then ! Restrict the field to the outermost contour: llc = floor(convert_to_ind(minval(e%out_cont%points, dim = 2), & diff --git a/Inst_eddies/nearby_extr.f90 b/Inst_eddies/nearby_extr.f90 index 39fdd57796cfeb59637efc19aca3d80b56fdc7ac..d778edbef2e34eb96970073230a33bf070209aad 100644 --- a/Inst_eddies/nearby_extr.f90 +++ b/Inst_eddies/nearby_extr.f90 @@ -19,8 +19,8 @@ contains ! extremum. 0 at other points. type(eddy), intent(in):: list(:) - ! Visible eddies at a given date. We need components extr%coord, - ! valid and cyclone to be defined. + ! Visible eddies at a given date. We need components extr%coord + ! and cyclone to be defined. integer, intent(in):: i ! identifying number of the target extremum @@ -36,7 +36,7 @@ contains selection = pack(extr_map, extr_map /= 0) selection = pack(selection, selection /= i & .and. ((list(selection)%cyclone .neqv. list(i)%cyclone) & - .or. list(selection)%valid)) + .or. list(selection)%out_cont%closed)) n_select = size(selection) allocate(nearby_extr(2, n_select)) forall (l = 1:n_select) & diff --git a/Inst_eddies/set_all_outerm.f90 b/Inst_eddies/set_all_outerm.f90 index a6395fc7d55c47328020199fc6babc15ab177b02..e99664c987021333a9563b3040ade124db8140cb 100644 --- a/Inst_eddies/set_all_outerm.f90 +++ b/Inst_eddies/set_all_outerm.f90 @@ -20,9 +20,9 @@ contains use nearby_extr_m, only: nearby_extr type(snapshot), intent(inout):: s - ! Define s%list%valid and s%list%out_cont. s%number_extr, - ! s%list%cyclone, s%list%extr, s%list%innermost_level, s%extr_map - ! should be defined on entry. + ! Define s%list%out_cont. s%number_extr, s%list%cyclone, + ! s%list%extr, s%list%innermost_level, s%extr_map should be + ! defined on entry. real, intent(in):: step(:) ! (2) longitude and latitude steps, in rad logical, intent(in):: periodic ! grid is periodic in longitude @@ -78,7 +78,7 @@ contains min_area = pi * (min_radius * 1e3)**2 forall (i = 1:s%number_extr) - s%list(i)%valid = .true. + s%list(i)%out_cont%closed = .true. ! must be intialized to true because it is used in nearby_extr end forall @@ -128,7 +128,6 @@ contains s%list(i)%cyclone, s%list(i)%extr%coord, innermost_level_2, & outside_points, ssh(llc(1):urc(1), llc(2):urc(2)), corner_window, & step, min_area) - s%list(i)%valid = s%list(i)%out_cont%closed end do end subroutine set_all_outerm diff --git a/Inst_eddies/write_eddy.f90 b/Inst_eddies/write_eddy.f90 index 263eb948a6221f8323dbd96c67dc76ab48d69058..bcadfbefe11c39f6c1df717f85f418ae78329aae 100644 --- a/Inst_eddies/write_eddy.f90 +++ b/Inst_eddies/write_eddy.f90 @@ -37,7 +37,7 @@ contains call dbf_write_attribute_03(hshpc%extremum, ishape, hshpc%extr_eddy_index, & i) call dbf_write_attribute_03(hshpc%extremum, ishape, hshpc%extr_valid, & - merge(1, 0, e%valid)) + merge(1, 0, e%out_cont%closed)) if (ieee_is_nan(e%max_speed)) then call dbf_write_attribute_03(hshpc%extremum, ishape, hshpc%extr_speed, & diff --git a/Inst_eddies/write_snapshot.f90 b/Inst_eddies/write_snapshot.f90 index cf5040960e2c3082dca86565102bb2b8f26e0407..4d6d57ef10861e4b5c7cedddd831b159b9b270f4 100644 --- a/Inst_eddies/write_snapshot.f90 +++ b/Inst_eddies/write_snapshot.f90 @@ -25,7 +25,7 @@ contains n_anti = 0 do i = 1, s%number_extr - if (s%list(i)%valid) then + if (s%list(i)%out_cont%closed) then if (s%list(i)%cyclone) then n_cyclo = n_cyclo + 1 call write_eddy(s%list(i), hshpc_cyclo, date, n_cyclo) diff --git a/Overlap/Tests/test_overlap.f90 b/Overlap/Tests/test_overlap.f90 index d15f501fc70df41f399ff2e16742037c48bbd0ff..53afbe15434a4321c2b94e409b58b2e938544c29 100644 --- a/Overlap/Tests/test_overlap.f90 +++ b/Overlap/Tests/test_overlap.f90 @@ -69,8 +69,8 @@ program test_overlap print *, k_test_1, ":" print *, "Valid isolated eddies:" do i = 1, flow(1)%number_extr - if (flow(1)%list(i)%valid .and. flow(1)%list(i)%delta_out & - == huge(0)) write(unit = *, fmt = "(i0, 1x)", advance = "no") i + if (flow(1)%list(i)%delta_out == huge(0)) & + write(unit = *, fmt = "(i0, 1x)", advance = "no") i end do print * @@ -79,8 +79,7 @@ program test_overlap print *, "Valid isolated eddies:" do i = 1, flow(max_delta + 1)%number_extr - if (flow(max_delta + 1)%list(i)%valid & - .and. flow(max_delta + 1)%list(i)%delta_in == huge(0)) & + if (flow(max_delta + 1)%list(i)%delta_in == huge(0)) & write(unit = *, fmt = "(i0, 1x)", advance = "no") i end do diff --git a/Overlap/candidate_overlap.f90 b/Overlap/candidate_overlap.f90 index f7a4b9f84f7b5cced54650156ccc863809f1ab3a..e94405a0eaec79d82ac91d29ebe6531df580a304 100644 --- a/Overlap/candidate_overlap.f90 +++ b/Overlap/candidate_overlap.f90 @@ -6,9 +6,8 @@ contains function candidate_overlap(extr_map, list, delta_out, delta) - ! Find the eddies in extr_map that are valid. Also, if delta_out < - ! delta then the eddies should not have a predecessor at time - ! distance < delta. + ! Select eddies in extr_map: if delta_out < delta then the eddies + ! should not have a predecessor at time distance < delta. use derived_types, only: eddy @@ -20,9 +19,9 @@ contains ! extremum. 0 at other points. type(eddy), intent(in):: list(:) - ! Visible eddies at a given date. We need components valid and - ! delta_in to be defined. Arriving in this subroutine, - ! list%delta_in could be <= delta or huge(0). + ! Visible eddies at a given date. We need component delta_in to be + ! defined. Arriving in this subroutine, list%delta_in could be <= + ! delta or huge(0). integer, intent(in):: delta_out ! Arriving in this subroutine, delta_out could be <= delta or @@ -34,8 +33,7 @@ contains candidate_overlap = pack(extr_map, extr_map /= 0) candidate_overlap = pack(candidate_overlap, & - list(candidate_overlap)%valid .and. (delta_out >= delta & - .or. list(candidate_overlap)%delta_in >= delta)) + delta_out >= delta .or. list(candidate_overlap)%delta_in >= delta) end function candidate_overlap diff --git a/Overlap/dispatch_snapshot.f90 b/Overlap/dispatch_snapshot.f90 index 47ff95d5a884375e80652c8ba42813aaebad492e..ca1c0228ca19537a4ea08cda3502996c2fda74a9 100644 --- a/Overlap/dispatch_snapshot.f90 +++ b/Overlap/dispatch_snapshot.f90 @@ -25,7 +25,7 @@ contains if (rank == 0 .or. k >= k_begin + max_delta) then do i = 1, s%number_extr - if (s%list(i)%valid .and. s%list(i)%delta_in == huge(0) & + if (s%list(i)%delta_in == huge(0) & .and. s%list(i)%delta_out == huge(0)) & write(unit_isolated, fmt = *) k, i end do diff --git a/Overlap/overlap.f90 b/Overlap/overlap.f90 index ab0fbf9c6deaf4f7928f3acb7f38a4595c63c970..63cf9a3430df32ff408d626ddc902173bb4d5156 100644 --- a/Overlap/overlap.f90 +++ b/Overlap/overlap.f90 @@ -53,71 +53,68 @@ contains loop_i1: do i1 = 1, flow(j - delta)%number_extr associate (e1 => flow(j - delta)%list(i1)) - test_valid: if (e1%valid) then - ! Define the geographical window around each eddy extremum: + ! Define the geographical window around each eddy extremum: - llc = e1%extr%coord_proj - dist_lim - urc = e1%extr%coord_proj + dist_lim + llc = e1%extr%coord_proj - dist_lim + urc = e1%extr%coord_proj + dist_lim - llc(2) = max(llc(2), 1) - urc(2) = min(urc(2), nlat) + llc(2) = max(llc(2), 1) + urc(2) = min(urc(2), nlat) - if (.not. periodic) then - llc(1) = max(llc(1), 1) - urc(1) = min(urc(1), nlon) - end if + if (.not. periodic) then + llc(1) = max(llc(1), 1) + urc(1) = min(urc(1), nlon) + end if - ! Pre-select potential successors: - selection = candidate_overlap(flow(j)%extr_map(llc(1):urc(1), & - llc(2):urc(2)), flow(j)%list, e1%delta_out, delta) + ! Pre-select potential successors: + selection = candidate_overlap(flow(j)%extr_map(llc(1):urc(1), & + llc(2):urc(2)), flow(j)%list, e1%delta_out, delta) - n_select = size(selection) + n_select = size(selection) - if (n_select /= 0) then - if (e1%speed_cont%n_points /= 0) then - polyline_1 = e1%speed_cont%polyline - else - polyline_1 = e1%out_cont%polyline - end if + if (n_select /= 0) then + if (e1%speed_cont%n_points /= 0) then + polyline_1 = e1%speed_cont%polyline + else + polyline_1 = e1%out_cont%polyline end if - - DO l = 1, n_select - i2 = selection(l) - associate (e2 => flow(j)%list(i2)) - ! Assertion: {e1%delta_out >= delta .or. e2%delta_in - ! >= delta} - - if (e2%speed_cont%n_points /= 0) then - polyline_2 = e2%speed_cont%polyline - else - polyline_2 = e2%out_cont%polyline - end if - - ! Shift the longitudes of polyline_2 to values close to the - ! longitude of extremum i1: - polyline_2%points(1, :) = polyline_2%points(1, :) & - + floor((e1%extr%coord(1) - e2%extr%coord(1)) / twopi & - + 0.5) * twopi - - call gpc_polygon_clip_f(GPC_INT, polygon(nparts = 1, & - part = [polyline_1], hole = [.false.]), & - polygon(nparts = 1, part = [polyline_2], & - hole = [.false.]), res_pol) - - if (res_pol%nparts /= 0) then - ! polyline_1 and polyline_2 overlap - if (spher_polygon_area(res_pol) >= min_inters & - * min(abs(spher_polyline_area(polyline_1)), & - abs(spher_polyline_area(polyline_2)))) then - write(unit_edge, fmt = *) & - (k - delta) * e_overestim + i1, k * e_overestim + i2 - e1%delta_out = min(e1%delta_out, delta) - e2%delta_in = min(e2%delta_in, delta) - end if + end if + + DO l = 1, n_select + i2 = selection(l) + associate (e2 => flow(j)%list(i2)) + ! Assertion: {e1%delta_out >= delta .or. e2%delta_in + ! >= delta} + + if (e2%speed_cont%n_points /= 0) then + polyline_2 = e2%speed_cont%polyline + else + polyline_2 = e2%out_cont%polyline + end if + + ! Shift the longitudes of polyline_2 to values close to the + ! longitude of extremum i1: + polyline_2%points(1, :) = polyline_2%points(1, :) & + + floor((e1%extr%coord(1) - e2%extr%coord(1)) / twopi & + + 0.5) * twopi + + call gpc_polygon_clip_f(GPC_INT, polygon(nparts = 1, & + part = [polyline_1], hole = [.false.]), polygon(nparts = 1, & + part = [polyline_2], hole = [.false.]), res_pol) + + if (res_pol%nparts /= 0) then + ! polyline_1 and polyline_2 overlap + if (spher_polygon_area(res_pol) >= min_inters & + * min(abs(spher_polyline_area(polyline_1)), & + abs(spher_polyline_area(polyline_2)))) then + write(unit_edge, fmt = *) & + (k - delta) * e_overestim + i1, k * e_overestim + i2 + e1%delta_out = min(e1%delta_out, delta) + e2%delta_in = min(e2%delta_in, delta) end if - end associate - end DO - end if test_valid + end if + end associate + end DO end associate end do loop_i1 diff --git a/Overlap/read_eddy.f90 b/Overlap/read_eddy.f90 index ee9673040b29adb2d49ac73b22d5ca24b9416258..d988bd2cb442382eff9030aeb89a71355df788bc 100644 --- a/Overlap/read_eddy.f90 +++ b/Overlap/read_eddy.f90 @@ -29,7 +29,6 @@ contains ! Local: - integer int_attr ! integer attribute TYPE(shpobject) psobject type(polygon) p real attr @@ -45,10 +44,6 @@ contains call dbf_read_attribute_03(d, hshp%extremum, hshp%extr_date, ishape) call dbf_read_attribute_03(i, hshp%extremum, hshp%extr_eddy_index, ishape) - call dbf_read_attribute_03(int_attr, hshp%extremum, hshp%extr_valid, & - ishape) - e%valid = int_attr == 1 - call dbf_read_attribute_03(e%max_speed, hshp%extremum, hshp%extr_speed, & ishape) if (e%max_speed == missing_speed) & diff --git a/Overlap/recv_snapshot.f90 b/Overlap/recv_snapshot.f90 index 4ff528b45c14e4775e24d3889f03198f419ca44e..9490eb950dabe9f31f144bc7efc3831a1c1d4428 100644 --- a/Overlap/recv_snapshot.f90 +++ b/Overlap/recv_snapshot.f90 @@ -35,7 +35,6 @@ contains call recv_ssh_contour(s%list(i)%out_cont, source, tag) call recv_ssh_contour(s%list(i)%speed_cont, source, tag) call ezmpi_recv(s%list(i)%max_speed, source, tag) - call ezmpi_recv(s%list(i)%valid, source, tag) call ezmpi_recv(s%list(i)%delta_in, source, tag) call ezmpi_recv(s%list(i)%delta_out, source, tag) call ezmpi_recv(s%list(i)%radius4, source, tag) diff --git a/Overlap/send_snapshot.f90 b/Overlap/send_snapshot.f90 index 05a830096465c30aa9fef63c9ef28f34510da2c6..a2e3c04d38f6793f4791daa9be9fdc2507db5cd2 100644 --- a/Overlap/send_snapshot.f90 +++ b/Overlap/send_snapshot.f90 @@ -32,7 +32,6 @@ contains call send_ssh_contour(s%list(i)%out_cont, dest, tag) call send_ssh_contour(s%list(i)%speed_cont, dest, tag) call ezmpi_send(s%list(i)%max_speed, dest, tag) - call ezmpi_send(s%list(i)%valid, dest, tag) call ezmpi_send(s%list(i)%delta_in, dest, tag) call ezmpi_send(s%list(i)%delta_out, dest, tag) call ezmpi_send(s%list(i)%radius4, dest, tag)