Skip to content
Snippets Groups Projects
test_read_eddy.f90 1.33 KiB
Newer Older
Lionel GUEZ's avatar
Lionel GUEZ committed
  use jumble, only: get_command_arg_dyn
  use derived_types, only: eddy, shpc_slice_handler
  use read_eddy_m, only: read_eddy
  use read_grid_m, only: read_grid, uniform_lon_lat
  use shpc_close_m, only: shpc_close
  use shpc_create_m, only: shpc_create
  use shpc_open_m, only: shpc_open
  use write_eddy_m, only: write_eddy

  implicit none

  type(eddy) e
Lionel GUEZ's avatar
Lionel GUEZ committed
  integer k, eddy_i
  integer:: ishape = 0
  TYPE(shpc_slice_handler) hshp_in, hshp_out
  character(len = :), allocatable:: shpc_dir
  logical:: cyclone = .false.
  namelist /main_nml/ ishape, cyclone

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

  call get_command_arg_dyn(1, shpc_dir, "Required argument: SHPC-directory")
  call read_grid(shpc_dir, rank = 0)
  print *, "Enter namelist main_nml."
  read(unit = *, nml = main_nml)
GUEZ Lionel's avatar
GUEZ Lionel committed
  call shpc_open(hshp_in, shpc_dir, cyclone, slice = 0, &
       with_proj = .not. uniform_lon_lat, pszaccess = "rb")
  call read_eddy(e, k, eddy_i, hshp_in, ishape)
  call shpc_create(hshp_out, shpc_dir = "SHPC", cyclone = hshp_in%cyclone, &
       slice = 0, with_proj = .not. uniform_lon_lat)
Lionel GUEZ's avatar
Lionel GUEZ committed
  CALL shpc_close(hshp_in)
  call write_eddy(e, hshp_out, k, eddy_i)
  write(hshp_out%unit, fmt = *) 0
  CALL shpc_close(hshp_out)
  print *, 'Created shapefiles in SHPC.'