Newer
Older
program test_read_eddy
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
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)
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)
call write_eddy(e, hshp_out, k, eddy_i)
print *, 'Created shapefiles in SHPC.'
end program test_read_eddy