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 @ 2117

Last change on this file since 2117 was 2104, checked in by cetlod, 14 years ago

update DEV_r2006_merge_TRA_TRC according to review

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 13.1 KB
Line 
1MODULE 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
41CONTAINS
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              rnf_dep(ji,jj) = 0.e0 
155              DO jk = 1, rnf_mod_dep(ji,jj)                          ! recalculates rnf_dep to be the depth 
156                rnf_dep(ji,jj) = rnf_dep(ji,jj) + fse3t(ji,jj,jk)    ! in metres to the bottom of the relevant grid box 
157              END DO 
158              zdep = 1. / rnf_dep(ji,jj) 
159              zse3t= 1. / fse3t(ji,jj,1) 
160              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 
161 
162              IF( rnf(ji,jj) > 0.e0 ) THEN 
163 
164                IF( lk_vvl ) THEN 
165                  ! indirect flux, concentration or dilution effect : force a dilution effect in all levels
166                  zdheat = 0.e0 
167                  zdsalt = 0.e0 
168                  DO jk = 1, rnf_mod_dep(ji,jj) 
169                    zta = -tsn(ji,jj,jk,jp_tem) * rnf(ji,jj) * zsrau * zdep 
170                    zsa = -tsn(ji,jj,jk,jp_sal) * rnf(ji,jj) * zsrau * zdep 
171                    tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) + zta        ! add the trend to the general tracer trend
172                    tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) + zsa
173                    zdheat = zdheat + zta * fse3t(ji,jj,jk) 
174                    zdsalt = zdsalt + zsa * fse3t(ji,jj,jk) 
175                  END DO 
176                  ! negate this total change in heat and salt content from top level    !!gm I don't understand this
177                  zta = -zdheat * zse3t 
178                  zsa = -zdsalt * zse3t 
179                  tsa(ji,jj,1,jp_tem) = tsa(ji,jj,1,jp_tem) + zta            ! add the trend to the general tracer trend
180                  tsa(ji,jj,1,jp_sal) = tsa(ji,jj,1,jp_sal) + zsa
181   
182                  ! direct flux 
183                  zta = rnf_tmp(ji,jj) * rnf(ji,jj) * zsrau * zdep 
184                  zsa = rnf_sal(ji,jj) * rnf(ji,jj) * zsrau * zdep 
185   
186                  DO jk = 1, rnf_mod_dep(ji,jj) 
187                    tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) + zta        ! add the trend to the general tracer trend
188                    tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) + zsa
189                  END DO 
190                ELSE 
191                  DO jk = 1, rnf_mod_dep(ji,jj) 
192                    zta = ( rnf_tmp(ji,jj) - tsn(ji,jj,jk,jp_tem) ) * rnf(ji,jj) * zsrau * zdep 
193                    zsa = ( rnf_sal(ji,jj) - tsn(ji,jj,jk,jp_sal) ) * rnf(ji,jj) * zsrau * zdep 
194                    tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) + zta        ! add the trend to the general tracer trend
195                    tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) + zsa
196                  END DO 
197                ENDIF 
198 
199              ELSEIF( rnf(ji,jj) < 0.e0) THEN   ! for use in baltic when flow is out of domain, want no change in temp and sal 
200 
201                IF( lk_vvl ) THEN 
202                  ! calculate automatic adjustment to sal and temp due to dilution/concentraion effect   
203                  zata = tsn(ji,jj,1,jp_tem) * rnf(ji,jj) * zsrau * zse3t 
204                  zasa = tsn(ji,jj,1,jp_sal) * rnf(ji,jj) * zsrau * zse3t 
205                  tsa(ji,jj,1,jp_tem) = tsa(ji,jj,1,jp_tem) + zata                  ! add the trend to the general tracer trend
206                  tsa(ji,jj,1,jp_sal) = tsa(ji,jj,1,jp_sal) + zasa
207                ENDIF 
208 
209              ENDIF 
210 
211           END DO 
212        END DO 
213
214      ELSE IF( ln_rnf ) THEN      ! Concentration dilution effect on (t,s) due to runoff without T, S and depth attributes
215
216
217        DO jj = 2, jpj
218           DO ji = fs_2, fs_jpim1   ! vector opt.
219#if ! defined key_zco
220              zse3t = 1. / fse3t(ji,jj,1)
221#endif
222              IF( lk_vvl) THEN
223                 zta =    rnf(ji,jj) * zsrau * tsn(ji,jj,1,jp_tem) * zse3t       ! & cooling/heating effect of runoff
224                 zsa =    0.e0                                                   ! No salinity concent./dilut. effect
225              ELSE
226                 zta =    0.0                                            ! temperature : heat flux
227                 zsa =  - rnf(ji,jj) * zsrau * tsn(ji,jj,1,jp_sal) * zse3t     ! salinity :  concent./dilut. effect
228              ENDIF
229              tsa(ji,jj,1,jp_tem) = tsa(ji,jj,1,jp_tem) + zta          ! add the trend to the general tracer trend
230              tsa(ji,jj,1,jp_sal) = tsa(ji,jj,1,jp_sal) + zsa
231           END DO
232        END DO
233 
234      ENDIF 
235
236      IF( l_trdtra )   THEN                      ! save the horizontal diffusive trends for further diagnostics
237         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
238         ztrds(:,:,:) = tsa(:,:,:,jp_sal) - ztrds(:,:,:)
239         CALL trd_tra( kt, 'TRA', jp_tem, jptra_trd_nsr, ztrdt )
240         CALL trd_tra( kt, 'TRA', jp_sal, jptra_trd_nsr, ztrds )
241         DEALLOCATE( ztrdt )      ;     DEALLOCATE( ztrds )
242      ENDIF
243      !
244      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' sbc  - Ta: ', mask1=tmask,   &
245         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
246      !
247   END SUBROUTINE tra_sbc
248
249   !!======================================================================
250END MODULE trasbc
Note: See TracBrowser for help on using the repository browser.