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/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/TRA – NEMO

source: branches/2011/DEV_r2739_STFC_dCSE/NEMOGCM/NEMO/OPA_SRC/TRA/trasbc.F90 @ 4401

Last change on this file since 4401 was 3211, checked in by spickles2, 12 years ago

Stephen Pickles, 11 Dec 2011

Commit to bring the rest of the DCSE NEMO development branch
in line with the latest development version. This includes
array index re-ordering of all OPA_SRC/.

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