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

source: branches/DEV_r1837_MLF/NEMO/OPA_SRC/TRA/trasbc.F90 @ 1870

Last change on this file since 1870 was 1870, checked in by gm, 14 years ago

ticket: #663 step-1 : introduce the modified forcing term

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