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 @ 247

Last change on this file since 247 was 247, checked in by opalod, 19 years ago

CL : Add CVS Header and CeCILL licence information

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.4 KB
Line 
1MODULE trasbc
2   !!==============================================================================
3   !!                       ***  MODULE  trasbc  ***
4   !! Ocean active tracers:  surface boundary condition
5   !!==============================================================================
6
7   !!----------------------------------------------------------------------
8   !!   tra_sbc      : update the tracer trend at ocean surface
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE oce             ! ocean dynamics and active tracers
12   USE dom_oce         ! ocean space domain variables
13   USE ocesbc          ! surface thermohaline fluxes
14   USE phycst          ! physical constant
15   USE traqsr          ! solar radiation penetration
16   USE trdmod          ! ocean trends
17   USE trdmod_oce      ! ocean variables trends
18   USE in_out_manager  ! I/O manager
19
20   IMPLICIT NONE
21   PRIVATE
22
23   !! * Routine accessibility
24   PUBLIC tra_sbc              ! routine called by step.F90
25
26   !! * Substitutions
27#  include "domzgr_substitute.h90"
28#  include "vectopt_loop_substitute.h90"
29   !!----------------------------------------------------------------------
30   !!   OPA 9.0 , LOCEAN-IPSL (2005)
31   !! $Header$
32   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
33   !!----------------------------------------------------------------------
34
35CONTAINS
36
37   SUBROUTINE tra_sbc ( kt )
38      !!----------------------------------------------------------------------
39      !!                  ***  ROUTINE tra_sbc  ***
40      !!                   
41      !! ** Purpose :   Compute the tracer surface boundary condition trend of
42      !!      (flux through the interface, concentration/dilution effect)
43      !!      and add it to the general trend of tracer equations.
44      !!
45      !! ** Method :
46      !!      * flux through the air-sea interface:
47      !!            - temperature : heat flux q (w/m2). If penetrative solar
48      !!         radiation q is only the non solar part of the heat flux, the
49      !!         solar part is added in traqsr.F routine.
50      !!            ta = ta + q /(rau0 rcp e3t)  for k=1
51      !!            - salinity    : no salt flux
52      !!      * concentration/dilution effect:
53      !!            The surface freshwater flux modify the ocean volume
54      !!         and thus the concentration of a tracer and the temperature.
55      !!         First order of the effect of surface freshwater exchange
56      !!         for salinity, it can be neglected on temperature (especially
57      !!         as the temparature of precipitations and runoffs is usually
58      !!         unknown.
59      !!            - temperature : we assume that the temperature of both
60      !!         precipitations and runoffs is equal to the SST, thus there
61      !!         is no additional flux since in this case, the concentration
62      !!         dilution effect is balanced by the net heat flux associated
63      !!         to the freshwater exchange:
64      !!            (Tp P - Te E) + STT (P-E) = 0 when Tp=Te=SST
65      !!            - salinity    : evaporation, precipitation and runoff
66      !!         water has a zero salinity, thus
67      !!            sa = sa + emp * sn / e3t   for k=1
68      !!         where emp, the surface freshwater budget (evaporation minus
69      !!         precipitation minus runoff) given in kg/m2/s is divided
70      !!         by 1000 kg/m3 (density of plain water) to obtain m/s.
71      !!
72      !! ** Action  : - Update the 1st level of (ta,sa) with the trend associated
73      !!                with the tracer surface boundary condition
74      !!              - save the trend it in ttrd ('key_trdtra')
75      !!
76      !! History :
77      !!   8.2  !  98-10  (G. Madec, G. Roullet, M. Imbard)  Original code
78      !!   8.2  !  01-02  (D. Ludicone)  sea ice and free surface
79      !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
80      !!   9.0  !  04-08  (C. Talandier) New trends organization
81      !!----------------------------------------------------------------------
82      !! * Modules used     
83      USE oce, ONLY :    ztdta => ua,      & ! use ua as 3D workspace   
84                         ztdsa => va         ! use va as 3D workspace   
85
86      !! * Arguments
87      INTEGER, INTENT( in ) ::   kt          ! ocean time-step index
88
89      !! * Local declarations
90      INTEGER  ::   ji, jj                   ! dummy loop indices
91      REAL(wp) ::   zta, zsa, zsrau, zse3t   ! temporary scalars
92      !!----------------------------------------------------------------------
93
94      IF( kt == nit000 ) THEN
95         IF(lwp) WRITE(numout,*)
96         IF(lwp) WRITE(numout,*) 'tra_sbc : TRAcer Surface Boundary Condition'
97         IF(lwp) WRITE(numout,*) '~~~~~~~ '
98      ENDIF
99
100      ! 0. initialization
101      zsrau = 1. / rauw
102#if ! defined key_s_coord
103      zse3t = 1. / fse3t(1,1,1)
104#endif
105
106      ! Save ta and sa trends
107      IF( l_trdtra )   THEN
108         ztdta(:,:,:) = ta(:,:,:) 
109         ztdsa(:,:,:) = sa(:,:,:) 
110      ENDIF
111
112      IF( .NOT.ln_traqsr )   qsr(:,:) = 0.e0   ! no solar radiation penetration
113
114      ! 1. Concentration dillution effect on (t,s)
115      DO jj = 2, jpj
116         DO ji = fs_2, fs_jpim1   ! vector opt.
117#if defined key_s_coord
118            zse3t = 1. / fse3t(ji,jj,1)
119#endif
120            ! temperature : heat flux
121            zta = ro0cpr * ( qt(ji,jj) - qsr(ji,jj) ) * zse3t
122
123            ! salinity :  concent./dilut. effect
124            zsa = emps(ji,jj) * zsrau * sn(ji,jj,1) * zse3t
125           
126            ! add the trend to the general tracer trend
127            ta(ji,jj,1) = ta(ji,jj,1) + zta
128            sa(ji,jj,1) = sa(ji,jj,1) + zsa
129         END DO
130      END DO
131
132      ! save the trends for diagnostic
133      ! sea surface boundary condition tracers trends
134      IF( l_trdtra )   THEN
135         ztdta(:,:,:) = ta(:,:,:) - ztdta(:,:,:)
136         ztdsa(:,:,:) = sa(:,:,:) - ztdsa(:,:,:)
137         CALL trd_mod(ztdta, ztdsa, jpttdnsr, 'TRA', kt)
138      ENDIF
139     
140      IF(l_ctl) THEN         ! print mean trends (used for debugging)
141         zta = SUM( ta(2:nictl,2:njctl,1:jpkm1) * tmask(2:nictl,2:njctl,1:jpkm1) )
142         zsa = SUM( sa(2:nictl,2:njctl,1:jpkm1) * tmask(2:nictl,2:njctl,1:jpkm1) )
143         WRITE(numout,*) ' sbc  - Ta: ', zta, ' Sa: ', zsa
144         t_ctl = zta   ;   s_ctl = zsa
145      ENDIF
146
147   END SUBROUTINE tra_sbc
148
149   !!======================================================================
150END MODULE trasbc
Note: See TracBrowser for help on using the repository browser.