Skip to content
Snippets Groups Projects
  • Lionel GUEZ's avatar
    b55a165b
    Add TAGS rule in `CMakeLists.txt`. Do not rely on external · b55a165b
    Lionel GUEZ authored
    `settings.mk` in GNUmakefile.
    
    Bug fix in procedure `dispatch_snapshot`: an isolated eddy is a valid eddy.
    
    In script `plot_snapshot.py`, in function snaphot, replace argument ax
    with argument `new_figure` so the user does not have to call figure
    and `axes(projection = projection)`. Add argument light to function
    snapshot so we can call snapshot with light set to False for a second
    snapshot. Add a test to only read `h.nc` when we need it.
    
    In script `read_overlap.py`, print more information: number of nodes,
    number of edges, number of nodes with at least one successor, number
    of nodes with at least one predecessor, splitting events, merging
    events.
    
    In script `stat.py`, use the convention that shapefiles are grouped in
    a directory instead of identifying a set of shapefiles by the end of
    their basename.
    
    In main program `test_successive_overlap`, we know that `delta_in` for
    snapshot 1 and `delta_out` for snapshot 2 are `huge(0)` so do not test
    this. Print eddy identifiers in a single line. Add the printing of
    identifiers of isolated eddies.
    b55a165b
    History
    Add TAGS rule in `CMakeLists.txt`. Do not rely on external
    Lionel GUEZ authored
    `settings.mk` in GNUmakefile.
    
    Bug fix in procedure `dispatch_snapshot`: an isolated eddy is a valid eddy.
    
    In script `plot_snapshot.py`, in function snaphot, replace argument ax
    with argument `new_figure` so the user does not have to call figure
    and `axes(projection = projection)`. Add argument light to function
    snapshot so we can call snapshot with light set to False for a second
    snapshot. Add a test to only read `h.nc` when we need it.
    
    In script `read_overlap.py`, print more information: number of nodes,
    number of edges, number of nodes with at least one successor, number
    of nodes with at least one predecessor, splitting events, merging
    events.
    
    In script `stat.py`, use the convention that shapefiles are grouped in
    a directory instead of identifying a set of shapefiles by the end of
    their basename.
    
    In main program `test_successive_overlap`, we know that `delta_in` for
    snapshot 1 and `delta_out` for snapshot 2 are `huge(0)` so do not test
    this. Print eddy identifiers in a single line. Add the printing of
    identifiers of isolated eddies.
candidate_overlap.f90 976 B
module candidate_overlap_m

  implicit none

contains

  function candidate_overlap(extr_map, list_vis, cyclone)

    ! Find the eddies in extr_map that are valid and have a given
    ! cyclonicity.

    use derived_types, only: eddy

    integer, allocatable:: candidate_overlap(:)

    integer, intent(in):: extr_map(:, :)
    ! At a point of extremum SSH: identification number or this
    ! extremum. 0 at other points.

    type(eddy), intent(in):: list_vis(:)
    ! Visible eddies at a given date. We need components ? to be defined.

    logical, intent(in):: cyclone ! cyclonicity of the target extremum

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

    candidate_overlap = pack(extr_map, extr_map /= 0)
    candidate_overlap = pack(candidate_overlap, &
         list_vis(candidate_overlap)%valid &
         .and. (list_vis(candidate_overlap)%cyclone .eqv. cyclone))
    
  end function candidate_overlap

end module candidate_overlap_m