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

Last change on this file since 473 was 457, checked in by opalod, 18 years ago

nemo_v1_update_049:RB: reorganization of tracers part, remove traadv_cen2_atsk.h90 traldf_iso_zps.F90 trazdf_iso.F90 trazdf_iso_vopt.F90, change atsk routines to jki

  • Property svn:eol-style set to native
  • Property svn:keywords set to Author Date Id Revision
File size: 6.3 KB
Line 
1MODULE trasbc
2   !!==============================================================================
3   !!                       ***  MODULE  trasbc  ***
4   !! Ocean active tracers:  surface boundary condition
5   !!==============================================================================
6   !! History :
7   !!   8.2  !  98-10  (G. Madec, G. Roullet, M. Imbard)  Original code
8   !!   8.2  !  01-02  (D. Ludicone)  sea ice and free surface
9   !!   8.5  !  02-06  (G. Madec)  F90: Free form and module
10   !!   9.0  !  04-08  (C. Talandier) New trends organization
11   !!----------------------------------------------------------------------
12   !!   tra_sbc      : update the tracer trend at ocean surface
13   !!----------------------------------------------------------------------
14   !! * Modules used
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   !! * Routine accessibility
29   PUBLIC tra_sbc              ! routine called by step.F90
30
31   !! * Substitutions
32#  include "domzgr_substitute.h90"
33#  include "vectopt_loop_substitute.h90"
34   !!----------------------------------------------------------------------
35   !!   OPA 9.0 , LOCEAN-IPSL (2005)
36   !! $Header$
37   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt
38   !!----------------------------------------------------------------------
39
40CONTAINS
41
42   SUBROUTINE tra_sbc ( kt )
43      !!----------------------------------------------------------------------
44      !!                  ***  ROUTINE tra_sbc  ***
45      !!                   
46      !! ** Purpose :   Compute the tracer surface boundary condition trend of
47      !!      (flux through the interface, concentration/dilution effect)
48      !!      and add it to the general trend of tracer equations.
49      !!
50      !! ** Method :
51      !!      * flux through the air-sea interface:
52      !!            - temperature : heat flux q (w/m2). If penetrative solar
53      !!         radiation q is only the non solar part of the heat flux, the
54      !!         solar part is added in traqsr.F routine.
55      !!            ta = ta + q /(rau0 rcp e3t)  for k=1
56      !!            - salinity    : no salt flux
57      !!      * concentration/dilution effect:
58      !!            The surface freshwater flux modify the ocean volume
59      !!         and thus the concentration of a tracer and the temperature.
60      !!         First order of the effect of surface freshwater exchange
61      !!         for salinity, it can be neglected on temperature (especially
62      !!         as the temparature of precipitations and runoffs is usually
63      !!         unknown.
64      !!            - temperature : we assume that the temperature of both
65      !!         precipitations and runoffs is equal to the SST, thus there
66      !!         is no additional flux since in this case, the concentration
67      !!         dilution effect is balanced by the net heat flux associated
68      !!         to the freshwater exchange:
69      !!            (Tp P - Te E) + STT (P-E) = 0 when Tp=Te=SST
70      !!            - salinity    : evaporation, precipitation and runoff
71      !!         water has a zero salinity, thus
72      !!            sa = sa + emp * sn / e3t   for k=1
73      !!         where emp, the surface freshwater budget (evaporation minus
74      !!         precipitation minus runoff) given in kg/m2/s is divided
75      !!         by 1000 kg/m3 (density of plain water) to obtain m/s.
76      !!
77      !! ** Action  : - Update the 1st level of (ta,sa) with the trend associated
78      !!                with the tracer surface boundary condition
79      !!              - save the trend it in ttrd ('key_trdtra')
80      !!
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_zco
103      zse3t = 1. / e3t_0(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_zco
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(ln_ctl) THEN         ! print mean trends (used for debugging)
141         CALL prt_ctl(tab3d_1=ta, clinfo1=' sbc  - Ta: ', mask1=tmask, &
142            &         tab3d_2=sa, clinfo2=' Sa: ', mask2=tmask, clinfo3='tra')
143      ENDIF
144
145   END SUBROUTINE tra_sbc
146
147   !!======================================================================
148END MODULE trasbc
Note: See TracBrowser for help on using the repository browser.