Skip to content
Snippets Groups Projects
test_write_null.f90 4.05 KiB
program test_write_null

  ! This program is a performance test for output of a shapefile
  ! collection. It writes null shapes.

  ! Libraries:
  use shapelib_03, only: shp_append_point_03, dbf_write_attribute_03, &
       shp_append_null_03

  use derived_types, only: shpc_slice_handler
  use shpc_close_m, only: shpc_close
  use shpc_create_m, only: shpc_create
  use shpc_open_m, only: shpc_open

  implicit none

  TYPE(shpc_slice_handler) hshpc
  integer i, ishape, iostat
  integer:: n_eddies = 50000
  logical:: mixed = .true.
  namelist /main_nml/ n_eddies, mixed

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

  call shpc_open(hshpc, shpc_dir = "SHPC", cyclone = .true., slice = 0, &
       pszaccess = "rb+", iostat = iostat)
  if (iostat /= 0) call shpc_create(hshpc, shpc_dir = "SHPC", &
       cyclone = .true., slice = 0, grid_lon_lat = .true.)
  print *, "Enter namelist main_nml."
  read(unit = *, nml = main_nml)

  if (mixed) then
     ! Alternate between shapefiles inside the loop on eddies:
     do i = 1, n_eddies
        call shp_append_point_03(ishape, hshpc%extremum, [0., 0.])
        call dbf_write_attribute_03(hshpc%extremum, ishape, hshpc%extr_ssh, 0.)
        call dbf_write_attribute_03(hshpc%extremum, ishape, hshpc%extr_date, 0)
        call dbf_write_attribute_03(hshpc%extremum, ishape, &
             hshpc%extr_eddy_index, i)
        call dbf_write_attribute_03(hshpc%extremum, ishape, hshpc%extr_speed, &
             0.)
        call shp_append_null_03(ishape, hshpc%outermost)
        call shp_append_null_03(ishape, hshpc%max_speed)
        call dbf_write_attribute_03(hshpc%outermost, ishape, &
             hshpc%out_r_eq_area, - 100.)
        call dbf_write_attribute_03(hshpc%outermost, ishape, hshpc%out_ssh, 0.)
        call dbf_write_attribute_03(hshpc%outermost, ishape, hshpc%out_date, 0)
        call dbf_write_attribute_03(hshpc%outermost, ishape, &
             hshpc%out_eddy_index, i)
        call dbf_write_attribute_03(hshpc%outermost, ishape, &
             hshpc%out_radius4, 0)
        call dbf_write_attribute_03(hshpc%max_speed, ishape, &
             hshpc%max_speed_r_eq_area, - 100.)
        call dbf_write_attribute_03(hshpc%max_speed, ishape, &
             hshpc%max_speed_ssh, 0.)
        call dbf_write_attribute_03(hshpc%max_speed, ishape, &
             hshpc%max_speed_date, 0)
        call dbf_write_attribute_03(hshpc%max_speed, ishape, &
             hshpc%max_speed_eddy_index, i)
     end do
  else
     ! Loop on eddies for each shapefile:
     
     do i = 1, n_eddies
        call shp_append_point_03(ishape, hshpc%extremum, [0., 0.])
        call dbf_write_attribute_03(hshpc%extremum, ishape, hshpc%extr_ssh, 0.)
        call dbf_write_attribute_03(hshpc%extremum, ishape, hshpc%extr_date, 0)
        call dbf_write_attribute_03(hshpc%extremum, ishape, &
             hshpc%extr_eddy_index, i)
        call dbf_write_attribute_03(hshpc%extremum, ishape, hshpc%extr_speed, &
             0.)
     end do

     do i = 1, n_eddies
        call shp_append_null_03(ishape, hshpc%outermost)
        call dbf_write_attribute_03(hshpc%outermost, ishape, &
             hshpc%out_r_eq_area, - 100.)
        call dbf_write_attribute_03(hshpc%outermost, ishape, hshpc%out_ssh, 0.)
        call dbf_write_attribute_03(hshpc%outermost, ishape, hshpc%out_date, 0)
        call dbf_write_attribute_03(hshpc%outermost, ishape, &
             hshpc%out_eddy_index, i)
        call dbf_write_attribute_03(hshpc%outermost, ishape, &
             hshpc%out_radius4, 0)
     end do

     do i = 1, n_eddies
        call shp_append_null_03(ishape, hshpc%max_speed)
        call dbf_write_attribute_03(hshpc%max_speed, ishape, &
             hshpc%max_speed_r_eq_area, - 100.)
        call dbf_write_attribute_03(hshpc%max_speed, ishape, &
             hshpc%max_speed_ssh, 0.)
        call dbf_write_attribute_03(hshpc%max_speed, ishape, &
             hshpc%max_speed_date, 0)
        call dbf_write_attribute_03(hshpc%max_speed, ishape, &
             hshpc%max_speed_eddy_index, i)
     end do
  end if

  CALL shpc_close(hshpc)

end program test_write_null