INTERFACE:
subroutine save_3d_ncdf(secs)DESCRIPTION:
USES:
use netcdf
use exceptions
use ncdf_3d
use grid_ncdf, only: xlen,ylen,zlen
use domain, only: ioff,joff,imin,imax,jmin,jmax,kmax
use domain, only: H,HU,HV,az,au,av,min_depth
use domain, only: convc
#if defined CURVILINEAR || defined SPHERICAL
use domain, only: dxv,dyu,arcd1
#else
use domain, only: dx,dy,ard1
#endif
use variables_2d, only: z,D
use variables_3d, only: Uavg, Vavg, Dun, Dvn
use variables_3d, only: dt,kmin,ho,hn,uu,hun,vv,hvn,ww,hcc,SS
use variables_3d, only: taubx,tauby
#ifdef _MOMENTUM_TERMS_
use variables_3d, only: tdv_u,adv_u,vsd_u,hsd_u,cor_u,epg_u,ipg_u
use variables_3d, only: tdv_v,adv_v,vsd_v,hsd_v,cor_v,epg_v,ipg_v
#endif
#ifndef NO_BAROCLINIC
use variables_3d, only: S,T,rho,rad,NN
#endif
use variables_3d, only: nummix3d_S,nummix3d_T,phymix3d_S,phymix3d_T
use variables_3d, only: numdis3d
use variables_3d, only: tke,num,nuh,eps
#ifdef SPM
use variables_3d, only: spm_pool,spm
#endif
#ifdef SPM
use suspended_matter, only: spm_save
#endif
#ifdef GETM_BIO
use bio_var, only: numc
use variables_3d, only: cc3d
#endif
#ifdef _FABM_
use getm_fabm,only: model,fabm_pel,fabm_ben,fabm_diag,fabm_diag_hz
#endif
use parameters, only: g,rho_0
use m3d, only: calc_temp,calc_salt
IMPLICIT NONE
INPUT PARAMETERS:
REALTYPE, intent(in) :: secs
!DEFINED PARAMTERS:
logical, parameter :: save3d=.true.
REVISION HISTORY:
Original author(s): Karsten Bolding & Hans BurchardLOCAL VARIABLES:
integer :: err,n
integer :: start(4),edges(4)
integer, save :: n3d=0
REALTYPE :: DONE(E2DFIELD)
REALTYPE :: dum(1)
integer :: i,j
REALTYPE :: uutmp(I3DFIELD),vvtmp(I3DFIELD)
#if defined(CURVILINEAR)
REALTYPE :: uurot(I3DFIELD),vvrot(I3DFIELD)
REALTYPE :: deg2rad = 3.141592654/180.
REALTYPE :: cosconv,sinconv
#endif
REALTYPE,dimension(E2DFIELD) :: ws2d
REALTYPE,dimension(I3DFIELD) :: ws