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

source: tags/nemo_dev_x9/NEMO/OPA_SRC/TRA/trasbc.F90 @ 8810

Last change on this file since 8810 was 106, checked in by opalod, 20 years ago

CT : UPDATE067 : Add control indices nictl, njctl used in SUM function output to compare mono versus multi procs runs

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