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

  implicit none

contains

  subroutine read_field_indices(hshp)
    use shapelib, only: dbfgetfieldindex, dbffileisnull
    use shapelib_03, only: dbf_get_field_index_03

    use derived_types, only: shpc_slice_handler
    TYPE(shpc_slice_handler), intent(inout):: hshp
    !---------------------------------------------------------------------

    call dbf_get_field_index_03(hshp%extremum, "ssh", hshp%extr_ssh)
    call dbf_get_field_index_03(hshp%extremum, "date", hshp%extr_date)
    call dbf_get_field_index_03(hshp%extremum, "eddy_index", &
         hshp%extr_eddy_index)
    call dbf_get_field_index_03(hshp%extremum, "valid", hshp%extr_valid)
    call dbf_get_field_index_03(hshp%extremum, "speed", hshp%extr_speed)

    if (.not. dbffileisnull(hshp%extr_proj)) then
       call dbf_get_field_index_03(hshp%extr_proj, "date", hshp%extr_proj_date)
       call dbf_get_field_index_03(hshp%extr_proj, "eddy_index", &
            hshp%extr_proj_eddy_index)
    end if

    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, "date", hshp%out_date)
    call dbf_get_field_index_03(hshp%outermost, "eddy_index", &
         hshp%out_eddy_index)

    ! We allow the field radius4 to be missing:
    hshp%out_radius4 = dbfgetfieldindex(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 dbf_get_field_index_03(hshp%max_speed, "date", hshp%max_speed_date)
    call dbf_get_field_index_03(hshp%max_speed, "eddy_index", &
         hshp%max_speed_eddy_index)

  end subroutine read_field_indices

end module read_field_indices_m