Skip to content
Snippets Groups Projects
shpc_create.f90 3.37 KiB
module shpc_create_m

  implicit none

contains

  subroutine shpc_create(hshp, shpc_dir, cyclone, slice, with_proj)

    use, intrinsic:: ISO_FORTRAN_ENV

    ! Libraries:
    use jumble, only: new_unit
    use shapelib, only: shpt_point, shpt_polygon, ftdouble, ftinteger
    use shapelib_03, only: shp_create_03, dbf_add_field_03

    use derived_types, only: shpc_slice_handler
    use get_slice_dir_m, only: get_slice_dir

    TYPE(shpc_slice_handler), intent(out):: hshp
    character(len = *), intent(in):: shpc_dir
    logical, intent(in):: cyclone
    integer, intent(in):: slice
    logical, intent(in):: with_proj


    ! Local:
    integer iostat

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

    hshp%dir = get_slice_dir(shpc_dir, cyclone, slice)

    ! extremum shapefile:
    call shp_create_03(hshp%dir // "/extremum", shpt_point, &
         hshp%extremum, iostat)

    if (iostat /= 0) then
       write(unit = error_unit, fmt = *) &
            "shpc_create: Have you created directory ", hshp%dir, "?"
       stop 1
    end if

    call dbf_add_field_03(hshp%extr_ssh, hshp%extremum, 'ssh', ftdouble, &
         nwidth = 13, ndecimals = 6)
    call dbf_add_field_03(hshp%extr_date, hshp%extremum, 'date', &
         ftinteger, nwidth = 5, ndecimals = 0)
    call dbf_add_field_03(hshp%extr_eddy_index, hshp%extremum, 'eddy_index', &
         ftinteger, nwidth = 5, ndecimals = 0)
    call dbf_add_field_03(hshp%extr_speed, hshp%extremum, 'speed', ftdouble, &
         nwidth = 13, ndecimals = 6)

    ! extr_proj shapefile:
    if (with_proj) then
       call shp_create_03(hshp%dir // "/extr_proj", shpt_point, hshp%extr_proj)
       call dbf_add_field_03(hshp%extr_proj_date, hshp%extr_proj, 'date', &
            ftinteger, nwidth = 5, ndecimals = 0)
       call dbf_add_field_03(hshp%extr_proj_eddy_index, hshp%extr_proj, &
            'eddy_index', ftinteger, nwidth = 5, ndecimals = 0)
    end if

    ! outermost_contour shapefile:
    call shp_create_03(hshp%dir // "/outermost_contour", shpt_polygon, &
         hshp%outermost)
    call dbf_add_field_03(hshp%out_r_eq_area, hshp%outermost, &
         'r_eq_area', ftdouble, nwidth = 10, ndecimals = 4)
    call dbf_add_field_03(hshp%out_ssh, hshp%outermost, 'ssh', ftdouble, &
         nwidth = 13, ndecimals = 6)
    call dbf_add_field_03(hshp%out_date, hshp%outermost, 'date', &
         ftinteger, nwidth = 5, ndecimals = 0)
    call dbf_add_field_03(hshp%out_eddy_index, hshp%outermost, 'eddy_index', &
         ftinteger, nwidth = 5, ndecimals = 0)

    ! max_speed_contour shapefile:
    call shp_create_03(hshp%dir // "/max_speed_contour", shpt_polygon, &
         hshp%max_speed)
    call dbf_add_field_03(hshp%max_speed_r_eq_area, hshp%max_speed, &
         'r_eq_area', ftdouble, nwidth = 10, ndecimals = 4)
    call dbf_add_field_03(hshp%max_speed_ssh, hshp%max_speed, 'ssh', &
         ftdouble, nwidth = 13, ndecimals = 6)
    call dbf_add_field_03(hshp%max_speed_date, hshp%max_speed, 'date', &
         ftinteger, nwidth = 5, ndecimals = 0)
    call dbf_add_field_03(hshp%max_speed_eddy_index, hshp%max_speed, &
         'eddy_index', ftinteger, nwidth = 5, ndecimals = 0)

    call new_unit(hshp%unit)
    open(hshp%unit, file = hshp%dir // "/ishape_last.txt", status = "replace", &
         action = "write")
    hshp%cyclone = cyclone
    hshp%with_proj = with_proj

  end subroutine shpc_create

end module shpc_create_m