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

Last change on this file since 642 was 592, checked in by opalod, 17 years ago

nemo_v2_update_001 : CT : - add non linear free surface (variable volume) with new cpp key key_vvl

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