MODULE caldyn_hevi_mod USE icosa USE transfert_mod USE caldyn_kernels_base_mod USE caldyn_kernels_hevi_mod USE caldyn_gcm_mod IMPLICIT NONE PRIVATE PUBLIC caldyn_hevi CONTAINS SUBROUTINE caldyn_hevi(write_out,tau, f_phis, f_ps, f_mass, f_theta_rhodz, f_u, f_q, & f_W, f_geopot, f_hflux, f_wflux, f_dps, f_dmass, f_dtheta_rhodz, & f_du_slow, f_du_fast, f_dPhi_slow, f_dPhi_fast, f_dW_slow, f_dW_fast) USE icosa USE observable_mod USE disvert_mod, ONLY : caldyn_eta, eta_mass USE vorticity_mod USE kinetic_mod USE theta2theta_rhodz_mod USE wind_mod USE mpipara USE trace USE omp_para USE output_field_mod USE checksum_mod IMPLICIT NONE LOGICAL,INTENT(IN) :: write_out REAL(rstd), INTENT(IN) :: tau TYPE(t_field),POINTER :: f_phis(:) TYPE(t_field),POINTER :: f_ps(:) TYPE(t_field),POINTER :: f_mass(:) TYPE(t_field),POINTER :: f_theta_rhodz(:) TYPE(t_field),POINTER :: f_u(:) TYPE(t_field),POINTER :: f_q(:) TYPE(t_field),POINTER :: f_W(:) TYPE(t_field),POINTER :: f_geopot(:) TYPE(t_field),POINTER :: f_hflux(:), f_wflux(:) TYPE(t_field) :: f_dps(:) TYPE(t_field) :: f_dmass(:) TYPE(t_field) :: f_dtheta_rhodz(:) TYPE(t_field) :: f_du_slow(:) TYPE(t_field) :: f_du_fast(:) TYPE(t_field) :: f_dW_slow(:) TYPE(t_field) :: f_dW_fast(:) TYPE(t_field) :: f_dPhi_slow(:) TYPE(t_field) :: f_dPhi_fast(:) REAL(rstd),POINTER :: ps(:), dps(:) REAL(rstd),POINTER :: mass(:,:), theta_rhodz(:,:,:), dtheta_rhodz(:,:,:) REAL(rstd),POINTER :: du(:,:), dW(:,:), dPhi(:,:), hflux(:,:), wflux(:,:) REAL(rstd),POINTER :: u(:,:), w(:,:), qu(:,:), qv(:,:) ! temporary shared variable REAL(rstd),POINTER :: theta(:,:,:) REAL(rstd),POINTER :: pk(:,:) REAL(rstd),POINTER :: geopot(:,:) REAL(rstd),POINTER :: convm(:,:) REAL(rstd),POINTER :: wwuu(:,:) INTEGER :: ind LOGICAL,SAVE :: first=.TRUE. !$OMP THREADPRIVATE(first) IF (first) THEN first=.FALSE. IF(caldyn_eta==eta_mass) THEN CALL init_message(f_ps,req_i1,req_ps) ELSE CALL init_message(f_mass,req_i1,req_mass) END IF CALL init_message(f_theta_rhodz,req_i1,req_theta_rhodz) CALL init_message(f_u,req_e1_vect,req_u) CALL init_message(f_qu,req_e1_scal,req_qu) IF(.NOT.hydrostatic) THEN CALL init_message(f_geopot,req_i1,req_geopot) CALL init_message(f_w,req_i1,req_w) END IF ENDIF CALL trace_start("caldyn") IF(caldyn_eta==eta_mass) THEN CALL send_message(f_ps,req_ps) ! COM00 CALL wait_message(req_ps) ! COM00 ELSE CALL send_message(f_mass,req_mass) ! COM00 CALL wait_message(req_mass) ! COM00 END IF CALL send_message(f_theta_rhodz,req_theta_rhodz) ! COM01 CALL wait_message(req_theta_rhodz) ! COM01 Moved from caldyn_pvort IF(.NOT.hydrostatic) THEN CALL send_message(f_geopot,req_geopot) ! COM03 CALL wait_message(req_geopot) ! COM03 CALL send_message(f_w,req_w) ! COM04 CALL wait_message(req_w) ! COM04 END IF DO ind=1,ndomain IF (.NOT. assigned_domain(ind)) CYCLE CALL swap_dimensions(ind) CALL swap_geometry(ind) ps=f_ps(ind) theta_rhodz=f_theta_rhodz(ind) mass=f_mass(ind) theta = f_theta(ind) CALL compute_theta(ps,theta_rhodz, mass,theta) pk = f_pk(ind) geopot = f_geopot(ind) du=f_du_fast(ind) IF(hydrostatic) THEN du(:,:)=0. CALL compute_geopot(mass,theta, ps,pk,geopot) ELSE W = f_W(ind) dW = f_dW_fast(ind) dPhi = f_dPhi_fast(ind) CALL compute_caldyn_solver(tau,mass,theta,pk,geopot,W,dPhi,dW,du) ! computes d(Phi,W,du)_fast and updates Phi,W END IF u=f_u(ind) CALL compute_caldyn_fast(tau,u,mass,theta,pk,geopot,du) ! computes du_fast and updates u ENDDO CALL send_message(f_u,req_u) ! COM02 CALL wait_message(req_u) ! COM02 DO ind=1,ndomain IF (.NOT. assigned_domain(ind)) CYCLE CALL swap_dimensions(ind) CALL swap_geometry(ind) u=f_u(ind) mass=f_mass(ind) qu=f_qu(ind) qv=f_qv(ind) CALL compute_pvort_only(u,mass,qu,qv) ENDDO CALL send_message(f_qu,req_qu) ! COM03 CALL wait_message(req_qu) ! COM03 DO ind=1,ndomain IF (.NOT. assigned_domain(ind)) CYCLE CALL swap_dimensions(ind) CALL swap_geometry(ind) u=f_u(ind) mass=f_mass(ind) theta = f_theta(ind) qu=f_qu(ind) hflux=f_hflux(ind) convm = f_dmass(ind) dtheta_rhodz=f_dtheta_rhodz(ind) du=f_du_slow(ind) IF(hydrostatic) THEN CALL compute_caldyn_slow_hydro(u,mass,hflux,du, .TRUE.) ELSE W = f_W(ind) dW = f_dW_slow(ind) geopot = f_geopot(ind) dPhi = f_dPhi_slow(ind) CALL compute_caldyn_slow_NH(u,mass,geopot,W, hflux,du,dPhi,dW) END IF CALL compute_caldyn_Coriolis(hflux,theta,qu, convm,dtheta_rhodz,du) IF(caldyn_eta==eta_mass) THEN wflux=f_wflux(ind) wwuu=f_wwuu(ind) dps=f_dps(ind) CALL compute_caldyn_vert(u,theta,mass,convm, wflux,wwuu, dps, dtheta_rhodz, du) IF(.NOT.hydrostatic) THEN CALL compute_caldyn_vert_NH(mass,geopot,W,wflux, du,dPhi,dW) END IF END IF ENDDO !$OMP BARRIER ! CALL check_mass_conservation(f_ps,f_dps) CALL trace_end("caldyn_hevi") !!$OMP BARRIER END SUBROUTINE caldyn_hevi END MODULE caldyn_hevi_mod