Skip to content
Snippets Groups Projects
  • Lionel GUEZ's avatar
    bf045ac7
    Move initialization of shapefiles to a separate procedure, · bf045ac7
    Lionel GUEZ authored
    init_shapefiles. This allows us to have variables for DBF field
    numbers, as module variables. We avoid the burden of passing this
    large number of variables as arguments to write_eddy. Safer to have
    variables for DBF field numbers than relying on the order of those
    fields.
    
    Remove file_list. This was a duplication of information.
    
    Use named constant for missing max speed value. It is used in two procedures.
    bf045ac7
    History
    Move initialization of shapefiles to a separate procedure,
    Lionel GUEZ authored
    init_shapefiles. This allows us to have variables for DBF field
    numbers, as module variables. We avoid the burden of passing this
    large number of variables as arguments to write_eddy. Safer to have
    variables for DBF field numbers than relying on the order of those
    fields.
    
    Remove file_list. This was a duplication of information.
    
    Use named constant for missing max speed value. It is used in two procedures.
write_eddy.f 4.02 KiB
module write_eddy_m
  
    implicit none

contains

  subroutine write_eddy(e, k, i, hshp_extremum, hshp_outermost, hshp_max_speed)

    use, intrinsic:: ieee_arithmetic, only: ieee_is_nan

    use derived_types, only: eddy, missing_speed
    use init_shapefiles_m, only: ifield_extr_ssh, ifield_extr_date, &
         ifield_extr_eddy_index, ifield_extr_interp, ifield_extr_cycl, &
         ifield_extr_suff_amp, ifield_extr_speed, ifield_out_area, &
         ifield_out_ssh, ifield_out_date, ifield_out_eddy_index, &
         ifield_out_twice, ifield_out_radius4, ifield_max_speed_area, &
         ifield_max_speed_ssh, ifield_max_speed_date, &
         ifield_max_speed_eddy_index 
    use nr_util, only: pi
    use shapelib, only: shpfileobject, shpt_polygon
    use shapelib_03, only: shp_append_point_03, dbf_write_attribute_03, &
         shp_append_object_03, shp_append_null_03

    type(eddy), intent(in):: e
    integer, intent(in):: k ! date index
    integer, intent(in):: i ! eddy index

    TYPE(shpfileobject), intent(inout):: hshp_extremum ! shapefile extremum_$m

    TYPE(shpfileobject), intent(inout):: hshp_outermost
    ! shapefile outermost_contour_$m

    TYPE(shpfileobject), intent(inout):: hshp_max_speed
    ! shapefile x_speed_contour_$m

    ! Local:
    integer ishape
    real, parameter:: rad_over_deg = 180. / pi

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

    call shp_append_point_03(ishape, hshp_extremum, e%coord_extr * rad_over_deg)
    
    call dbf_write_attribute_03(hshp_extremum, ishape, ifield_extr_ssh, &
         e%ssh_extr)
    call dbf_write_attribute_03(hshp_extremum, ishape, ifield_extr_date, k)
    call dbf_write_attribute_03(hshp_extremum, ishape, ifield_extr_eddy_index, &
         i)
    call dbf_write_attribute_03(hshp_extremum, ishape, ifield_extr_interp, &
         merge(1, 0, e%interpolated))
    call dbf_write_attribute_03(hshp_extremum, ishape, ifield_extr_cycl, &
         merge(1, 0, e%cyclone))
    call dbf_write_attribute_03(hshp_extremum, ishape, ifield_extr_suff_amp, &
         merge(1, 0, e%suff_amp))

    if (ieee_is_nan(e%max_speed)) then
       call dbf_write_attribute_03(hshp_extremum, ishape, ifield_extr_speed, &
            missing_speed)
       ! (Cannot write NaN to dbf file.)
    else
       call dbf_write_attribute_03(hshp_extremum, ishape, ifield_extr_speed, &
            e%max_speed)
    end if

    if (e%interpolated) then
       call shp_append_null_03(ishape, hshp_outermost)
       call shp_append_null_03(ishape, hshp_max_speed)
    else
       if (e%out_cont%n_points == 0) then
          call shp_append_null_03(ishape, hshp_outermost)
       else
          call shp_append_object_03(ishape, hshp_outermost, shpt_polygon, &
               e%out_cont%points * rad_over_deg)
       end if

       if (e%speed_cont%n_points == 0) then
          call shp_append_null_03(ishape, hshp_max_speed)
       else
          call shp_append_object_03(ishape, hshp_max_speed, shpt_polygon, &
               e%speed_cont%points * rad_over_deg)
       end if
    end if

    call dbf_write_attribute_03(hshp_outermost, ishape, ifield_out_area, &
         e%out_cont%area)
    call dbf_write_attribute_03(hshp_outermost, ishape, ifield_out_ssh, &
         e%out_cont%ssh)
    call dbf_write_attribute_03(hshp_outermost, ishape, ifield_out_date, k)
    call dbf_write_attribute_03(hshp_outermost, ishape, ifield_out_eddy_index, &
         i)
    call dbf_write_attribute_03(hshp_outermost, ishape, ifield_out_twice, &
         merge(1, 0, e%twice))
    call dbf_write_attribute_03(hshp_outermost, ishape, ifield_out_radius4, &
         e%radius4)

    call dbf_write_attribute_03(hshp_max_speed, ishape, ifield_max_speed_area, &
         e%speed_cont%area)
    call dbf_write_attribute_03(hshp_max_speed, ishape, ifield_max_speed_ssh, &
         e%speed_cont%ssh)
    call dbf_write_attribute_03(hshp_max_speed, ishape, ifield_max_speed_date, &
         k)
    call dbf_write_attribute_03(hshp_max_speed, ishape, &
         ifield_max_speed_eddy_index, i)

  end subroutine write_eddy

end module write_eddy_m