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

source: branches/DEV_r2191_3partymerge2010/NEMO/OPA_SRC/TRA/trasbc.F90 @ 2208

Last change on this file since 2208 was 2208, checked in by rblod, 14 years ago

Put FCM NEMO code changes in DEV_r2191_3partymerge2010 branch

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 9.3 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          ! ocean trends
20   USE trdmod_oce      ! ocean variables trends
21   USE in_out_manager  ! I/O manager
22   USE prtctl          ! Print control
23   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
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   !!   OPA 9.0 , LOCEAN-IPSL (2005)
37   !! $Id$
38   !! Software governed by the CeCILL licence  (NEMOGCM/License_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      USE oce, ONLY :   ztrdt => ua   ! use ua as 3D workspace   
104      USE oce, ONLY :   ztrds => va   ! use va as 3D workspace   
105      !!
106      INTEGER, INTENT(in) ::   kt     ! ocean time-step index
107      !!
108      INTEGER  ::   ji, jj, jk           ! dummy loop indices 
109      REAL(wp) ::   zta, zsa             ! local scalars, adjustment to temperature and salinity 
110      REAL(wp) ::   zata, zasa           ! local scalars, calculations of automatic change to temp & sal due to vvl (done elsewhere) 
111      REAL(wp) ::   zsrau, zse3t, zdep   ! local scalars, 1/density, 1/height of box, 1/height of effected water column 
112      REAL(wp) ::   zdheat, zdsalt       ! total change of temperature and salinity 
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
121      zsrau = 1. / rau0             ! initialization
122#if defined key_zco
123      zse3t = 1. / e3t_0(1)
124#endif
125
126      IF( l_trdtra ) THEN           ! Save ta and sa trends
127         ztrdt(:,:,:) = ta(:,:,:) 
128         ztrds(:,:,:) = sa(:,:,:) 
129      ENDIF
130
131      IF( .NOT.ln_traqsr )   qsr(:,:) = 0.e0   ! no solar radiation penetration
132
133      ! Concentration dilution effect on (t,s) due to evapouration, precipitation and qns, but not river runoff 
134      DO jj = 2, jpj
135         DO ji = fs_2, fs_jpim1   ! vector opt.
136#if ! defined key_zco
137            zse3t = 1. / fse3t(ji,jj,1)
138#endif
139            IF( lk_vvl) THEN
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
142               zsa = ( emps(ji,jj) - emp(ji,jj) ) &
143                &                 * zsrau * sn(ji,jj,1)  * zse3t     ! concent./dilut. effect due to sea-ice
144                                                                     ! melt/formation and (possibly) SSS restoration
145            ELSE
146               zta =  ro0cpr * qns(ji,jj) * zse3t                    ! temperature : heat flux
147               zsa =  emps(ji,jj) * zsrau * sn(ji,jj,1) * zse3t      ! salinity :  concent./dilut. effect
148            ENDIF
149            ta(ji,jj,1) = ta(ji,jj,1) + zta                          ! add the trend to the general tracer trend
150            sa(ji,jj,1) = sa(ji,jj,1) + zsa
151         END DO
152      END DO
153
154      !                             !==  Runoffs  ==!
155      ! Effect on (t,s) due to river runoff (dilution effect automatically applied via vertical tracer advection)
156      IF( ln_rnf ) THEN 
157         DO jj = 2, jpj 
158            DO ji = fs_2, fs_jpim1
159               zdep = 1. / h_rnf(ji,jj) 
160               IF ( rnf(ji,jj) .ne. 0.0 ) THEN
161                  DO jk = 1, nk_rnf(ji,jj)
162                                        ta(ji,jj,jk) = ta(ji,jj,jk) + tsc_rnf(ji,jj,jp_tem) * zdep
163                     IF( ln_rnf_sal )   sa(ji,jj,jk) = sa(ji,jj,jk) + tsc_rnf(ji,jj,jp_sal) * zdep
164                  ENDDO
165               ENDIF
166            ENDDO 
167         ENDDO 
168      ENDIF 
169
170      CALL lbc_lnk( ta, 'T', 1. )    ;    CALL lbc_lnk( sa, 'T', 1. )
171
172      IF( l_trdtra ) THEN      ! save the sbc trends for diagnostic
173         ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:)
174         ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:)
175         CALL trd_mod(ztrdt, ztrds, jptra_trd_nsr, 'TRA', kt)
176      ENDIF
177      !
178      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' sbc  - Ta: ', mask1=tmask,   &
179         &                       tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
180      !
181   END SUBROUTINE tra_sbc
182
183   !!======================================================================
184END MODULE trasbc
Note: See TracBrowser for help on using the repository browser.