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.
trasbc.F90 in branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/TRA – NEMO

source: branches/DEV_r2006_merge_TRA_TRC/NEMO/OPA_SRC/TRA/trasbc.F90 @ 2082

Last change on this file since 2082 was 2052, checked in by cetlod, 14 years ago

Improve the merge TRA-TRC, see ticket:701

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 13.2 KB
Line 
1MODULE trasbc
2   !!==============================================================================
3   !!                       ***  MODULE  trasbc  ***
4   !! Ocean active tracers:  surface boundary condition
5   !!==============================================================================
6   !! History :  8.2  !  98-10  (G. Madec, G. Roullet, M. Imbard)  Original code
7   !!            8.2  !  01-02  (D. Ludicone)  sea ice and free surface
8   !!            8.5  !  02-06  (G. Madec)  F90: Free form and module
9   !!----------------------------------------------------------------------
10
11   !!----------------------------------------------------------------------
12   !!   tra_sbc      : update the tracer trend at ocean surface
13   !!----------------------------------------------------------------------
14   USE oce             ! ocean dynamics and active tracers
15   USE sbc_oce         ! surface boundary condition: ocean
16   USE dom_oce         ! ocean space domain variables
17   USE phycst          ! physical constant
18   USE traqsr          ! solar radiation penetration
19   USE trdmod_oce      ! ocean trends
20   USE trdtra          ! ocean trends
21   USE in_out_manager  ! I/O manager
22   USE prtctl          ! Print control
23   USE sbcrnf          ! River runoff 
24   USE sbcmod          ! ln_rnf 
25
26   IMPLICIT NONE
27   PRIVATE
28
29   PUBLIC   tra_sbc    ! routine called by step.F90
30
31   !! * Substitutions
32#  include "domzgr_substitute.h90"
33#  include "vectopt_loop_substitute.h90"
34   !!----------------------------------------------------------------------
35   !!   OPA 9.0 , LOCEAN-IPSL (2005)
36   !! $Id$
37   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
38   !!----------------------------------------------------------------------
39
40CONTAINS
41
42   SUBROUTINE tra_sbc ( kt )
43      !!----------------------------------------------------------------------
44      !!                  ***  ROUTINE tra_sbc  ***
45      !!                   
46      !! ** Purpose :   Compute the tracer surface boundary condition trend of
47      !!      (flux through the interface, concentration/dilution effect)
48      !!      and add it to the general trend of tracer equations.
49      !!
50      !! ** Method :
51      !!      Following Roullet and Madec (2000), the air-sea flux can be divided
52      !!      into three effects: (1) Fext, external forcing;
53      !!      (2) Fwi, concentration/dilution effect due to water exchanged
54      !!         at the surface by evaporation, precipitations and runoff (E-P-R);
55      !!      (3) Fwe, tracer carried with the water that is exchanged.
56      !!
57      !!      Fext, flux through the air-sea interface for temperature and salt:
58      !!            - temperature : heat flux q (w/m2). If penetrative solar
59      !!         radiation q is only the non solar part of the heat flux, the
60      !!         solar part is added in traqsr.F routine.
61      !!            ta = ta + q /(rau0 rcp e3t)  for k=1
62      !!            - salinity    : no salt flux
63      !!
64      !!      The formulation for Fwb and Fwi vary according to the free
65      !!      surface formulation (linear or variable volume).
66      !!      * Linear free surface
67      !!            The surface freshwater flux modifies the ocean volume
68      !!         and thus the concentration of a tracer and the temperature.
69      !!         First order of the effect of surface freshwater exchange
70      !!         for salinity, it can be neglected on temperature (especially
71      !!         as the temperature of precipitations and runoffs is usually
72      !!         unknown).
73      !!            - temperature : we assume that the temperature of both
74      !!         precipitations and runoffs is equal to the SST, thus there
75      !!         is no additional flux since in this case, the concentration
76      !!         dilution effect is balanced by the net heat flux associated
77      !!         to the freshwater exchange (Fwe+Fwi=0):
78      !!            (Tp P - Te E) + SST (P-E) = 0 when Tp=Te=SST
79      !!            - salinity    : evaporation, precipitation and runoff
80      !!         water has a zero salinity (Fwe=0), thus only Fwi remains:
81      !!            sa = sa + emp * sn / e3t   for k=1
82      !!         where emp, the surface freshwater budget (evaporation minus
83      !!         precipitation minus runoff) given in kg/m2/s is divided
84      !!         by 1035 kg/m3 (density of ocena water) to obtain m/s.   
85      !!         Note: even though Fwe does not appear explicitly for
86      !!         temperature in this routine, the heat carried by the water
87      !!         exchanged through the surface is part of the total heat flux
88      !!         forcing and must be taken into account in the global heat
89      !!         balance).
90      !!      * nonlinear free surface (variable volume, lk_vvl)
91      !!         contrary to the linear free surface case, Fwi is properly
92      !!         taken into account by using the true layer thicknesses to       
93      !!         calculate tracer content and advection. There is no need to
94      !!         deal with it in this routine.
95      !!           - temperature: Fwe=SST (P-E+R) is added to Fext.
96      !!           - salinity:  Fwe = 0, there is no surface flux of salt.
97      !!
98      !! ** Action  : - Update the 1st level of (ta,sa) with the trend associated
99      !!                with the tracer surface boundary condition
100      !!              - save the trend it in ttrd ('key_trdtra')
101      !!----------------------------------------------------------------------
102      !!
103      INTEGER, INTENT(in) ::   kt     ! ocean time-step index
104      !!
105      INTEGER  ::   ji, jj, jk           ! dummy loop indices 
106      REAL(wp) ::   zta, zsa             ! temporary scalars, adjustment to temperature and salinity 
107      REAL(wp) ::   zata, zasa           ! temporary scalars, calculations of automatic change to temp & sal due to vvl (done elsewhere) 
108      REAL(wp) ::   zsrau, zse3t, zdep   ! temporary 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               zta =  ro0cpr * qns(ji,jj) * zse3t &                  ! temperature : heat flux
139                &    - emp(ji,jj) * zsrau * tsn(ji,jj,1,jp_tem) * zse3t      ! & cooling/heating effet of EMP flux
140               zsa = ( emps(ji,jj) - emp(ji,jj) ) &
141                &                 * zsrau * tsn(ji,jj,1,jp_sal) * zse3t     ! concent./dilut. effect due to sea-ice
142                                                                     ! melt/formation and (possibly) SSS restoration
143            ELSE
144               zta =  ro0cpr * qns(ji,jj) * zse3t                    ! temperature : heat flux
145               zsa =  emps(ji,jj) * zsrau * tsn(ji,jj,1,jp_sal) * zse3t      ! salinity :  concent./dilut. effect
146            ENDIF
147            tsa(ji,jj,1,jp_tem) = tsa(ji,jj,1,jp_tem) + zta                  ! add the trend to the general tracer trend
148            tsa(ji,jj,1,jp_sal) = tsa(ji,jj,1,jp_sal) + zsa
149         END DO
150      END DO
151
152      IF ( ln_rnf .AND. ln_rnf_att ) THEN 
153        ! Concentration / dilution effect on (t,s) due to river runoff 
154        DO jj = 1, jpj 
155           DO ji = 1, jpi 
156              rnf_dep(ji,jj) = 0. 
157              DO jk = 1, rnf_mod_dep(ji,jj)                          ! recalculates rnf_dep to be the depth 
158                rnf_dep(ji,jj) = rnf_dep(ji,jj) + fse3t(ji,jj,jk)    ! in metres to the bottom of the relevant grid box 
159              ENDDO 
160              zdep = 1. / rnf_dep(ji,jj) 
161              zse3t= 1. / fse3t(ji,jj,1) 
162              IF ( rnf_tmp(ji,jj) == -999 )   rnf_tmp(ji,jj) = tsn(ji,jj,1,jp_tem)    ! if not specified set runoff temp to be sst 
163 
164              IF ( rnf(ji,jj) > 0.0 ) THEN 
165 
166                IF( lk_vvl ) THEN 
167                  ! indirect flux, concentration or dilution effect : force a dilution effect in all levels
168                  zdheat = 0.0 
169                  zdsalt = 0.0 
170                  DO jk = 1, rnf_mod_dep(ji,jj) 
171                    zta = -tsn(ji,jj,jk,jp_tem) * rnf(ji,jj) * zsrau * zdep 
172                    zsa = -tsn(ji,jj,jk,jp_sal) * rnf(ji,jj) * zsrau * zdep 
173                    tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) + zta                  ! add the trend to the general tracer trend
174                    tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) + zsa
175                    zdheat = zdheat + zta * fse3t(ji,jj,jk) 
176                    zdsalt = zdsalt + zsa * fse3t(ji,jj,jk) 
177                  ENDDO 
178                  ! negate this total change in heat and salt content from top level 
179                  zta = -zdheat * zse3t 
180                  zsa = -zdsalt * zse3t 
181                  tsa(ji,jj,1,jp_tem) = tsa(ji,jj,1,jp_tem) + zta                  ! add the trend to the general tracer trend
182                  tsa(ji,jj,1,jp_sal) = tsa(ji,jj,1,jp_sal) + zsa
183   
184                  ! direct flux 
185                  zta = rnf_tmp(ji,jj) * rnf(ji,jj) * zsrau * zdep 
186                  zsa = rnf_sal(ji,jj) * rnf(ji,jj) * zsrau * zdep 
187   
188                  DO jk = 1, rnf_mod_dep(ji,jj) 
189                    tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) + zta                  ! add the trend to the general tracer trend
190                    tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) + zsa
191                  ENDDO 
192   
193                ELSE 
194                  DO jk = 1, rnf_mod_dep(ji,jj) 
195                    zta = ( rnf_tmp(ji,jj) - tsn(ji,jj,jk,jp_tem) ) * rnf(ji,jj) * zsrau * zdep 
196                    zsa = ( rnf_sal(ji,jj) - tsn(ji,jj,jk,jp_sal) ) * rnf(ji,jj) * zsrau * zdep 
197                    tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) + zta                  ! add the trend to the general tracer trend
198                    tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) + zsa
199                  ENDDO 
200                ENDIF 
201 
202              ELSE IF( rnf(ji,jj) < 0.) THEN   ! for use in baltic when flow is out of domain, want no change in temp and sal 
203 
204                IF( lk_vvl ) THEN 
205                  ! calculate automatic adjustment to sal and temp due to dilution/concentraion effect   
206                  zata = tsn(ji,jj,1,jp_tem) * rnf(ji,jj) * zsrau * zse3t 
207                  zasa = tsn(ji,jj,1,jp_sal) * rnf(ji,jj) * zsrau * zse3t 
208                  tsa(ji,jj,1,jp_tem) = tsa(ji,jj,1,jp_tem) + zata                  ! add the trend to the general tracer trend
209                  tsa(ji,jj,1,jp_sal) = tsa(ji,jj,1,jp_sal) + zasa
210                ENDIF 
211 
212              ENDIF 
213 
214           ENDDO 
215        ENDDO 
216
217      ELSE IF( ln_rnf ) THEN
218
219      ! Concentration dilution effect on (t,s) due to runoff without temperatue, salinity and depth attributes
220        DO jj = 2, jpj
221           DO ji = fs_2, fs_jpim1   ! vector opt.
222#if ! defined key_zco
223              zse3t = 1. / fse3t(ji,jj,1)
224#endif
225              IF( lk_vvl) THEN
226                 zta =    rnf(ji,jj) * zsrau * tsn(ji,jj,1,jp_tem) * zse3t       ! & cooling/heating effect of runoff
227                 zsa =    0.e0                                            ! No salinity concent./dilut. effect
228              ELSE
229                 zta =    0.0                                            ! temperature : heat flux
230                 zsa =  - rnf(ji,jj) * zsrau * tsn(ji,jj,1,jp_sal) * zse3t     ! salinity :  concent./dilut. effect
231              ENDIF
232              tsa(ji,jj,1,jp_tem) = tsa(ji,jj,1,jp_tem) + zta          ! add the trend to the general tracer trend
233              tsa(ji,jj,1,jp_sal) = tsa(ji,jj,1,jp_sal) + zsa
234           END DO
235        END DO
236 
237      ENDIF 
238
239      IF( l_trdtra )   THEN                      ! save the horizontal diffusive trends for further diagnostics
240         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
241         ztrds(:,:,:) = tsa(:,:,:,jp_sal) - ztrds(:,:,:)
242         CALL trd_tra( kt, 'TRA', jp_tem, jptra_trd_nsr, ztrdt )
243         CALL trd_tra( kt, 'TRA', jp_sal, jptra_trd_nsr, ztrds )
244         DEALLOCATE( ztrdt )      ;     DEALLOCATE( ztrds )
245      ENDIF
246      !
247      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' sbc  - Ta: ', mask1=tmask,   &
248         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
249      !
250   END SUBROUTINE tra_sbc
251
252   !!======================================================================
253END MODULE trasbc
Note: See TracBrowser for help on using the repository browser.