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

source: trunk/NEMOGCM/NEMO/OPA_SRC/TRA/trasbc.F90 @ 7698

Last change on this file since 7698 was 7698, checked in by mocavero, 7 years ago

update trunk with OpenMP parallelization

  • Property svn:keywords set to Id
File size: 13.5 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   !!            3.6  !  2014-11  (P. Mathiot) isf melting forcing
12   !!----------------------------------------------------------------------
13
14   !!----------------------------------------------------------------------
15   !!   tra_sbc       : update the tracer trend at ocean surface
16   !!----------------------------------------------------------------------
17   USE oce            ! ocean dynamics and active tracers
18   USE sbc_oce        ! surface boundary condition: ocean
19   USE dom_oce        ! ocean space domain variables
20   USE phycst         ! physical constant
21   USE eosbn2         ! Equation Of State
22   USE sbcmod         ! ln_rnf 
23   USE sbcrnf         ! River runoff 
24   USE sbcisf         ! Ice shelf   
25   USE iscplini       ! Ice sheet coupling
26   USE traqsr         ! solar radiation penetration
27   USE trd_oce        ! trends: ocean variables
28   USE trdtra         ! trends manager: tracers
29   !
30   USE in_out_manager ! I/O manager
31   USE prtctl         ! Print control
32   USE iom            ! xIOS server
33   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
34   USE wrk_nemo       ! Memory Allocation
35   USE timing         ! Timing
36
37   IMPLICIT NONE
38   PRIVATE
39
40   PUBLIC   tra_sbc   ! routine called by step.F90
41
42   !! * Substitutions
43#  include "vectopt_loop_substitute.h90"
44   !!----------------------------------------------------------------------
45   !! NEMO/OPA 3.7 , NEMO Consortium (2014)
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 :   The (air+ice)-sea flux has two components:
60      !!      (1) Fext, external forcing (i.e. flux through the (air+ice)-sea interface);
61      !!      (2) Fwe , tracer carried with the water that is exchanged with air+ice.
62      !!               The input forcing fields (emp, rnf, sfx, isf) contain Fext+Fwe,
63      !!             they are simply added to the tracer trend (tsa).
64      !!               In linear free surface case (ln_linssh=T), the volume of the
65      !!             ocean does not change with the water exchanges at the (air+ice)-sea
66      !!             interface. Therefore another term has to be added, to mimic the
67      !!             concentration/dilution effect associated with water exchanges.
68      !!
69      !! ** Action  : - Update tsa with the surface boundary condition trend
70      !!              - send trends to trdtra module for further diagnostics(l_trdtra=T)
71      !!----------------------------------------------------------------------
72      INTEGER, INTENT(in) ::   kt   ! ocean time-step index
73      !
74      INTEGER  ::   ji, jj, jk, jn        ! dummy loop indices 
75      INTEGER  ::   ikt, ikb              ! local integers
76      REAL(wp) ::   zfact, z1_e3t, zdep   ! local scalar
77      REAL(wp), POINTER, DIMENSION(:,:,:) ::  ztrdt, ztrds
78      !!----------------------------------------------------------------------
79      !
80      IF( nn_timing == 1 )  CALL timing_start('tra_sbc')
81      !
82      IF( kt == nit000 ) THEN
83         IF(lwp) WRITE(numout,*)
84         IF(lwp) WRITE(numout,*) 'tra_sbc : TRAcer Surface Boundary Condition'
85         IF(lwp) WRITE(numout,*) '~~~~~~~ '
86      ENDIF
87      !
88      IF( l_trdtra ) THEN                    !* Save ta and sa trends
89         CALL wrk_alloc( jpi, jpj, jpk, ztrdt, ztrds ) 
90!$OMP PARALLEL DO schedule(static) private(jk, jj, ji)
91         DO jk = 1, jpk
92            DO jj = 1, jpj
93               DO ji = 1, jpi
94                  ztrdt(ji,jj,jk) = tsa(ji,jj,jk,jp_tem)
95                  ztrds(ji,jj,jk) = tsa(ji,jj,jk,jp_sal)
96               END DO
97            END DO
98         END DO
99      ENDIF
100      !
101!!gm  This should be moved into sbcmod.F90 module ? (especially now that ln_traqsr is read in namsbc namelist)
102      IF( .NOT.ln_traqsr ) THEN     ! no solar radiation penetration
103!$OMP PARALLEL DO schedule(static) private(jj, ji)
104         DO jj = 1, jpj
105            DO ji = 1, jpi
106               qns(ji,jj) = qns(ji,jj) + qsr(ji,jj)      ! total heat flux in qns
107               qsr(ji,jj) = 0._wp                     ! qsr set to zero
108            END DO
109         END DO
110      ENDIF
111
112      !----------------------------------------
113      !        EMP, SFX and QNS effects
114      !----------------------------------------
115      !                             !==  Set before sbc tracer content fields  ==!
116      IF( kt == nit000 ) THEN             !* 1st time-step
117         IF( ln_rstart .AND.    &               ! Restart: read in restart file
118              & iom_varid( numror, 'sbc_hc_b', ldstop = .FALSE. ) > 0 ) THEN
119            IF(lwp) WRITE(numout,*) '          nit000-1 sbc tracer content field read in the restart file'
120            zfact = 0.5_wp
121            CALL iom_get( numror, jpdom_autoglo, 'sbc_hc_b', sbc_tsc_b(:,:,jp_tem) )   ! before heat content sbc trend
122            CALL iom_get( numror, jpdom_autoglo, 'sbc_sc_b', sbc_tsc_b(:,:,jp_sal) )   ! before salt content sbc trend
123         ELSE                                   ! No restart or restart not found: Euler forward time stepping
124            zfact = 1._wp
125            DO jn = 1, jpts
126!$OMP PARALLEL DO schedule(static) private(jj, ji)
127               DO jj = 1, jpj
128                  DO ji = 1, jpi
129                     sbc_tsc(ji,jj,jn) = 0._wp
130                     sbc_tsc_b(ji,jj,jn) = 0._wp
131                  END DO
132               END DO
133            END DO
134         ENDIF
135      ELSE                                !* other time-steps: swap of forcing fields
136         zfact = 0.5_wp
137         DO jn = 1, jpts
138!$OMP PARALLEL DO schedule(static) private(jj, ji)
139            DO jj = 1, jpj
140               DO ji = 1, jpi
141                  sbc_tsc_b(ji,jj,jn) = sbc_tsc(ji,jj,jn)
142               END DO
143            END DO
144         END DO
145      ENDIF
146      !                             !==  Now sbc tracer content fields  ==!
147!$OMP PARALLEL DO schedule(static) private(jj, ji)
148      DO jj = 2, jpj
149         DO ji = fs_2, fs_jpim1   ! vector opt.
150            sbc_tsc(ji,jj,jp_tem) = r1_rau0_rcp * qns(ji,jj)   ! non solar heat flux
151            sbc_tsc(ji,jj,jp_sal) = r1_rau0     * sfx(ji,jj)   ! salt flux due to freezing/melting
152         END DO
153      END DO
154      IF( ln_linssh ) THEN                !* linear free surface 
155!$OMP PARALLEL DO schedule(static) private(jj, ji)
156         DO jj = 2, jpj                         !==>> add concentration/dilution effect due to constant volume cell
157            DO ji = fs_2, fs_jpim1   ! vector opt.
158               sbc_tsc(ji,jj,jp_tem) = sbc_tsc(ji,jj,jp_tem) + r1_rau0 * emp(ji,jj) * tsn(ji,jj,1,jp_tem)
159               sbc_tsc(ji,jj,jp_sal) = sbc_tsc(ji,jj,jp_sal) + r1_rau0 * emp(ji,jj) * tsn(ji,jj,1,jp_sal)
160            END DO
161         END DO                                 !==>> output c./d. term
162         IF( iom_use('emp_x_sst') )   CALL iom_put( "emp_x_sst", emp (:,:) * tsn(:,:,1,jp_tem) )
163         IF( iom_use('emp_x_sss') )   CALL iom_put( "emp_x_sss", emp (:,:) * tsn(:,:,1,jp_sal) )
164      ENDIF
165      !
166      DO jn = 1, jpts               !==  update tracer trend  ==!
167!$OMP PARALLEL DO schedule(static) private(jj, ji)
168         DO jj = 2, jpj
169            DO ji = fs_2, fs_jpim1   ! vector opt. 
170               tsa(ji,jj,1,jn) = tsa(ji,jj,1,jn) + zfact * ( sbc_tsc_b(ji,jj,jn) + sbc_tsc(ji,jj,jn) ) / e3t_n(ji,jj,1)
171            END DO
172         END DO
173      END DO
174      !                 
175      IF( lrst_oce ) THEN           !==  write sbc_tsc in the ocean restart file  ==!
176         CALL iom_rstput( kt, nitrst, numrow, 'sbc_hc_b', sbc_tsc(:,:,jp_tem) )
177         CALL iom_rstput( kt, nitrst, numrow, 'sbc_sc_b', sbc_tsc(:,:,jp_sal) )
178      ENDIF
179      !
180      !----------------------------------------
181      !       Ice Shelf effects (ISF)
182      !     tbl treated as in Losh (2008) JGR
183      !----------------------------------------
184      !
185!!gm BUG ?   Why no differences between non-linear and linear free surface ?
186!!gm         probably taken into account in r1_hisf_tbl : to be verified
187      IF( ln_isf ) THEN
188         zfact = 0.5_wp
189         DO jj = 2, jpj
190            DO ji = fs_2, fs_jpim1
191               !
192               ikt = misfkt(ji,jj)
193               ikb = misfkb(ji,jj)
194               !
195               ! level fully include in the ice shelf boundary layer
196               ! sign - because fwf sign of evapo (rnf sign of precip)
197               DO jk = ikt, ikb - 1
198               ! compute trend
199                  tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem)                                                &
200                     &           + zfact * ( risf_tsc_b(ji,jj,jp_tem) + risf_tsc(ji,jj,jp_tem) )             &
201                     &           * r1_hisf_tbl(ji,jj)
202               END DO
203   
204               ! level partially include in ice shelf boundary layer
205               ! compute trend
206               tsa(ji,jj,ikb,jp_tem) = tsa(ji,jj,ikb,jp_tem)                                                 &
207                  &              + zfact * ( risf_tsc_b(ji,jj,jp_tem) + risf_tsc(ji,jj,jp_tem) )             &
208                  &              * r1_hisf_tbl(ji,jj) * ralpha(ji,jj)
209
210            END DO
211         END DO
212         IF( lrst_oce ) THEN
213            CALL iom_rstput( kt, nitrst, numrow, 'fwf_isf_b', fwfisf  (:,:)        )
214            CALL iom_rstput( kt, nitrst, numrow, 'isf_hc_b' , risf_tsc(:,:,jp_tem) )
215            CALL iom_rstput( kt, nitrst, numrow, 'isf_sc_b' , risf_tsc(:,:,jp_sal) )
216         ENDIF
217      END IF
218      !
219      !----------------------------------------
220      !        River Runoff effects
221      !----------------------------------------
222      !
223      IF( ln_rnf ) THEN         ! input of heat and salt due to river runoff
224         zfact = 0.5_wp
225         DO jj = 2, jpj 
226            DO ji = fs_2, fs_jpim1
227               IF( rnf(ji,jj) /= 0._wp ) THEN
228                  zdep = zfact / h_rnf(ji,jj)
229                  DO jk = 1, nk_rnf(ji,jj)
230                                        tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem)                                 &
231                                           &                 +  ( rnf_tsc_b(ji,jj,jp_tem) + rnf_tsc(ji,jj,jp_tem) ) * zdep
232                     IF( ln_rnf_sal )   tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal)                                 &
233                                           &                 +  ( rnf_tsc_b(ji,jj,jp_sal) + rnf_tsc(ji,jj,jp_sal) ) * zdep 
234                  END DO
235               ENDIF
236            END DO 
237         END DO 
238      ENDIF
239
240      IF( iom_use('rnf_x_sst') )   CALL iom_put( "rnf_x_sst", rnf*tsn(:,:,1,jp_tem) )   ! runoff term on sst
241      IF( iom_use('rnf_x_sss') )   CALL iom_put( "rnf_x_sss", rnf*tsn(:,:,1,jp_sal) )   ! runoff term on sss
242
243      !
244      !----------------------------------------
245      !        Ice Sheet coupling imbalance correction to have conservation
246      !----------------------------------------
247      !
248      IF( ln_iscpl .AND. ln_hsb) THEN         ! input of heat and salt due to river runoff
249!$OMP PARALLEL DO schedule(static) private(jk, jj, ji, zdep)
250         DO jk = 1,jpk
251            DO jj = 2, jpj 
252               DO ji = fs_2, fs_jpim1
253                  zdep = 1._wp / e3t_n(ji,jj,jk) 
254                  tsa(ji,jj,jk,jp_tem) = tsa(ji,jj,jk,jp_tem) - htsc_iscpl(ji,jj,jk,jp_tem)                       &
255                      &                                         * zdep
256                  tsa(ji,jj,jk,jp_sal) = tsa(ji,jj,jk,jp_sal) - htsc_iscpl(ji,jj,jk,jp_sal)                       &
257                      &                                         * zdep 
258               END DO 
259            END DO 
260         END DO
261      ENDIF
262
263      IF( l_trdtra )   THEN                      ! save the horizontal diffusive trends for further diagnostics
264!$OMP PARALLEL DO schedule(static) private(jk, jj, ji)
265         DO jk = 1, jpk
266            DO jj = 1, jpj
267               DO ji = 1, jpi
268                  ztrdt(ji,jj,jk) = tsa(ji,jj,jk,jp_tem) - ztrdt(ji,jj,jk)
269                  ztrds(ji,jj,jk) = tsa(ji,jj,jk,jp_sal) - ztrds(ji,jj,jk)
270               END DO 
271            END DO 
272         END DO
273         CALL trd_tra( kt, 'TRA', jp_tem, jptra_nsr, ztrdt )
274         CALL trd_tra( kt, 'TRA', jp_sal, jptra_nsr, ztrds )
275         CALL wrk_dealloc( jpi, jpj, jpk, ztrdt, ztrds ) 
276      ENDIF
277      !
278      IF(ln_ctl)   CALL prt_ctl( tab3d_1=tsa(:,:,:,jp_tem), clinfo1=' sbc  - Ta: ', mask1=tmask,   &
279         &                       tab3d_2=tsa(:,:,:,jp_sal), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
280      !
281      IF( nn_timing == 1 )  CALL timing_stop('tra_sbc')
282      !
283   END SUBROUTINE tra_sbc
284
285   !!======================================================================
286END MODULE trasbc
Note: See TracBrowser for help on using the repository browser.