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 branches/2012/dev_LOCEAN_UKMO_2012/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/2012/dev_LOCEAN_UKMO_2012/NEMOGCM/NEMO/OPA_SRC/TRA/trasbc.F90 @ 3653

Last change on this file since 3653 was 3653, checked in by cetlod, 11 years ago

commit the changes from LOCEAN & UKMO merge, see ticket #1021

  • Property svn:keywords set to Id
File size: 12.7 KB
Line 
1MODULE trasbc
2   !!==============================================================================
3   !!                       ***  MODULE  trasbc  ***
4   !! Ocean active tracers:  surface boundary condition
5   !!==============================================================================
6   !! History :  OPA  !  1998-10  (G. Madec, G. Roullet, M. Imbard)  Original code
7   !!            8.2  !  2001-02  (D. Ludicone)  sea ice and free surface
8   !!  NEMO      1.0  !  2002-06  (G. Madec)  F90: Free form and module
9   !!            3.3  !  2010-04  (M. Leclair, G. Madec)  Forcing averaged over 2 time steps
10   !!             -   !  2010-09  (C. Ethe, G. Madec) Merge TRA-TRC
11   !!----------------------------------------------------------------------
12
13   !!----------------------------------------------------------------------
14   !!   tra_sbc      : update the tracer trend at ocean surface
15   !!----------------------------------------------------------------------
16   USE oce             ! ocean dynamics and active tracers
17   USE sbc_oce         ! surface boundary condition: ocean
18   USE dom_oce         ! ocean space domain variables
19   USE phycst          ! physical constant
20   USE traqsr          ! solar radiation penetration
21   USE trdmod_oce      ! ocean trends
22   USE trdtra          ! ocean trends
23   USE in_out_manager  ! I/O manager
24   USE prtctl          ! Print control
25   USE sbcrnf          ! River runoff 
26   USE sbcmod          ! ln_rnf 
27   USE iom
28   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
29   USE wrk_nemo        ! Memory Allocation
30   USE timing          ! Timing
31
32   IMPLICIT NONE
33   PRIVATE
34
35   PUBLIC   tra_sbc    ! routine called by step.F90
36
37   !! * Substitutions
38#  include "domzgr_substitute.h90"
39#  include "vectopt_loop_substitute.h90"
40   !!----------------------------------------------------------------------
41   !! NEMO/OPA 3.3 , NEMO Consortium (2010)
42   !! $Id$
43   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
44   !!----------------------------------------------------------------------
45CONTAINS
46
47   SUBROUTINE tra_sbc ( kt )
48      !!----------------------------------------------------------------------
49      !!                  ***  ROUTINE tra_sbc  ***
50      !!                   
51      !! ** Purpose :   Compute the tracer surface boundary condition trend of
52      !!      (flux through the interface, concentration/dilution effect)
53      !!      and add it to the general trend of tracer equations.
54      !!
55      !! ** Method :
56      !!      Following Roullet and Madec (2000), the air-sea flux can be divided
57      !!      into three effects: (1) Fext, external forcing;
58      !!      (2) Fwi, concentration/dilution effect due to water exchanged
59      !!         at the surface by evaporation, precipitations and runoff (E-P-R);
60      !!      (3) Fwe, tracer carried with the water that is exchanged.
61      !!
62      !!      Fext, flux through the air-sea interface for temperature and salt:
63      !!            - temperature : heat flux q (w/m2). If penetrative solar
64      !!         radiation q is only the non solar part of the heat flux, the
65      !!         solar part is added in traqsr.F routine.
66      !!            ta = ta + q /(rau0 rcp e3t)  for k=1
67      !!            - salinity    : no salt flux
68      !!
69      !!      The formulation for Fwb and Fwi vary according to the free
70      !!      surface formulation (linear or variable volume).
71      !!      * Linear free surface
72      !!            The surface freshwater flux modifies the ocean volume
73      !!         and thus the concentration of a tracer and the temperature.
74      !!         First order of the effect of surface freshwater exchange
75      !!         for salinity, it can be neglected on temperature (especially
76      !!         as the temperature of precipitations and runoffs is usually
77      !!         unknown).
78      !!            - temperature : we assume that the temperature of both
79      !!         precipitations and runoffs is equal to the SST, thus there
80      !!         is no additional flux since in this case, the concentration
81      !!         dilution effect is balanced by the net heat flux associated
82      !!         to the freshwater exchange (Fwe+Fwi=0):
83      !!            (Tp P - Te E) + SST (P-E) = 0 when Tp=Te=SST
84      !!            - salinity    : evaporation, precipitation and runoff
85      !!         water has a zero salinity (Fwe=0), thus only Fwi remains:
86      !!            sa = sa + emp * sn / e3t   for k=1
87      !!         where emp, the surface freshwater budget (evaporation minus
88      !!         precipitation minus runoff) given in kg/m2/s is divided
89      !!         by 1035 kg/m3 (density of ocena water) to obtain m/s.   
90      !!         Note: even though Fwe does not appear explicitly for
91      !!         temperature in this routine, the heat carried by the water
92      !!         exchanged through the surface is part of the total heat flux
93      !!         forcing and must be taken into account in the global heat
94      !!         balance).
95      !!      * nonlinear free surface (variable volume, lk_vvl)
96      !!         contrary to the linear free surface case, Fwi is properly
97      !!         taken into account by using the true layer thicknesses to       
98      !!         calculate tracer content and advection. There is no need to
99      !!         deal with it in this routine.
100      !!           - temperature: Fwe=SST (P-E+R) is added to Fext.
101      !!           - salinity:  Fwe = 0, there is no surface flux of salt.
102      !!
103      !! ** Action  : - Update the 1st level of (ta,sa) with the trend associated
104      !!                with the tracer surface boundary condition
105      !!              - save the trend it in ttrd ('key_trdtra')
106      !!----------------------------------------------------------------------
107      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
108      !!
109      INTEGER  ::   ji, jj, jk, jn           ! dummy loop indices 
110      REAL(wp) ::   zfact, z1_e3t, zsrau, zdep
111      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrdt, ztrds
112      !!----------------------------------------------------------------------
113      !
114      IF( nn_timing == 1 )  CALL timing_start('tra_sbc')
115      !
116      IF( kt == nit000 ) THEN
117         IF(lwp) WRITE(numout,*)
118         IF(lwp) WRITE(numout,*) 'tra_sbc : TRAcer Surface Boundary Condition'
119         IF(lwp) WRITE(numout,*) '~~~~~~~ '
120      ENDIF
121
122      zsrau = 1. / rau0             ! initialization
123
124      IF( l_trdtra )   THEN                    !* Save ta and sa trends
125         CALL wrk_alloc( jpi, jpj, jpk, ztrdt, ztrds ) 
126         ztrdt(:,:,:) = tsa(:,:,:,jp_tem)
127         ztrds(:,:,:) = tsa(:,:,:,jp_sal)
128      ENDIF
129
130!!gm      IF( .NOT.ln_traqsr )   qsr(:,:) = 0.e0   ! no solar radiation penetration
131      IF( .NOT.ln_traqsr ) THEN     ! no solar radiation penetration
132         qns(:,:) = qns(:,:) + qsr(:,:)      ! total heat flux in qns
133         qsr(:,:) = 0.e0                     ! qsr set to zero
134      ENDIF
135
136      !----------------------------------------
137      !        EMP, EMPS and QNS effects
138      !----------------------------------------
139      !                                          Set before sbc tracer content fields
140      !                                          ************************************
141      IF( kt == nit000 ) THEN                      ! Set the forcing field at nit000 - 1
142         !                                         ! -----------------------------------
143         IF( ln_rstart .AND.    &                     ! Restart: read in restart file
144              & iom_varid( numror, 'sbc_hc_b', ldstop = .FALSE. ) > 0 ) THEN
145            IF(lwp) WRITE(numout,*) '          nit000-1 surface tracer content forcing fields red in the restart file'
146            zfact = 0.5e0
147            CALL iom_get( numror, jpdom_autoglo, 'sbc_hc_b', sbc_tsc_b(:,:,jp_tem) )   ! before heat content sbc trend
148            CALL iom_get( numror, jpdom_autoglo, 'sbc_sc_b', sbc_tsc_b(:,:,jp_sal) )   ! before salt content sbc trend
149         ELSE                                         ! No restart or restart not found: Euler forward time stepping
150            zfact = 1.e0
151            sbc_tsc_b(:,:,:) = 0.e0
152         ENDIF
153      ELSE                                         ! Swap of forcing fields
154         !                                         ! ----------------------
155         zfact = 0.5e0
156         sbc_tsc_b(:,:,:) = sbc_tsc(:,:,:)
157      ENDIF
158      !                                          Compute now sbc tracer content fields
159      !                                          *************************************
160
161                                                   ! Concentration dilution effect on (t,s) due to 
162                                                   ! evaporation, precipitation and qns, but not river runoff
163                                               
164      IF( lk_vvl ) THEN                            ! Variable Volume case
165         DO jj = 1, jpj
166            DO ji = 1, jpi 
167               ! temperature : heat flux + cooling/heating effet of EMP flux
168               sbc_tsc(ji,jj,jp_tem) = ro0cpr * qns(ji,jj) - zsrau * emp(ji,jj) * tsn(ji,jj,1,jp_tem)
169               ! concent./dilut. effect due to sea-ice melt/formation and (possibly) SSS restoration
170               sbc_tsc(ji,jj,jp_sal) = ( emps(ji,jj) - emp(ji,jj) ) * zsrau * tsn(ji,jj,1,jp_sal)
171            END DO
172         END DO
173      ELSE                                         ! Constant Volume case
174         DO jj = 2, jpj
175            DO ji = fs_2, fs_jpim1   ! vector opt.
176               ! temperature : heat flux
177               sbc_tsc(ji,jj,jp_tem) = ro0cpr * qns(ji,jj)
178               ! salinity    : salt flux + concent./dilut. effect (both in emps)
179               sbc_tsc(ji,jj,jp_sal) = zsrau * emps(ji,jj) * tsn(ji,jj,1,jp_sal)
180            END DO
181         END DO
182      ENDIF
183      ! Concentration dilution effect on (t,s) due to evapouration, precipitation and qns, but not river runoff 
184      DO jn = 1, jpts
185         DO jj = 2, jpj
186            DO ji = fs_2, fs_jpim1   ! vector opt.
187               z1_e3t = zfact / fse3t(ji,jj,1)
188               tsa(ji,jj,1,jn) = tsa(ji,jj,1,jn) + ( sbc_tsc_b(ji,jj,jn) + sbc_tsc(ji,jj,jn) ) * z1_e3t
189            END DO
190         END DO
191      END DO
192      !                                          Write in the ocean restart file
193      !                                          *******************************
194      IF( lrst_oce ) THEN
195         IF(lwp) WRITE(numout,*)
196         IF(lwp) WRITE(numout,*) 'sbc : ocean surface tracer content forcing fields written in ocean restart file ',   &
197            &                    'at it= ', kt,' date= ', ndastp
198         IF(lwp) WRITE(numout,*) '~~~~'
199         CALL iom_rstput( kt, nitrst, numrow, 'sbc_hc_b', sbc_tsc(:,:,jp_tem) )
200         CALL iom_rstput( kt, nitrst, numrow, 'sbc_sc_b', sbc_tsc(:,:,jp_sal) )
201      ENDIF
202      !
203      !----------------------------------------
204      !        River Runoff effects
205      !----------------------------------------
206      !
207      zfact = 0.5e0
208
209      ! Effect on (t,s) due to river runoff (dilution effect automatically applied via vertical tracer advection)
210      IF( ln_rnf ) THEN 
211         DO jj = 2, jpj 
212            DO ji = fs_2, fs_jpim1
213               zdep = 1. / h_rnf(ji,jj)
214               zdep = zfact * zdep 
215               IF ( rnf(ji,jj) /= 0._wp ) THEN
216                  DO jk = 1, nk_rnf(ji,jj)
217                                        tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem)   &
218                                          &               +  ( rnf_tsc_b(ji,jj,jp_tem) + rnf_tsc(ji,jj,jp_tem) ) * zdep
219                     IF( ln_rnf_sal )   tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal)   &
220                                          &               +  ( rnf_tsc_b(ji,jj,jp_sal) + rnf_tsc(ji,jj,jp_sal) ) * zdep 
221                  END DO
222               ENDIF
223            END DO 
224         END DO 
225      ENDIF 
226!!gm  It should be useless
227      CALL lbc_lnk( tsa(:,:,:,jp_tem), 'T', 1. )    ;    CALL lbc_lnk( tsa(:,:,:,jp_sal), 'T', 1. )
228
229      IF( l_trdtra )   THEN                      ! save the horizontal diffusive trends for further diagnostics
230         ztrdt(:,:,:) = tsa(:,:,:,jp_tem) - ztrdt(:,:,:)
231         ztrds(:,:,:) = tsa(:,:,:,jp_sal) - ztrds(:,:,:)
232         CALL trd_tra( kt, 'TRA', jp_tem, jptra_trd_nsr, ztrdt )
233         CALL trd_tra( kt, 'TRA', jp_sal, jptra_trd_nsr, ztrds )
234         CALL wrk_dealloc( jpi, jpj, jpk, ztrdt, ztrds ) 
235      ENDIF
236      !
237      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' sbc  - Ta: ', mask1=tmask,   &
238         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
239      !
240      IF( nn_timing == 1 )  CALL timing_stop('tra_sbc')
241      !
242   END SUBROUTINE tra_sbc
243
244   !!======================================================================
245END MODULE trasbc
Note: See TracBrowser for help on using the repository browser.