MODULE traisf !!============================================================================== !! *** MODULE traisf *** !! Ocean active tracers: ice shelf boundary condition !!============================================================================== !! History : 4.0 ! 2019-09 (P. Mathiot) original file !!---------------------------------------------------------------------- !!---------------------------------------------------------------------- !! tra_isf : update the tracer trend at ocean surface !!---------------------------------------------------------------------- USE oce ! ocean dynamics and active tracers USE dom_oce ! ocean space domain variables USE phycst ! physical constant USE eosbn2 ! Equation Of State USE isf ! Ice shelf variable USE isfutils ! ! USE in_out_manager ! I/O manager USE iom ! xIOS server USE timing ! Timing IMPLICIT NONE PRIVATE PUBLIC tra_isf ! routine called by step.F90 !! * Substitutions # include "vectopt_loop_substitute.h90" !!---------------------------------------------------------------------- !! NEMO/OCE 4.0 , NEMO Consortium (2018) !! $Id: trasbc.F90 10499 2019-01-10 15:12:24Z deazer $ !! Software governed by the CeCILL license (see ./LICENSE) !!---------------------------------------------------------------------- CONTAINS SUBROUTINE tra_isf ( kt ) !!---------------------------------------------------------------------- !! *** ROUTINE tra_isf *** !! !! ** Purpose : Compute the temperature trend due to the ice shelf melting (qhoce + qhc) !! !! ** Action : - update tsa for cav, par and cpl case !!---------------------------------------------------------------------- INTEGER, INTENT(in) :: kt ! ocean time-step index !!---------------------------------------------------------------------- ! IF( ln_timing ) CALL timing_start('tra_sbc') ! ! cavity case IF ( ln_isfcav_mlt ) CALL tra_isf_mlt(misfkt_cav, misfkb_cav, rhisf_tbl_cav, rfrac_tbl_cav, risf_cav_tsc, risf_cav_tsc_b, tsa) ! ! parametrisation case IF ( ln_isfpar_mlt ) CALL tra_isf_mlt(misfkt_par, misfkb_par, rhisf_tbl_par, rfrac_tbl_par, risf_par_tsc, risf_par_tsc_b, tsa) ! ! ice sheet coupling case IF ( ll_isfcpl .AND. kt == nit000 ) CALL tra_isf_cpl(risfcpl_tsc, tsa) ! ! ice sheet coupling case ( IF ( ll_isfcpl_cons ) CALL tra_isf_cpl(risfcpl_cons_tsc, tsa) ! IF( ln_timing ) CALL timing_stop('tra_isf') ! END SUBROUTINE tra_isf ! SUBROUTINE tra_isf_mlt(ktop, kbot, phtbl, pfrac, ptsc, ptsc_b, pts) !!---------------------------------------------------------------------- !! *** ROUTINE tra_isf_mlt *** !! !! *** Purpose : Compute the temperature trend due to the ice shelf melting (qhoce + qhc) for cav or par case !! !! *** Action :: Update tsa with the surface boundary condition trend !! !!---------------------------------------------------------------------- REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(inout) :: pts !!---------------------------------------------------------------------- INTEGER , DIMENSION(jpi,jpj) , INTENT(in ) :: ktop , kbot REAL(wp), DIMENSION(jpi,jpj) , INTENT(in ) :: phtbl, pfrac REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in ) :: ptsc , ptsc_b !!---------------------------------------------------------------------- INTEGER :: ji,jj,jk ! loop index INTEGER :: ikt, ikb ! top and bottom level of the tbl REAL(wp), DIMENSION(jpi,jpj) :: ztc ! total ice shelf tracer trend !!---------------------------------------------------------------------- ! ! compute 2d total trend due to isf ztc(:,:) = 0.5_wp * ( ptsc(:,:,jp_tem) + ptsc_b(:,:,jp_tem) ) / phtbl(:,:) ! ! update tsa DO jj = 1,jpj DO ji = 1,jpi ! ikt = ktop(ji,jj) ikb = kbot(ji,jj) ! ! level fully include in the ice shelf boundary layer ! sign - because fwf sign of evapo (rnf sign of precip) DO jk = ikt, ikb - 1 pts(ji,jj,jk,jp_tem) = pts(ji,jj,jk,jp_tem) + ztc(ji,jj) END DO ! ! level partially include in ice shelf boundary layer pts(ji,jj,ikb,jp_tem) = pts(ji,jj,ikb,jp_tem) + ztc(ji,jj) * pfrac(ji,jj) ! END DO END DO ! END SUBROUTINE tra_isf_mlt ! SUBROUTINE tra_isf_cpl( ptsc, ptsa ) !!---------------------------------------------------------------------- !! *** ROUTINE tra_isf_cpl *** !! !! *** Action :: Update tsa with the ice shelf coupling trend !! !!---------------------------------------------------------------------- REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(inout) :: ptsa !!---------------------------------------------------------------------- REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in ) :: ptsc !( >0 out ) !!---------------------------------------------------------------------- INTEGER :: jk !!---------------------------------------------------------------------- ! DO jk = 1,jpk ptsa(:,:,jk,jp_tem) = ptsa(:,:,jk,jp_tem) - ptsc(:,:,jk,jp_tem) * r1_e1e2t(:,:) / e3t_n(:,:,jk) ptsa(:,:,jk,jp_sal) = ptsa(:,:,jk,jp_sal) - ptsc(:,:,jk,jp_sal) * r1_e1e2t(:,:) / e3t_n(:,:,jk) END DO ! END SUBROUTINE tra_isf_cpl ! END MODULE traisf