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

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

CT : UPDATE151 : New trends organization

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