1 | MODULE trasbc |
---|
2 | !!============================================================================== |
---|
3 | !! *** MODULE trasbc *** |
---|
4 | !! Ocean active tracers: surface boundary condition |
---|
5 | !!============================================================================== |
---|
6 | !! History : OPA ! 1998-10 (G. Madec, G. Roullet, M. Imbard) Original code |
---|
7 | !! 8.2 ! 2001-02 (D. Ludicone) sea ice and free surface |
---|
8 | !! NEMO 1.0 ! 2002-06 (G. Madec) F90: Free form and module |
---|
9 | !! 3.3 ! 2010-04 (M. Leclair, G. Madec) Forcing averaged over 2 time steps |
---|
10 | !! - ! 2010-09 (C. Ethe, G. Madec) Merge TRA-TRC |
---|
11 | !! 3.6 ! 2014-11 (P. Mathiot) isf melting forcing |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | |
---|
14 | !!---------------------------------------------------------------------- |
---|
15 | !! tra_sbc : update the tracer trend at ocean surface |
---|
16 | !!---------------------------------------------------------------------- |
---|
17 | USE oce ! ocean dynamics and active tracers |
---|
18 | USE sbc_oce ! surface boundary condition: ocean |
---|
19 | USE dom_oce ! ocean space domain variables |
---|
20 | USE phycst ! physical constant |
---|
21 | USE eosbn2 ! Equation Of State |
---|
22 | USE sbcmod ! ln_rnf |
---|
23 | USE sbcrnf ! River runoff |
---|
24 | USE sbcisf ! Ice shelf |
---|
25 | USE iscplini ! Ice sheet coupling |
---|
26 | USE traqsr ! solar radiation penetration |
---|
27 | USE trd_oce ! trends: ocean variables |
---|
28 | USE trdtra ! trends manager: tracers |
---|
29 | ! |
---|
30 | USE in_out_manager ! I/O manager |
---|
31 | USE prtctl ! Print control |
---|
32 | USE iom ! xIOS server |
---|
33 | USE lbclnk ! ocean lateral boundary conditions (or mpp link) |
---|
34 | USE wrk_nemo ! Memory Allocation |
---|
35 | USE timing ! Timing |
---|
36 | USE iom_def, ONLY : lwxios |
---|
37 | |
---|
38 | IMPLICIT NONE |
---|
39 | PRIVATE |
---|
40 | |
---|
41 | PUBLIC tra_sbc ! routine called by step.F90 |
---|
42 | |
---|
43 | !! * Substitutions |
---|
44 | # include "vectopt_loop_substitute.h90" |
---|
45 | !!---------------------------------------------------------------------- |
---|
46 | !! NEMO/OPA 3.7 , NEMO Consortium (2014) |
---|
47 | !! $Id$ |
---|
48 | !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) |
---|
49 | !!---------------------------------------------------------------------- |
---|
50 | CONTAINS |
---|
51 | |
---|
52 | SUBROUTINE tra_sbc ( kt ) |
---|
53 | !!---------------------------------------------------------------------- |
---|
54 | !! *** ROUTINE tra_sbc *** |
---|
55 | !! |
---|
56 | !! ** Purpose : Compute the tracer surface boundary condition trend of |
---|
57 | !! (flux through the interface, concentration/dilution effect) |
---|
58 | !! and add it to the general trend of tracer equations. |
---|
59 | !! |
---|
60 | !! ** Method : The (air+ice)-sea flux has two components: |
---|
61 | !! (1) Fext, external forcing (i.e. flux through the (air+ice)-sea interface); |
---|
62 | !! (2) Fwe , tracer carried with the water that is exchanged with air+ice. |
---|
63 | !! The input forcing fields (emp, rnf, sfx, isf) contain Fext+Fwe, |
---|
64 | !! they are simply added to the tracer trend (tsa). |
---|
65 | !! In linear free surface case (ln_linssh=T), the volume of the |
---|
66 | !! ocean does not change with the water exchanges at the (air+ice)-sea |
---|
67 | !! interface. Therefore another term has to be added, to mimic the |
---|
68 | !! concentration/dilution effect associated with water exchanges. |
---|
69 | !! |
---|
70 | !! ** Action : - Update tsa with the surface boundary condition trend |
---|
71 | !! - send trends to trdtra module for further diagnostics(l_trdtra=T) |
---|
72 | !!---------------------------------------------------------------------- |
---|
73 | INTEGER, INTENT(in) :: kt ! ocean time-step index |
---|
74 | ! |
---|
75 | INTEGER :: ji, jj, jk, jn ! dummy loop indices |
---|
76 | INTEGER :: ikt, ikb ! local integers |
---|
77 | REAL(wp) :: zfact, z1_e3t, zdep ! local scalar |
---|
78 | REAL(wp), POINTER, DIMENSION(:,:,:) :: ztrdt, ztrds |
---|
79 | !!---------------------------------------------------------------------- |
---|
80 | ! |
---|
81 | IF( nn_timing == 1 ) CALL timing_start('tra_sbc') |
---|
82 | ! |
---|
83 | IF( kt == nit000 ) THEN |
---|
84 | IF(lwp) WRITE(numout,*) |
---|
85 | IF(lwp) WRITE(numout,*) 'tra_sbc : TRAcer Surface Boundary Condition' |
---|
86 | IF(lwp) WRITE(numout,*) '~~~~~~~ ' |
---|
87 | ENDIF |
---|
88 | ! |
---|
89 | IF( l_trdtra ) THEN !* Save ta and sa trends |
---|
90 | CALL wrk_alloc( jpi, jpj, jpk, ztrdt, ztrds ) |
---|
91 | ztrdt(:,:,:) = tsa(:,:,:,jp_tem) |
---|
92 | ztrds(:,:,:) = tsa(:,:,:,jp_sal) |
---|
93 | ENDIF |
---|
94 | ! |
---|
95 | !!gm This should be moved into sbcmod.F90 module ? (especially now that ln_traqsr is read in namsbc namelist) |
---|
96 | IF( .NOT.ln_traqsr ) THEN ! no solar radiation penetration |
---|
97 | qns(:,:) = qns(:,:) + qsr(:,:) ! total heat flux in qns |
---|
98 | qsr(:,:) = 0._wp ! qsr set to zero |
---|
99 | ENDIF |
---|
100 | |
---|
101 | !---------------------------------------- |
---|
102 | ! EMP, SFX and QNS effects |
---|
103 | !---------------------------------------- |
---|
104 | ! !== Set before sbc tracer content fields ==! |
---|
105 | IF( kt == nit000 ) THEN !* 1st time-step |
---|
106 | IF( ln_rstart .AND. & ! Restart: read in restart file |
---|
107 | & iom_varid( numror, 'sbc_hc_b', ldstop = .FALSE. ) > 0 ) THEN |
---|
108 | IF(lwp) WRITE(numout,*) ' nit000-1 sbc tracer content field read in the restart file' |
---|
109 | zfact = 0.5_wp |
---|
110 | sbc_tsc(:,:,:) = 0._wp |
---|
111 | CALL iom_get( numror, jpdom_autoglo, 'sbc_hc_b', sbc_tsc_b(:,:,jp_tem) ) ! before heat content sbc trend |
---|
112 | CALL iom_get( numror, jpdom_autoglo, 'sbc_sc_b', sbc_tsc_b(:,:,jp_sal) ) ! before salt content sbc trend |
---|
113 | ELSE ! No restart or restart not found: Euler forward time stepping |
---|
114 | zfact = 1._wp |
---|
115 | sbc_tsc(:,:,:) = 0._wp |
---|
116 | sbc_tsc_b(:,:,:) = 0._wp |
---|
117 | ENDIF |
---|
118 | ELSE !* other time-steps: swap of forcing fields |
---|
119 | zfact = 0.5_wp |
---|
120 | sbc_tsc_b(:,:,:) = sbc_tsc(:,:,:) |
---|
121 | ENDIF |
---|
122 | ! !== Now sbc tracer content fields ==! |
---|
123 | DO jj = 2, jpj |
---|
124 | DO ji = fs_2, fs_jpim1 ! vector opt. |
---|
125 | sbc_tsc(ji,jj,jp_tem) = r1_rau0_rcp * qns(ji,jj) ! non solar heat flux |
---|
126 | sbc_tsc(ji,jj,jp_sal) = r1_rau0 * sfx(ji,jj) ! salt flux due to freezing/melting |
---|
127 | END DO |
---|
128 | END DO |
---|
129 | IF( ln_linssh ) THEN !* linear free surface |
---|
130 | DO jj = 2, jpj !==>> add concentration/dilution effect due to constant volume cell |
---|
131 | DO ji = fs_2, fs_jpim1 ! vector opt. |
---|
132 | sbc_tsc(ji,jj,jp_tem) = sbc_tsc(ji,jj,jp_tem) + r1_rau0 * emp(ji,jj) * tsn(ji,jj,1,jp_tem) |
---|
133 | sbc_tsc(ji,jj,jp_sal) = sbc_tsc(ji,jj,jp_sal) + r1_rau0 * emp(ji,jj) * tsn(ji,jj,1,jp_sal) |
---|
134 | END DO |
---|
135 | END DO !==>> output c./d. term |
---|
136 | IF( iom_use('emp_x_sst') ) CALL iom_put( "emp_x_sst", emp (:,:) * tsn(:,:,1,jp_tem) ) |
---|
137 | IF( iom_use('emp_x_sss') ) CALL iom_put( "emp_x_sss", emp (:,:) * tsn(:,:,1,jp_sal) ) |
---|
138 | ENDIF |
---|
139 | ! |
---|
140 | DO jn = 1, jpts !== update tracer trend ==! |
---|
141 | DO jj = 2, jpj |
---|
142 | DO ji = fs_2, fs_jpim1 ! vector opt. |
---|
143 | tsa(ji,jj,1,jn) = tsa(ji,jj,1,jn) + zfact * ( sbc_tsc_b(ji,jj,jn) + sbc_tsc(ji,jj,jn) ) / e3t_n(ji,jj,1) |
---|
144 | END DO |
---|
145 | END DO |
---|
146 | END DO |
---|
147 | ! |
---|
148 | IF( lrst_oce ) THEN !== write sbc_tsc in the ocean restart file ==! |
---|
149 | IF( lwxios ) CALL iom_swap( cwxios_context ) |
---|
150 | CALL iom_rstput( kt, nitrst, numrow, 'sbc_hc_b', sbc_tsc(:,:,jp_tem), ldxios = lwxios ) |
---|
151 | CALL iom_rstput( kt, nitrst, numrow, 'sbc_sc_b', sbc_tsc(:,:,jp_sal), ldxios = lwxios ) |
---|
152 | IF( lwxios ) CALL iom_swap( cxios_context ) |
---|
153 | ENDIF |
---|
154 | ! |
---|
155 | !---------------------------------------- |
---|
156 | ! Ice Shelf effects (ISF) |
---|
157 | ! tbl treated as in Losh (2008) JGR |
---|
158 | !---------------------------------------- |
---|
159 | ! |
---|
160 | !!gm BUG ? Why no differences between non-linear and linear free surface ? |
---|
161 | !!gm probably taken into account in r1_hisf_tbl : to be verified |
---|
162 | IF( ln_isf ) THEN |
---|
163 | zfact = 0.5_wp |
---|
164 | DO jj = 2, jpj |
---|
165 | DO ji = fs_2, fs_jpim1 |
---|
166 | ! |
---|
167 | ikt = misfkt(ji,jj) |
---|
168 | ikb = misfkb(ji,jj) |
---|
169 | ! |
---|
170 | ! level fully include in the ice shelf boundary layer |
---|
171 | ! sign - because fwf sign of evapo (rnf sign of precip) |
---|
172 | DO jk = ikt, ikb - 1 |
---|
173 | ! compute trend |
---|
174 | tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) & |
---|
175 | & + zfact * ( risf_tsc_b(ji,jj,jp_tem) + risf_tsc(ji,jj,jp_tem) ) & |
---|
176 | & * r1_hisf_tbl(ji,jj) |
---|
177 | END DO |
---|
178 | |
---|
179 | ! level partially include in ice shelf boundary layer |
---|
180 | ! compute trend |
---|
181 | tsa(ji,jj,ikb,jp_tem) = tsa(ji,jj,ikb,jp_tem) & |
---|
182 | & + zfact * ( risf_tsc_b(ji,jj,jp_tem) + risf_tsc(ji,jj,jp_tem) ) & |
---|
183 | & * r1_hisf_tbl(ji,jj) * ralpha(ji,jj) |
---|
184 | |
---|
185 | END DO |
---|
186 | END DO |
---|
187 | END IF |
---|
188 | ! |
---|
189 | !---------------------------------------- |
---|
190 | ! River Runoff effects |
---|
191 | !---------------------------------------- |
---|
192 | ! |
---|
193 | IF( ln_rnf ) THEN ! input of heat and salt due to river runoff |
---|
194 | zfact = 0.5_wp |
---|
195 | DO jj = 2, jpj |
---|
196 | DO ji = fs_2, fs_jpim1 |
---|
197 | IF( rnf(ji,jj) /= 0._wp ) THEN |
---|
198 | zdep = zfact / h_rnf(ji,jj) |
---|
199 | DO jk = 1, nk_rnf(ji,jj) |
---|
200 | tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) & |
---|
201 | & + ( rnf_tsc_b(ji,jj,jp_tem) + rnf_tsc(ji,jj,jp_tem) ) * zdep |
---|
202 | IF( ln_rnf_sal ) tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) & |
---|
203 | & + ( rnf_tsc_b(ji,jj,jp_sal) + rnf_tsc(ji,jj,jp_sal) ) * zdep |
---|
204 | END DO |
---|
205 | ENDIF |
---|
206 | END DO |
---|
207 | END DO |
---|
208 | ENDIF |
---|
209 | |
---|
210 | IF( iom_use('rnf_x_sst') ) CALL iom_put( "rnf_x_sst", rnf*tsn(:,:,1,jp_tem) ) ! runoff term on sst |
---|
211 | IF( iom_use('rnf_x_sss') ) CALL iom_put( "rnf_x_sss", rnf*tsn(:,:,1,jp_sal) ) ! runoff term on sss |
---|
212 | |
---|
213 | ! |
---|
214 | !---------------------------------------- |
---|
215 | ! Ice Sheet coupling imbalance correction to have conservation |
---|
216 | !---------------------------------------- |
---|
217 | ! |
---|
218 | IF( ln_iscpl .AND. ln_hsb) THEN ! input of heat and salt due to river runoff |
---|
219 | DO jk = 1,jpk |
---|
220 | DO jj = 2, jpj |
---|
221 | DO ji = fs_2, fs_jpim1 |
---|
222 | zdep = 1._wp / e3t_n(ji,jj,jk) |
---|
223 | tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) - htsc_iscpl(ji,jj,jk,jp_tem) & |
---|
224 | & * zdep |
---|
225 | tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) - htsc_iscpl(ji,jj,jk,jp_sal) & |
---|
226 | & * zdep |
---|
227 | END DO |
---|
228 | END DO |
---|
229 | END DO |
---|
230 | ENDIF |
---|
231 | |
---|
232 | IF( l_trdtra ) THEN ! save the horizontal diffusive trends for further diagnostics |
---|
233 | ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:) |
---|
234 | ztrds(:,:,:) = tsa(:,:,:,jp_sal) - ztrds(:,:,:) |
---|
235 | CALL trd_tra( kt, 'TRA', jp_tem, jptra_nsr, ztrdt ) |
---|
236 | CALL trd_tra( kt, 'TRA', jp_sal, jptra_nsr, ztrds ) |
---|
237 | CALL wrk_dealloc( jpi, jpj, jpk, ztrdt, ztrds ) |
---|
238 | ENDIF |
---|
239 | ! |
---|
240 | IF(ln_ctl) CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' sbc - Ta: ', mask1=tmask, & |
---|
241 | & tab3d_2=tsa(:,:,:,jp_sal), clinfo2= ' Sa: ', mask2=tmask, clinfo3='tra' ) |
---|
242 | ! |
---|
243 | IF( nn_timing == 1 ) CALL timing_stop('tra_sbc') |
---|
244 | ! |
---|
245 | END SUBROUTINE tra_sbc |
---|
246 | |
---|
247 | !!====================================================================== |
---|
248 | END MODULE trasbc |
---|