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-09 (C. Ethe, G. Madec) Merge TRA-TRC |
---|
10 | !!---------------------------------------------------------------------- |
---|
11 | |
---|
12 | !!---------------------------------------------------------------------- |
---|
13 | !! tra_sbc : update the tracer trend at ocean surface |
---|
14 | !!---------------------------------------------------------------------- |
---|
15 | USE oce ! ocean dynamics and active tracers |
---|
16 | USE sbc_oce ! surface boundary condition: ocean |
---|
17 | USE dom_oce ! ocean space domain variables |
---|
18 | USE phycst ! physical constant |
---|
19 | USE traqsr ! solar radiation penetration |
---|
20 | USE trdmod_oce ! ocean trends |
---|
21 | USE trdtra ! ocean trends |
---|
22 | USE in_out_manager ! I/O manager |
---|
23 | USE prtctl ! Print control |
---|
24 | USE sbcrnf ! River runoff |
---|
25 | USE sbcmod ! ln_rnf |
---|
26 | |
---|
27 | IMPLICIT NONE |
---|
28 | PRIVATE |
---|
29 | |
---|
30 | PUBLIC tra_sbc ! routine called by step.F90 |
---|
31 | |
---|
32 | !! * Substitutions |
---|
33 | # include "domzgr_substitute.h90" |
---|
34 | # include "vectopt_loop_substitute.h90" |
---|
35 | !!---------------------------------------------------------------------- |
---|
36 | !! NEMO/OPA 3.3 , LOCEAN-IPSL (2010) |
---|
37 | !! $Id$ |
---|
38 | !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) |
---|
39 | !!---------------------------------------------------------------------- |
---|
40 | |
---|
41 | CONTAINS |
---|
42 | |
---|
43 | SUBROUTINE tra_sbc ( kt ) |
---|
44 | !!---------------------------------------------------------------------- |
---|
45 | !! *** ROUTINE tra_sbc *** |
---|
46 | !! |
---|
47 | !! ** Purpose : Compute the tracer surface boundary condition trend of |
---|
48 | !! (flux through the interface, concentration/dilution effect) |
---|
49 | !! and add it to the general trend of tracer equations. |
---|
50 | !! |
---|
51 | !! ** Method : |
---|
52 | !! Following Roullet and Madec (2000), the air-sea flux can be divided |
---|
53 | !! into three effects: (1) Fext, external forcing; |
---|
54 | !! (2) Fwi, concentration/dilution effect due to water exchanged |
---|
55 | !! at the surface by evaporation, precipitations and runoff (E-P-R); |
---|
56 | !! (3) Fwe, tracer carried with the water that is exchanged. |
---|
57 | !! |
---|
58 | !! Fext, flux through the air-sea interface for temperature and salt: |
---|
59 | !! - temperature : heat flux q (w/m2). If penetrative solar |
---|
60 | !! radiation q is only the non solar part of the heat flux, the |
---|
61 | !! solar part is added in traqsr.F routine. |
---|
62 | !! ta = ta + q /(rau0 rcp e3t) for k=1 |
---|
63 | !! - salinity : no salt flux |
---|
64 | !! |
---|
65 | !! The formulation for Fwb and Fwi vary according to the free |
---|
66 | !! surface formulation (linear or variable volume). |
---|
67 | !! * Linear free surface |
---|
68 | !! The surface freshwater flux modifies the ocean volume |
---|
69 | !! and thus the concentration of a tracer and the temperature. |
---|
70 | !! First order of the effect of surface freshwater exchange |
---|
71 | !! for salinity, it can be neglected on temperature (especially |
---|
72 | !! as the temperature of precipitations and runoffs is usually |
---|
73 | !! unknown). |
---|
74 | !! - temperature : we assume that the temperature of both |
---|
75 | !! precipitations and runoffs is equal to the SST, thus there |
---|
76 | !! is no additional flux since in this case, the concentration |
---|
77 | !! dilution effect is balanced by the net heat flux associated |
---|
78 | !! to the freshwater exchange (Fwe+Fwi=0): |
---|
79 | !! (Tp P - Te E) + SST (P-E) = 0 when Tp=Te=SST |
---|
80 | !! - salinity : evaporation, precipitation and runoff |
---|
81 | !! water has a zero salinity (Fwe=0), thus only Fwi remains: |
---|
82 | !! sa = sa + emp * sn / e3t for k=1 |
---|
83 | !! where emp, the surface freshwater budget (evaporation minus |
---|
84 | !! precipitation minus runoff) given in kg/m2/s is divided |
---|
85 | !! by 1035 kg/m3 (density of ocena water) to obtain m/s. |
---|
86 | !! Note: even though Fwe does not appear explicitly for |
---|
87 | !! temperature in this routine, the heat carried by the water |
---|
88 | !! exchanged through the surface is part of the total heat flux |
---|
89 | !! forcing and must be taken into account in the global heat |
---|
90 | !! balance). |
---|
91 | !! * nonlinear free surface (variable volume, lk_vvl) |
---|
92 | !! contrary to the linear free surface case, Fwi is properly |
---|
93 | !! taken into account by using the true layer thicknesses to |
---|
94 | !! calculate tracer content and advection. There is no need to |
---|
95 | !! deal with it in this routine. |
---|
96 | !! - temperature: Fwe=SST (P-E+R) is added to Fext. |
---|
97 | !! - salinity: Fwe = 0, there is no surface flux of salt. |
---|
98 | !! |
---|
99 | !! ** Action : - Update the 1st level of (ta,sa) with the trend associated |
---|
100 | !! with the tracer surface boundary condition |
---|
101 | !! - save the trend it in ttrd ('key_trdtra') |
---|
102 | !!---------------------------------------------------------------------- |
---|
103 | INTEGER, INTENT(in) :: kt ! ocean time-step index |
---|
104 | !! |
---|
105 | INTEGER :: ji, jj, jk ! dummy loop indices |
---|
106 | REAL(wp) :: zta, zsa ! local scalars, adjustment to temperature and salinity |
---|
107 | REAL(wp) :: zata, zasa ! local scalars, calculations of automatic change to temp & sal due to vvl (done elsewhere) |
---|
108 | REAL(wp) :: zsrau, zse3t, zdep ! local scalars, 1/density, 1/height of box, 1/height of effected water column |
---|
109 | REAL(wp) :: zdheat, zdsalt ! total change of temperature and salinity |
---|
110 | REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: ztrdt, ztrds |
---|
111 | !!---------------------------------------------------------------------- |
---|
112 | |
---|
113 | IF( kt == nit000 ) THEN |
---|
114 | IF(lwp) WRITE(numout,*) |
---|
115 | IF(lwp) WRITE(numout,*) 'tra_sbc : TRAcer Surface Boundary Condition' |
---|
116 | IF(lwp) WRITE(numout,*) '~~~~~~~ ' |
---|
117 | ENDIF |
---|
118 | |
---|
119 | zsrau = 1. / rau0 ! initialization |
---|
120 | #if defined key_zco |
---|
121 | zse3t = 1. / e3t_0(1) |
---|
122 | #endif |
---|
123 | |
---|
124 | IF( l_trdtra ) THEN !* Save ta and sa trends |
---|
125 | ALLOCATE( ztrdt(jpi,jpj,jpk) ) ; ztrdt(:,:,:) = tsa(:,:,:,jp_tem) |
---|
126 | ALLOCATE( ztrds(jpi,jpj,jpk) ) ; ztrds(:,:,:) = tsa(:,:,:,jp_sal) |
---|
127 | ENDIF |
---|
128 | |
---|
129 | IF( .NOT.ln_traqsr ) qsr(:,:) = 0.e0 ! no solar radiation penetration |
---|
130 | |
---|
131 | ! Concentration dilution effect on (t,s) due to evapouration, precipitation and qns, but not river runoff |
---|
132 | DO jj = 2, jpj |
---|
133 | DO ji = fs_2, fs_jpim1 ! vector opt. |
---|
134 | #if ! defined key_zco |
---|
135 | zse3t = 1. / fse3t(ji,jj,1) |
---|
136 | #endif |
---|
137 | IF( lk_vvl) THEN |
---|
138 | ! temperature : heat flux and heat content of EMP flux |
---|
139 | zta = ( ro0cpr * qns(ji,jj) - emp(ji,jj) * zsrau * tsn(ji,jj,1,jp_tem) ) * zse3t |
---|
140 | ! Salinity : concent./dilut. effect due to sea-ice melt/formation and (possibly) SSS restoration |
---|
141 | zsa = ( emps(ji,jj) - emp(ji,jj) ) * zsrau * tsn(ji,jj,1,jp_sal) * zse3t |
---|
142 | ELSE |
---|
143 | zta = ro0cpr * qns(ji,jj) * zse3t ! temperature : heat flux |
---|
144 | zsa = emps(ji,jj) * zsrau * tsn(ji,jj,1,jp_sal) * zse3t ! salinity : concent./dilut. effect |
---|
145 | ENDIF |
---|
146 | tsa(ji,jj,1,jp_tem) = tsa(ji,jj,1,jp_tem) + zta ! add the trend to the general tracer trend |
---|
147 | tsa(ji,jj,1,jp_sal) = tsa(ji,jj,1,jp_sal) + zsa |
---|
148 | END DO |
---|
149 | END DO |
---|
150 | |
---|
151 | IF( ln_rnf .AND. ln_rnf_att ) THEN ! Concentration / dilution effect on (t,s) due to river runoff |
---|
152 | DO jj = 1, jpj |
---|
153 | DO ji = 1, jpi |
---|
154 | zdep = 1. / rnf_dep(ji,jj) |
---|
155 | zse3t= 1. / fse3t(ji,jj,1) |
---|
156 | IF( rnf_tem(ji,jj) == -999 ) rnf_tem(ji,jj) = tsn(ji,jj,1,jp_tem) ! if not specified set runoff temp to be sst |
---|
157 | |
---|
158 | IF( rnf(ji,jj) > 0.e0 ) THEN |
---|
159 | |
---|
160 | IF( lk_vvl ) THEN |
---|
161 | ! indirect flux, concentration or dilution effect : force a dilution effect in all levels |
---|
162 | zdheat = 0.e0 |
---|
163 | zdsalt = 0.e0 |
---|
164 | DO jk = 1, rnf_mod_dep(ji,jj) |
---|
165 | zta = -tsn(ji,jj,jk,jp_tem) * rnf(ji,jj) * zsrau * zdep |
---|
166 | zsa = -tsn(ji,jj,jk,jp_sal) * rnf(ji,jj) * zsrau * zdep |
---|
167 | tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) + zta ! add the trend to the general tracer trend |
---|
168 | tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) + zsa |
---|
169 | zdheat = zdheat + zta * fse3t(ji,jj,jk) |
---|
170 | zdsalt = zdsalt + zsa * fse3t(ji,jj,jk) |
---|
171 | END DO |
---|
172 | ! negate this total change in heat and salt content from top level !!gm I don't understand this |
---|
173 | zta = -zdheat * zse3t |
---|
174 | zsa = -zdsalt * zse3t |
---|
175 | tsa(ji,jj,1,jp_tem) = tsa(ji,jj,1,jp_tem) + zta ! add the trend to the general tracer trend |
---|
176 | tsa(ji,jj,1,jp_sal) = tsa(ji,jj,1,jp_sal) + zsa |
---|
177 | |
---|
178 | ! direct flux |
---|
179 | zta = rnf_tem(ji,jj) * rnf(ji,jj) * zsrau * zdep |
---|
180 | zsa = rnf_sal(ji,jj) * rnf(ji,jj) * zsrau * zdep |
---|
181 | |
---|
182 | DO jk = 1, rnf_mod_dep(ji,jj) |
---|
183 | tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) + zta ! add the trend to the general tracer trend |
---|
184 | tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) + zsa |
---|
185 | END DO |
---|
186 | ELSE |
---|
187 | DO jk = 1, rnf_mod_dep(ji,jj) |
---|
188 | zta = ( rnf_tem(ji,jj) - tsn(ji,jj,jk,jp_tem) ) * rnf(ji,jj) * zsrau * zdep |
---|
189 | zsa = ( rnf_sal(ji,jj) - tsn(ji,jj,jk,jp_sal) ) * rnf(ji,jj) * zsrau * zdep |
---|
190 | tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) + zta ! add the trend to the general tracer trend |
---|
191 | tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) + zsa |
---|
192 | END DO |
---|
193 | ENDIF |
---|
194 | |
---|
195 | ELSEIF( rnf(ji,jj) < 0.e0) THEN ! for use in baltic when flow is out of domain, want no change in temp and sal |
---|
196 | |
---|
197 | IF( lk_vvl ) THEN |
---|
198 | ! calculate automatic adjustment to sal and temp due to dilution/concentraion effect |
---|
199 | zata = tsn(ji,jj,1,jp_tem) * rnf(ji,jj) * zsrau * zse3t |
---|
200 | zasa = tsn(ji,jj,1,jp_sal) * rnf(ji,jj) * zsrau * zse3t |
---|
201 | tsa(ji,jj,1,jp_tem) = tsa(ji,jj,1,jp_tem) + zata ! add the trend to the general tracer trend |
---|
202 | tsa(ji,jj,1,jp_sal) = tsa(ji,jj,1,jp_sal) + zasa |
---|
203 | ENDIF |
---|
204 | |
---|
205 | ENDIF |
---|
206 | |
---|
207 | END DO |
---|
208 | END DO |
---|
209 | |
---|
210 | ELSE IF( ln_rnf ) THEN ! Concentration dilution effect on (t,s) due to runoff without T, S and depth attributes |
---|
211 | |
---|
212 | |
---|
213 | DO jj = 2, jpj |
---|
214 | DO ji = fs_2, fs_jpim1 ! vector opt. |
---|
215 | #if ! defined key_zco |
---|
216 | zse3t = 1. / fse3t(ji,jj,1) |
---|
217 | #endif |
---|
218 | IF( lk_vvl) THEN |
---|
219 | zta = rnf(ji,jj) * zsrau * tsn(ji,jj,1,jp_tem) * zse3t ! & cooling/heating effect of runoff |
---|
220 | zsa = 0.e0 ! No salinity concent./dilut. effect |
---|
221 | ELSE |
---|
222 | zta = 0.0 ! temperature : heat flux |
---|
223 | zsa = - rnf(ji,jj) * zsrau * tsn(ji,jj,1,jp_sal) * zse3t ! salinity : concent./dilut. effect |
---|
224 | ENDIF |
---|
225 | tsa(ji,jj,1,jp_tem) = tsa(ji,jj,1,jp_tem) + zta ! add the trend to the general tracer trend |
---|
226 | tsa(ji,jj,1,jp_sal) = tsa(ji,jj,1,jp_sal) + zsa |
---|
227 | END DO |
---|
228 | END DO |
---|
229 | |
---|
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_trd_nsr, ztrdt ) |
---|
236 | CALL trd_tra( kt, 'TRA', jp_sal, jptra_trd_nsr, ztrds ) |
---|
237 | DEALLOCATE( ztrdt ) ; DEALLOCATE( 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 | END SUBROUTINE tra_sbc |
---|
244 | |
---|
245 | !!====================================================================== |
---|
246 | END MODULE trasbc |
---|