New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
traisf.F90 in NEMO/branches/2020/dev_r13333_KERNEL-08_techene_gm_HPG_SPG/src/OCE/TRA – NEMO

source: NEMO/branches/2020/dev_r13333_KERNEL-08_techene_gm_HPG_SPG/src/OCE/TRA/traisf.F90 @ 14037

Last change on this file since 14037 was 14037, checked in by ayoung, 3 years ago

Updated to trunk at 14020. Sette tests passed with change of results for configurations with non-linear ssh. Ticket #2506.

File size: 7.6 KB
RevLine 
[11395]1MODULE traisf
2   !!==============================================================================
[11403]3   !!                       ***  MODULE  traisf  ***
4   !! Ocean active tracers:  ice shelf boundary condition
[11395]5   !!==============================================================================
6   !! History :    4.0  !  2019-09  (P. Mathiot) original file
7   !!----------------------------------------------------------------------
8
9   !!----------------------------------------------------------------------
10   !!   tra_isf       : update the tracer trend at ocean surface
11   !!----------------------------------------------------------------------
[12077]12   USE isf_oce                                     ! Ice shelf variables
[14037]13   USE par_oce , ONLY : nijtile, ntile, ntsi, ntei, ntsj, ntej
[13237]14   USE dom_oce                                     ! ocean space domain variables
[12077]15   USE isfutils, ONLY : debug                      ! debug option
16   USE timing  , ONLY : timing_start, timing_stop  ! Timing
17   USE in_out_manager                              ! I/O manager
[11395]18
19   IMPLICIT NONE
20   PRIVATE
21
22   PUBLIC   tra_isf   ! routine called by step.F90
23
24   !! * Substitutions
[12340]25#  include "do_loop_substitute.h90"
[13237]26#  include "domzgr_substitute.h90"
[11395]27   !!----------------------------------------------------------------------
28   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
29   !! $Id: trasbc.F90 10499 2019-01-10 15:12:24Z deazer $
30   !! Software governed by the CeCILL license (see ./LICENSE)
31   !!----------------------------------------------------------------------
32CONTAINS
33
[12068]34   SUBROUTINE tra_isf ( kt, Kmm, pts, Krhs )
[11395]35      !!----------------------------------------------------------------------
[11403]36      !!                  ***  ROUTINE tra_isf  ***
[11395]37      !!                   
[11403]38      !! ** Purpose :  Compute the temperature trend due to the ice shelf melting (qhoce + qhc)
[11395]39      !!
[12068]40      !! ** Action  : - update pts(:,:,:,:,Krhs) for cav, par and cpl case
[11395]41      !!----------------------------------------------------------------------
[12068]42      INTEGER                                  , INTENT(in   ) :: kt        ! ocean time step
43      INTEGER                                  , INTENT(in   ) :: Kmm, Krhs ! ocean time level indices
44      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts       ! active tracers and RHS of tracer equation
[11395]45      !!----------------------------------------------------------------------
46      !
[11529]47      IF( ln_timing )   CALL timing_start('tra_isf')
[11395]48      !
[14037]49      IF( ntile == 0 .OR. ntile == 1 )  THEN                       ! Do only on the first tile
50         IF( kt == nit000 ) THEN
51            IF(lwp) WRITE(numout,*)
52            IF(lwp) WRITE(numout,*) 'tra_isf : Ice shelf heat fluxes'
53            IF(lwp) WRITE(numout,*) '~~~~~~~ '
54         ENDIF
[11902]55      ENDIF
56      !
[11541]57      ! cavity case
[12068]58      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, pts(:,:,:,:,Krhs))
[11403]59      !
[11541]60      ! parametrisation case
[12068]61      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, pts(:,:,:,:,Krhs))
[11541]62      !
[11403]63      ! ice sheet coupling case
[11541]64      IF ( ln_isfcpl ) THEN
[11521]65         !
[12077]66         ! Dynamical stability at start up after change in under ice shelf cavity geometry is achieve by correcting the divergence.
67         ! This is achieved by applying a volume flux in order to keep the horizontal divergence after remapping
68         ! the same as at the end of the latest time step. So correction need to be apply at nit000 (euler time step) and
69         ! half of it at nit000+1 (leap frog time step).
70         ! in accordance to this, the heat content flux due to injected water need to be added in the temperature and salt trend
71         ! at time step nit000 and nit000+1
[12068]72         IF ( kt == nit000  ) CALL tra_isf_cpl(Kmm, risfcpl_tsc       , pts(:,:,:,:,Krhs))
73         IF ( kt == nit000+1) CALL tra_isf_cpl(Kmm, risfcpl_tsc*0.5_wp, pts(:,:,:,:,Krhs))
[11521]74         !
75         ! ensure 0 trend due to unconservation of the ice shelf coupling
[12068]76         IF ( ln_isfcpl_cons ) CALL tra_isf_cpl(Kmm, risfcpl_cons_tsc, pts(:,:,:,:,Krhs))
[11521]77         !
78      END IF
[11395]79      !
[11902]80      IF ( ln_isfdebug ) THEN
[14037]81         IF( ntile == 0 .OR. ntile == nijtile ) THEN                       ! Do only for the full domain
82            CALL debug('tra_isf: pts(:,:,:,:,Krhs) T', pts(:,:,:,1,Krhs))
83            CALL debug('tra_isf: pts(:,:,:,:,Krhs) S', pts(:,:,:,2,Krhs))
84         ENDIF
[11902]85      END IF
86      !
[11395]87      IF( ln_timing )   CALL timing_stop('tra_isf')
88      !
89   END SUBROUTINE tra_isf
90   !
91   SUBROUTINE tra_isf_mlt(ktop, kbot, phtbl, pfrac, ptsc, ptsc_b, pts)
92      !!----------------------------------------------------------------------
[11403]93      !!                  ***  ROUTINE tra_isf_mlt  ***
94      !!
95      !! *** Purpose :  Compute the temperature trend due to the ice shelf melting (qhoce + qhc) for cav or par case
96      !!
[12068]97      !! *** Action :: Update pts(:,:,:,:,Krhs) with the surface boundary condition trend
[11403]98      !!
99      !!----------------------------------------------------------------------
[11395]100      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(inout) :: pts
101      !!----------------------------------------------------------------------
102      INTEGER , DIMENSION(jpi,jpj)     , INTENT(in   ) :: ktop , kbot
103      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(in   ) :: phtbl, pfrac
104      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in   ) :: ptsc , ptsc_b
105      !!----------------------------------------------------------------------
[11403]106      INTEGER                      :: ji,jj,jk  ! loop index   
107      INTEGER                      :: ikt, ikb  ! top and bottom level of the tbl
[14037]108      REAL(wp), DIMENSION(A2D(nn_hls))     :: ztc       ! total ice shelf tracer trend
[11403]109      !!----------------------------------------------------------------------
[11395]110      !
111      ! compute 2d total trend due to isf
[14037]112      DO_2D( 0, 0, 0, 0 )
113         ztc(ji,jj) = 0.5_wp * ( ptsc(ji,jj,jp_tem) + ptsc_b(ji,jj,jp_tem) ) / phtbl(ji,jj)
114      END_2D
[11395]115      !
[12068]116      ! update pts(:,:,:,:,Krhs)
[14037]117      DO_2D( 0, 0, 0, 0 )
[12340]118         !
119         ikt = ktop(ji,jj)
120         ikb = kbot(ji,jj)
121         !
122         ! level fully include in the ice shelf boundary layer
123         DO jk = ikt, ikb - 1
124            pts(ji,jj,jk,jp_tem) = pts(ji,jj,jk,jp_tem) + ztc(ji,jj)
[11395]125         END DO
[12340]126         !
127         ! level partially include in ice shelf boundary layer
128         pts(ji,jj,ikb,jp_tem) = pts(ji,jj,ikb,jp_tem) + ztc(ji,jj) * pfrac(ji,jj)
129         !
130      END_2D
[11395]131      !
132   END SUBROUTINE tra_isf_mlt
133   !
[12068]134   SUBROUTINE tra_isf_cpl( Kmm, ptsc, ptsa )
[11423]135      !!----------------------------------------------------------------------
136      !!                  ***  ROUTINE tra_isf_cpl  ***
137      !!
[12068]138      !! *** Action :: Update pts(:,:,:,:,Krhs) with the ice shelf coupling trend
[11423]139      !!
140      !!----------------------------------------------------------------------
141      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(inout) :: ptsa
142      !!----------------------------------------------------------------------
[12068]143      INTEGER                              , INTENT(in   ) :: Kmm   ! ocean time level index
[11521]144      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) :: ptsc
[11423]145      !!----------------------------------------------------------------------
[14037]146      INTEGER :: ji, jj, jk
[11423]147      !!----------------------------------------------------------------------
148      !
[14037]149      DO_3D( 0, 0, 0, 0, 1, jpk )
150         ptsa(ji,jj,jk,jp_tem) = ptsa(ji,jj,jk,jp_tem) + ptsc(ji,jj,jk,jp_tem) * r1_e1e2t(ji,jj) / e3t(ji,jj,jk,Kmm)
151         ptsa(ji,jj,jk,jp_sal) = ptsa(ji,jj,jk,jp_sal) + ptsc(ji,jj,jk,jp_sal) * r1_e1e2t(ji,jj) / e3t(ji,jj,jk,Kmm)
152      END_3D
[11423]153      !
154   END SUBROUTINE tra_isf_cpl
[11395]155   !
156END MODULE traisf
Note: See TracBrowser for help on using the repository browser.