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/2019/ENHANCE-02_ISF_nemo/src/OCE/TRA – NEMO

source: NEMO/branches/2019/ENHANCE-02_ISF_nemo/src/OCE/TRA/traisf.F90 @ 11908

Last change on this file since 11908 was 11908, checked in by mathiot, 4 years ago

ENHANCE-02_ISF_nemo: fix issue initialisation after ice sheet coupling step

File size: 6.4 KB
Line 
1MODULE traisf
2   !!==============================================================================
3   !!                       ***  MODULE  traisf  ***
4   !! Ocean active tracers:  ice shelf boundary condition
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   !!----------------------------------------------------------------------
12   USE oce            ! ocean dynamics and active tracers
13   USE dom_oce        ! ocean space domain variables
14   USE phycst         ! physical constant
15   USE eosbn2         ! Equation Of State
16   USE isf            ! Ice shelf variable
17   USE isfutils       !
18   !
19   USE in_out_manager ! I/O manager
20   USE iom            ! xIOS server
21   USE timing         ! Timing
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC   tra_isf   ! routine called by step.F90
27
28   !! * Substitutions
29#  include "vectopt_loop_substitute.h90"
30   !!----------------------------------------------------------------------
31   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
32   !! $Id: trasbc.F90 10499 2019-01-10 15:12:24Z deazer $
33   !! Software governed by the CeCILL license (see ./LICENSE)
34   !!----------------------------------------------------------------------
35CONTAINS
36
37   SUBROUTINE tra_isf ( kt )
38      !!----------------------------------------------------------------------
39      !!                  ***  ROUTINE tra_isf  ***
40      !!                   
41      !! ** Purpose :  Compute the temperature trend due to the ice shelf melting (qhoce + qhc)
42      !!
43      !! ** Action  : - update tsa for cav, par and cpl case
44      !!----------------------------------------------------------------------
45      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
46      !!----------------------------------------------------------------------
47      !
48      IF( ln_timing )   CALL timing_start('tra_isf')
49      !
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
55      !
56      ! cavity case
57      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)
58      !
59      ! parametrisation case
60      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)
61      !
62      ! ice sheet coupling case
63      IF ( ln_isfcpl ) THEN
64         !
65         IF ( kt == nit000  ) CALL tra_isf_cpl(risfcpl_tsc       , tsa)
66         IF ( kt == nit000+1) CALL tra_isf_cpl(risfcpl_tsc*0.5_wp, tsa)
67         !
68         ! ensure 0 trend due to unconservation of the ice shelf coupling
69         IF ( ln_isfcpl_cons ) CALL tra_isf_cpl(risfcpl_cons_tsc, tsa)
70
71         IF ( ln_isfdebug ) THEN
72            CALL debug('tra_isf: risfcpl_tsc T',risfcpl_tsc(:,:,1))
73            CALL debug('tra_isf: risfcpl_tsc S',risfcpl_tsc(:,:,2))
74         END IF
75         !
76      END IF
77      !
78      IF ( ln_isfdebug ) THEN
79         CALL debug('tra_isf: tsa T'        ,tsa(:,:,:,1))
80         CALL debug('tra_isf: tsa S'        ,tsa(:,:,:,2))
81      END IF
82      !
83      IF( ln_timing )   CALL timing_stop('tra_isf')
84      !
85   END SUBROUTINE tra_isf
86   !
87   SUBROUTINE tra_isf_mlt(ktop, kbot, phtbl, pfrac, ptsc, ptsc_b, pts)
88      !!----------------------------------------------------------------------
89      !!                  ***  ROUTINE tra_isf_mlt  ***
90      !!
91      !! *** Purpose :  Compute the temperature trend due to the ice shelf melting (qhoce + qhc) for cav or par case
92      !!
93      !! *** Action :: Update tsa with the surface boundary condition trend
94      !!
95      !!----------------------------------------------------------------------
96      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(inout) :: pts
97      !!----------------------------------------------------------------------
98      INTEGER , DIMENSION(jpi,jpj)     , INTENT(in   ) :: ktop , kbot
99      REAL(wp), DIMENSION(jpi,jpj)     , INTENT(in   ) :: phtbl, pfrac
100      REAL(wp), DIMENSION(jpi,jpj,jpts), INTENT(in   ) :: ptsc , ptsc_b
101      !!----------------------------------------------------------------------
102      INTEGER                      :: ji,jj,jk  ! loop index   
103      INTEGER                      :: ikt, ikb  ! top and bottom level of the tbl
104      REAL(wp), DIMENSION(jpi,jpj) :: ztc       ! total ice shelf tracer trend
105      !!----------------------------------------------------------------------
106      !
107      ! compute 2d total trend due to isf
108      ztc(:,:) = 0.5_wp * ( ptsc(:,:,jp_tem) + ptsc_b(:,:,jp_tem) ) / phtbl(:,:)
109      !
110      ! update tsa
111      DO jj = 1,jpj
112         DO ji = 1,jpi
113            !
114            ikt = ktop(ji,jj)
115            ikb = kbot(ji,jj)
116            !
117            ! level fully include in the ice shelf boundary layer
118            DO jk = ikt, ikb - 1
119               pts(ji,jj,jk,jp_tem) = pts(ji,jj,jk,jp_tem) + ztc(ji,jj)
120            END DO
121            !
122            ! level partially include in ice shelf boundary layer
123            pts(ji,jj,ikb,jp_tem) = pts(ji,jj,ikb,jp_tem) + ztc(ji,jj) * pfrac(ji,jj)
124            !
125         END DO
126      END DO
127      !
128   END SUBROUTINE tra_isf_mlt
129   !
130   SUBROUTINE tra_isf_cpl( ptsc, ptsa )
131      !!----------------------------------------------------------------------
132      !!                  ***  ROUTINE tra_isf_cpl  ***
133      !!
134      !! *** Action :: Update tsa with the ice shelf coupling trend
135      !!
136      !!----------------------------------------------------------------------
137      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(inout) :: ptsa
138      !!----------------------------------------------------------------------
139      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts), INTENT(in   ) :: ptsc
140      !!----------------------------------------------------------------------
141      INTEGER :: jk
142      !!----------------------------------------------------------------------
143      !
144      DO jk = 1,jpk
145         ptsa(:,:,jk,jp_tem) = ptsa(:,:,jk,jp_tem) + ptsc(:,:,jk,jp_tem) * r1_e1e2t(:,:) / e3t_n(:,:,jk)
146         ptsa(:,:,jk,jp_sal) = ptsa(:,:,jk,jp_sal) + ptsc(:,:,jk,jp_sal) * r1_e1e2t(:,:) / e3t_n(:,:,jk)
147      END DO
148      !
149   END SUBROUTINE tra_isf_cpl
150   !
151END MODULE traisf
Note: See TracBrowser for help on using the repository browser.