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

source: trunk/NEMO/OPA_SRC/TRA/trasbc.F90 @ 1739

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

Use rau0 instead of rauw for sbc, uchange rau0 to 1035, see ticket #606

  • Property svn:eol-style set to native
  • Property svn:keywords set to Id
File size: 7.8 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
24   IMPLICIT NONE
25   PRIVATE
26
27   PUBLIC   tra_sbc    ! routine called by step.F90
28
29   !! * Substitutions
30#  include "domzgr_substitute.h90"
31#  include "vectopt_loop_substitute.h90"
32   !!----------------------------------------------------------------------
33   !!   OPA 9.0 , LOCEAN-IPSL (2005)
34   !! $Id$
35   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt)
36   !!----------------------------------------------------------------------
37
38CONTAINS
39
40   SUBROUTINE tra_sbc ( kt )
41      !!----------------------------------------------------------------------
42      !!                  ***  ROUTINE tra_sbc  ***
43      !!                   
44      !! ** Purpose :   Compute the tracer surface boundary condition trend of
45      !!      (flux through the interface, concentration/dilution effect)
46      !!      and add it to the general trend of tracer equations.
47      !!
48      !! ** Method :
49      !!      Following Roullet and Madec (2000), the air-sea flux can be divided
50      !!      into three effects: (1) Fext, external forcing;
51      !!      (2) Fwi, concentration/dilution effect due to water exchanged
52      !!         at the surface by evaporation, precipitations and runoff (E-P-R);
53      !!      (3) Fwe, tracer carried with the water that is exchanged.
54      !!
55      !!      Fext, flux through the air-sea interface for temperature and salt:
56      !!            - temperature : heat flux q (w/m2). If penetrative solar
57      !!         radiation q is only the non solar part of the heat flux, the
58      !!         solar part is added in traqsr.F routine.
59      !!            ta = ta + q /(rau0 rcp e3t)  for k=1
60      !!            - salinity    : no salt flux
61      !!
62      !!      The formulation for Fwb and Fwi vary according to the free
63      !!      surface formulation (linear or variable volume).
64      !!      * Linear free surface
65      !!            The surface freshwater flux modifies the ocean volume
66      !!         and thus the concentration of a tracer and the temperature.
67      !!         First order of the effect of surface freshwater exchange
68      !!         for salinity, it can be neglected on temperature (especially
69      !!         as the temperature of precipitations and runoffs is usually
70      !!         unknown).
71      !!            - temperature : we assume that the temperature of both
72      !!         precipitations and runoffs is equal to the SST, thus there
73      !!         is no additional flux since in this case, the concentration
74      !!         dilution effect is balanced by the net heat flux associated
75      !!         to the freshwater exchange (Fwe+Fwi=0):
76      !!            (Tp P - Te E) + SST (P-E) = 0 when Tp=Te=SST
77      !!            - salinity    : evaporation, precipitation and runoff
78      !!         water has a zero salinity (Fwe=0), thus only Fwi remains:
79      !!            sa = sa + emp * sn / e3t   for k=1
80      !!         where emp, the surface freshwater budget (evaporation minus
81      !!         precipitation minus runoff) given in kg/m2/s is divided
82      !!         by 1035 kg/m3 (density of ocena water) to obtain m/s.   
83      !!         Note: even though Fwe does not appear explicitly for
84      !!         temperature in this routine, the heat carried by the water
85      !!         exchanged through the surface is part of the total heat flux
86      !!         forcing and must be taken into account in the global heat
87      !!         balance).
88      !!      * nonlinear free surface (variable volume, lk_vvl)
89      !!         contrary to the linear free surface case, Fwi is properly
90      !!         taken into account by using the true layer thicknesses to       
91      !!         calculate tracer content and advection. There is no need to
92      !!         deal with it in this routine.
93      !!           - temperature: Fwe=SST (P-E+R) is added to Fext.
94      !!           - salinity:  Fwe = 0, there is no surface flux of salt.
95      !!
96      !! ** Action  : - Update the 1st level of (ta,sa) with the trend associated
97      !!                with the tracer surface boundary condition
98      !!              - save the trend it in ttrd ('key_trdtra')
99      !!----------------------------------------------------------------------
100      USE oce, ONLY :   ztrdt => ua   ! use ua as 3D workspace   
101      USE oce, ONLY :   ztrds => va   ! use va as 3D workspace   
102      !!
103      INTEGER, INTENT(in) ::   kt     ! ocean time-step index
104      !!
105      INTEGER  ::   ji, jj                   ! dummy loop indices
106      REAL(wp) ::   zta, zsa, zsrau, zse3t   ! temporary scalars
107      !!----------------------------------------------------------------------
108
109      IF( kt == nit000 ) THEN
110         IF(lwp) WRITE(numout,*)
111         IF(lwp) WRITE(numout,*) 'tra_sbc : TRAcer Surface Boundary Condition'
112         IF(lwp) WRITE(numout,*) '~~~~~~~ '
113      ENDIF
114
115      zsrau = 1. / rau0             ! initialization
116#if defined key_zco
117      zse3t = 1. / e3t_0(1)
118#endif
119
120      IF( l_trdtra ) THEN           ! Save ta and sa trends
121         ztrdt(:,:,:) = ta(:,:,:) 
122         ztrds(:,:,:) = sa(:,:,:) 
123      ENDIF
124
125      IF( .NOT.ln_traqsr )   qsr(:,:) = 0.e0   ! no solar radiation penetration
126
127      ! Concentration dillution effect on (t,s)
128      DO jj = 2, jpj
129         DO ji = fs_2, fs_jpim1   ! vector opt.
130#if ! defined key_zco
131            zse3t = 1. / fse3t(ji,jj,1)
132#endif
133            IF( lk_vvl) THEN
134               zta = ro0cpr * qns(ji,jj) * zse3t &                   ! temperature : heat flux
135                &    - emp(ji,jj) * zsrau * tn(ji,jj,1)  * zse3t     ! & cooling/heating effet of EMP flux
136               zsa = 0.e0                                            ! No salinity concent./dilut. effect
137            ELSE
138               zta = ro0cpr * qns(ji,jj) * zse3t     ! temperature : heat flux
139               zsa = emps(ji,jj) * zsrau * sn(ji,jj,1)   * zse3t     ! salinity :  concent./dilut. effect
140            ENDIF
141            ta(ji,jj,1) = ta(ji,jj,1) + zta                          ! add the trend to the general tracer trend
142            sa(ji,jj,1) = sa(ji,jj,1) + zsa
143         END DO
144      END DO
145
146      IF( l_trdtra ) THEN      ! save the sbc trends for diagnostic
147         ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:)
148         ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:)
149         CALL trd_mod(ztrdt, ztrds, jptra_trd_nsr, 'TRA', kt)
150      ENDIF
151      !
152      IF(ln_ctl)   CALL prt_ctl( tab3d_1=ta, clinfo1=' sbc  - Ta: ', mask1=tmask,   &
153         &                       tab3d_2=sa, clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
154      !
155   END SUBROUTINE tra_sbc
156
157   !!======================================================================
158END MODULE trasbc
Note: See TracBrowser for help on using the repository browser.