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_R1821_Rivers/NEMO/OPA_SRC/TRA – NEMO

source: branches/DEV_R1821_Rivers/NEMO/OPA_SRC/TRA/trasbc.F90 @ 1938

Last change on this file since 1938 was 1938, checked in by rfurner, 14 years ago

rnf has been separated from emp and emps. Also temperature and salinity of runoff can be specified, and runoff can be added to a user specified depth

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 11.3 KB
RevLine 
[3]1MODULE trasbc
2   !!==============================================================================
3   !!                       ***  MODULE  trasbc  ***
4   !! Ocean active tracers:  surface boundary condition
5   !!==============================================================================
[503]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
[3]9   !!----------------------------------------------------------------------
[503]10
11   !!----------------------------------------------------------------------
[3]12   !!   tra_sbc      : update the tracer trend at ocean surface
13   !!----------------------------------------------------------------------
14   USE oce             ! ocean dynamics and active tracers
[888]15   USE sbc_oce         ! surface boundary condition: ocean
[3]16   USE dom_oce         ! ocean space domain variables
17   USE phycst          ! physical constant
[216]18   USE traqsr          ! solar radiation penetration
19   USE trdmod          ! ocean trends
20   USE trdmod_oce      ! ocean variables trends
[3]21   USE in_out_manager  ! I/O manager
[258]22   USE prtctl          ! Print control
[1938]23   USE sbcrnf          ! River runoff 
24   USE sbcmod          ! ln_rnf 
[3]25
26   IMPLICIT NONE
27   PRIVATE
28
[503]29   PUBLIC   tra_sbc    ! routine called by step.F90
[3]30
31   !! * Substitutions
32#  include "domzgr_substitute.h90"
33#  include "vectopt_loop_substitute.h90"
34   !!----------------------------------------------------------------------
[247]35   !!   OPA 9.0 , LOCEAN-IPSL (2005)
[888]36   !! $Id$
[503]37   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
[3]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 :
[664]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:
[3]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
[664]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
[3]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
[664]71      !!         as the temperature of precipitations and runoffs is usually
72      !!         unknown).
[3]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
[664]77      !!         to the freshwater exchange (Fwe+Fwi=0):
78      !!            (Tp P - Te E) + SST (P-E) = 0 when Tp=Te=SST
[3]79      !!            - salinity    : evaporation, precipitation and runoff
[664]80      !!         water has a zero salinity (Fwe=0), thus only Fwi remains:
[3]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
[1739]84      !!         by 1035 kg/m3 (density of ocena water) to obtain m/s.   
[664]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.
[3]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')
[503]101      !!----------------------------------------------------------------------
102      USE oce, ONLY :   ztrdt => ua   ! use ua as 3D workspace   
103      USE oce, ONLY :   ztrds => va   ! use va as 3D workspace   
[3]104      !!
[503]105      INTEGER, INTENT(in) ::   kt     ! ocean time-step index
106      !!
[1938]107      INTEGER  ::   ji, jj, jk           ! dummy loop indices 
108      REAL(wp) ::   zta, zsa             ! temporary scalars, adjustment to temperature and salinity 
109      REAL(wp) ::   azta, azsa           ! temporary scalars, calculations of automatic change to temp & sal due to vvl (done elsewhere) 
110      REAL(wp) ::   zsrau, zse3t, zdep   ! temporary scalars, 1/density, 1/height of box, 1/height of effected water column 
111      REAL(wp) ::   dheat, dsalt          ! total change of temperature and salinity 
112      REAL(wp) ::   tot_sal1, tot_tmp1 
[3]113      !!----------------------------------------------------------------------
114
115      IF( kt == nit000 ) THEN
116         IF(lwp) WRITE(numout,*)
117         IF(lwp) WRITE(numout,*) 'tra_sbc : TRAcer Surface Boundary Condition'
118         IF(lwp) WRITE(numout,*) '~~~~~~~ '
119      ENDIF
120
[1739]121      zsrau = 1. / rau0             ! initialization
[457]122#if defined key_zco
123      zse3t = 1. / e3t_0(1)
[3]124#endif
125
[503]126      IF( l_trdtra ) THEN           ! Save ta and sa trends
127         ztrdt(:,:,:) = ta(:,:,:) 
128         ztrds(:,:,:) = sa(:,:,:) 
[216]129      ENDIF
130
[3]131      IF( .NOT.ln_traqsr )   qsr(:,:) = 0.e0   ! no solar radiation penetration
132
[1938]133      ! Concentration dillution effect on (t,s) due to evapouration, precipitation and qns, but not river runoff 
[3]134      DO jj = 2, jpj
135         DO ji = fs_2, fs_jpim1   ! vector opt.
[457]136#if ! defined key_zco
[3]137            zse3t = 1. / fse3t(ji,jj,1)
138#endif
[592]139            IF( lk_vvl) THEN
[1938]140               zta =  ro0cpr * qns(ji,jj) * zse3t &                  ! temperature : heat flux
141                &    - emp(ji,jj) * zsrau * tn(ji,jj,1) * zse3t      ! & cooling/heating effet of EMP flux
[592]142               zsa = 0.e0                                            ! No salinity concent./dilut. effect
143            ELSE
[1938]144               zta =  ro0cpr * qns(ji,jj) * zse3t                    ! temperature : heat flux
145               zsa =  emps(ji,jj) * zsrau * sn(ji,jj,1) * zse3t      ! salinity :  concent./dilut. effect
[592]146            ENDIF
147            ta(ji,jj,1) = ta(ji,jj,1) + zta                          ! add the trend to the general tracer trend
[3]148            sa(ji,jj,1) = sa(ji,jj,1) + zsa
149         END DO
150      END DO
[216]151
[1938]152      IF ( ln_rnf ) 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)=tn(ji,jj,1)        ! if not specified set runoff temp to be sst 
163 
164              IF ( rnf(ji,jj) .gt. 0.0 ) THEN 
165 
166                IF( lk_vvl) THEN 
167                  !!!indirect flux, concentration or dilution effect 
168                  !!!force a dilution effect in all levels; 
169                  dheat=0.0 
170                  dsalt=0.0 
171                  DO jk=1, rnf_mod_dep(ji,jj) 
172                    zta = -tn(ji,jj,jk) * rnf(ji,jj) * zsrau * zdep 
173                    zsa = -sn(ji,jj,jk) * rnf(ji,jj) * zsrau * zdep 
174                    ta(ji,jj,jk)=ta(ji,jj,jk)+zta 
175                    sa(ji,jj,jk)=sa(ji,jj,jk)+zsa 
176                    dheat=dheat+zta*fse3t(ji,jj,jk) 
177                    dsalt=dsalt+zsa*fse3t(ji,jj,jk) 
178                  ENDDO 
179                  !!!negate this total change in heat and salt content from top level 
180                  zta=-dheat*zse3t 
181                  zsa=-dsalt*zse3t 
182                  ta(ji,jj,1)=ta(ji,jj,1)+zta 
183                  sa(ji,jj,1)=sa(ji,jj,1)+zsa 
184   
185                  !!!direct flux 
186                  zta = rnf_tmp(ji,jj) * rnf(ji,jj) * zsrau * zdep 
187                  zsa = rnf_sal(ji,jj) * rnf(ji,jj) * zsrau * zdep 
188   
189                  DO jk=1, rnf_mod_dep(ji,jj) 
190                    ta(ji,jj,jk) = ta(ji,jj,jk) + zta 
191                    sa(ji,jj,jk) = sa(ji,jj,jk) + zsa 
192                  ENDDO 
193   
194                ELSE 
195                  DO jk=1, rnf_mod_dep(ji,jj) 
196                    zta = ( rnf_tmp(ji,jj)-tn(ji,jj,jk) ) * rnf(ji,jj) * zsrau * zdep 
197                    zsa = ( rnf_sal(ji,jj)-sn(ji,jj,jk) ) * rnf(ji,jj) * zsrau * zdep 
198                    ta(ji,jj,jk) = ta(ji,jj,jk) + zta 
199                    sa(ji,jj,jk) = sa(ji,jj,jk) + zsa 
200                  ENDDO 
201                ENDIF 
202 
203              ELSEIF (rnf(ji,jj) .lt. 0.) THEN   !! for use in baltic when flow is out of domain, want no change in temp and sal 
204 
205                IF( lk_vvl) THEN 
206                  !calculate automatic adjustment to sal and temp due to dilution/concentraion effect   
207                  azta = -tn(ji,jj,1) * rnf(ji,jj) * zsrau * zse3t 
208                  azsa = -sn(ji,jj,1) * rnf(ji,jj) * zsrau * zse3t 
209                  !!!negate this change in sal and temp   
210                  ta(ji,jj,1)=ta(ji,jj,1)-azta 
211                  sa(ji,jj,1)=sa(ji,jj,1)-azsa 
212                ENDIF 
213 
214              ENDIF 
215 
216           ENDDO 
217        ENDDO 
218       
219      ENDIF 
220
[503]221      IF( l_trdtra ) THEN      ! save the sbc trends for diagnostic
222         ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:)
223         ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:)
224         CALL trd_mod(ztrdt, ztrds, jptra_trd_nsr, 'TRA', kt)
[216]225      ENDIF
[503]226      !
227      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' sbc  - Ta: ', mask1=tmask,   &
228         &                       tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
229      !
[3]230   END SUBROUTINE tra_sbc
231
232   !!======================================================================
233END MODULE trasbc
Note: See TracBrowser for help on using the repository browser.