Skip to content
Snippets Groups Projects
read_field_indices.f90 1.95 KiB
Newer Older
module read_field_indices_m

  implicit none

contains

  subroutine read_field_indices(hshp, rank)
    use ezmpi, only: ezmpi_bcast
    use shapelib_03, only: dbf_get_field_index_03

    use derived_types, only: shpc
    TYPE(shpc), intent(inout):: hshp
    integer, intent(in):: rank

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

    if (rank == 0) then
       call dbf_get_field_index_03(hshp%extremum, "ssh", hshp%extr_ssh)
       call dbf_get_field_index_03(hshp%extremum, "days_1950", &
       call dbf_get_field_index_03(hshp%extremum, "eddy_index", &
            hshp%extr_eddy_index)
       call dbf_get_field_index_03(hshp%extremum, "interpolat", &
            hshp%extr_interp)
       call dbf_get_field_index_03(hshp%extremum, "valid", hshp%extr_valid)
       call dbf_get_field_index_03(hshp%extremum, "speed", hshp%extr_speed)
       call dbf_get_field_index_03(hshp%outermost, "r_eq_area", &
            hshp%out_r_eq_area)
       call dbf_get_field_index_03(hshp%outermost, "ssh", hshp%out_ssh)
       call dbf_get_field_index_03(hshp%outermost, "radius4", &
       call dbf_get_field_index_03(hshp%max_speed, "r_eq_area", &
            hshp%max_speed_r_eq_area)
       call dbf_get_field_index_03(hshp%max_speed, "ssh", hshp%max_speed_ssh)
    call ezmpi_bcast(hshp%extr_ssh, root = 0)
    call ezmpi_bcast(hshp%extr_date, root = 0)
    call ezmpi_bcast(hshp%extr_eddy_index, root = 0)
    call ezmpi_bcast(hshp%extr_interp, root = 0)
    call ezmpi_bcast(hshp%extr_valid, root = 0)
    call ezmpi_bcast(hshp%extr_speed, root = 0)
    call ezmpi_bcast(hshp%out_r_eq_area, root = 0)
    call ezmpi_bcast(hshp%out_ssh, root = 0)
    call ezmpi_bcast(hshp%out_radius4, root = 0)
    call ezmpi_bcast(hshp%max_speed_r_eq_area, root = 0)
    call ezmpi_bcast(hshp%max_speed_ssh, root = 0)

  end subroutine read_field_indices

end module read_field_indices_m