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

source: branches/dev_001_GM/NEMO/OPA_SRC/TRA/trasbc.F90 @ 786

Last change on this file since 786 was 786, checked in by gm, 16 years ago

dev_001_GM - merge TRC-TRA on OPA only, trabbl & zpshde not done and trdmld not OK - compilation OK

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 7.9 KB
Line 
1MODULE trasbc
2   !!======================================================================
3   !!                       ***  MODULE  trasbc  ***
4   !! Ocean active tracers:  surface boundary condition
5   !!======================================================================
6   !! History :  OPA  !  98-10  (G. Madec, G. Roullet, M. Imbard)  Original code
7   !!            8.2  !  01-02  (D. Ludicone)  sea ice and free surface
8   !!   NEMO     1.0  !  02-06  (G. Madec)  F90: Free form and module
9   !!            2.4  !  08-01  (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 dom_oce         ! ocean space domain variables
17   USE ocesbc          ! surface thermohaline fluxes
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 2.4 , LOCEAN-IPSL (2008)
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 :
50      !!      Following Roullet and Madec (2000), the air-sea flux can be divided
51      !!      into three effects: (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    : no salt flux
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 1000 kg/m3 (density of plain 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      INTEGER, INTENT(in) ::   kt     ! ocean time-step index
102      !!
103      INTEGER  ::   ji, jj                   ! dummy loop indices
104      REAL(wp) ::   zta, zsa, zsrau, zse3t   ! temporary scalars
105      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   ztrdt, ztrds   ! 3D workspace
106      !!----------------------------------------------------------------------
107
108      IF( kt == nit000 ) THEN
109         IF(lwp) WRITE(numout,*)
110         IF(lwp) WRITE(numout,*) 'tra_sbc : TRAcer Surface Boundary Condition'
111         IF(lwp) WRITE(numout,*) '~~~~~~~ '
112      ENDIF
113
114      zsrau = 1. / rauw             ! initialization
115#if defined key_zco
116      zse3t = 1. / e3t_0(1)
117#endif
118
119      IF( l_trdtra ) THEN           ! Save ta and sa trends
120         ztrdt(:,:,:) = ta(:,:,:) 
121         ztrds(:,:,:) = sa(:,:,:) 
122      ENDIF
123
124      IF( .NOT.ln_traqsr )   qsr(:,:) = 0.e0   ! no solar radiation penetration
125
126      ! Concentration dillution effect on (t,s)
127      DO jj = 2, jpj
128         DO ji = fs_2, fs_jpim1   ! vector opt.
129#if ! defined key_zco
130            zse3t = 1. / fse3t(ji,jj,1)
131#endif
132            IF( lk_vvl) THEN
133               zta = ro0cpr * ( qt(ji,jj) - qsr(ji,jj) ) * zse3t &   ! temperature : heat flux
134                &    - emp(ji,jj) * zsrau * tn(ji,jj,1)  * zse3t     ! & cooling/heating effet of EMP flux
135               zsa = 0.e0                                            ! No salinity concent./dilut. effect
136            ELSE
137               zta = ro0cpr * ( qt(ji,jj) - qsr(ji,jj) ) * zse3t     ! temperature : heat flux
138               zsa = emps(ji,jj) * zsrau * sn(ji,jj,1)   * zse3t     ! salinity :  concent./dilut. effect
139            ENDIF
140            ta(ji,jj,1) = ta(ji,jj,1) + zta                          ! add the trend to the general tracer trend
141            sa(ji,jj,1) = sa(ji,jj,1) + zsa
142         END DO
143      END DO
144
145      IF( l_trdtra )   THEN                      ! save the horizontal diffusive trends for further diagnostics
146         ztrdt(:,:,:) = ta(:,:,:) - ztrdt(:,:,:)
147         ztrds(:,:,:) = sa(:,:,:) - ztrds(:,:,:)
148         CALL trd_tra( kt, jp_tem, jpt_trd_qns, 'TRA', ptrd3d=ztrdt)
149         CALL trd_tra( kt, jp_sal, jpt_trd_qns, 'TRA', ptrd3d=ztrds)
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.