-
Lionel GUEZ authored
Use out_cont%closed instead.
Lionel GUEZ authoredUse out_cont%closed instead.
write_snapshot.f90 1.19 KiB
module write_snapshot_m
implicit none
contains
subroutine write_snapshot(s, hshpc_cyclo, hshpc_anti, date)
! Libraries:
use shapelib_03, only: shp_get_info_03
use derived_types, only: snapshot, shpc_slice_handler
use write_eddy_m, only: write_eddy
type(snapshot), intent(in):: s
TYPE(shpc_slice_handler), intent(in):: hshpc_cyclo, hshpc_anti
integer, intent(in):: date
! Local:
integer i, n_cyclo, n_anti, n_entities
!-----------------------------------------------------------------
n_cyclo = 0
n_anti = 0
do i = 1, s%number_extr
if (s%list(i)%out_cont%closed) then
if (s%list(i)%cyclone) then
n_cyclo = n_cyclo + 1
call write_eddy(s%list(i), hshpc_cyclo, date, n_cyclo)
else
n_anti = n_anti + 1
call write_eddy(s%list(i), hshpc_anti, date, n_anti)
end if
end if
end do
call shp_get_info_03(hshpc_cyclo%extremum, n_entities)
write(hshpc_cyclo%unit, fmt = *) n_entities - 1
call shp_get_info_03(hshpc_anti%extremum, n_entities)
write(hshpc_anti%unit, fmt = *) n_entities - 1
end subroutine write_snapshot
end module write_snapshot_m