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 NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA – NEMO

source: NEMO/branches/2019/dev_r11943_MERGE_2019/src/OCE/TRA/trasbc.F90 @ 12150

Last change on this file since 12150 was 12150, checked in by davestorkey, 4 years ago

2019/dev_r11943_MERGE_2019: Merge in UKMO_MERGE_2019.

  • Property svn:keywords set to Id
File size: 11.4 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   !!            4.1  !  2019-09  (P. Mathiot) isf moved in traisf
13   !!----------------------------------------------------------------------
14
15   !!----------------------------------------------------------------------
16   !!   tra_sbc       : update the tracer trend at ocean surface
17   !!----------------------------------------------------------------------
18   USE oce            ! ocean dynamics and active tracers
19   USE sbc_oce        ! surface boundary condition: ocean
20   USE dom_oce        ! ocean space domain variables
21   USE phycst         ! physical constant
22   USE eosbn2         ! Equation Of State
23   USE sbcmod         ! ln_rnf 
24   USE sbcrnf         ! River runoff 
25   USE traqsr         ! solar radiation penetration
26   USE trd_oce        ! trends: ocean variables
27   USE trdtra         ! trends manager: tracers
28#if defined key_asminc   
29   USE asminc         ! Assimilation increment
30#endif
31   !
32   USE in_out_manager ! I/O manager
33   USE prtctl         ! Print control
34   USE iom            ! xIOS server
35   USE lbclnk         ! ocean lateral boundary conditions (or mpp link)
36   USE timing         ! Timing
37
38   IMPLICIT NONE
39   PRIVATE
40
41   PUBLIC   tra_sbc   ! routine called by step.F90
42
43   !! * Substitutions
44#  include "vectopt_loop_substitute.h90"
45   !!----------------------------------------------------------------------
46   !! NEMO/OCE 4.0 , NEMO Consortium (2018)
47   !! $Id$
48   !! Software governed by the CeCILL license (see ./LICENSE)
49   !!----------------------------------------------------------------------
50CONTAINS
51
52   SUBROUTINE tra_sbc ( kt, Kmm, pts, Krhs )
53      !!----------------------------------------------------------------------
54      !!                  ***  ROUTINE tra_sbc  ***
55      !!                   
56      !! ** Purpose :   Compute the tracer surface boundary condition trend of
57      !!      (flux through the interface, concentration/dilution effect)
58      !!      and add it to the general trend of tracer equations.
59      !!
60      !! ** Method :   The (air+ice)-sea flux has two components:
61      !!      (1) Fext, external forcing (i.e. flux through the (air+ice)-sea interface);
62      !!      (2) Fwe , tracer carried with the water that is exchanged with air+ice.
63      !!               The input forcing fields (emp, rnf, sfx) contain Fext+Fwe,
64      !!             they are simply added to the tracer trend (ts(Krhs)).
65      !!               In linear free surface case (ln_linssh=T), the volume of the
66      !!             ocean does not change with the water exchanges at the (air+ice)-sea
67      !!             interface. Therefore another term has to be added, to mimic the
68      !!             concentration/dilution effect associated with water exchanges.
69      !!
70      !! ** Action  : - Update ts(Krhs) with the surface boundary condition trend
71      !!              - send trends to trdtra module for further diagnostics(l_trdtra=T)
72      !!----------------------------------------------------------------------
73      INTEGER,                                   INTENT(in   ) :: kt         ! ocean time-step index
74      INTEGER,                                   INTENT(in   ) :: Kmm, Krhs  ! time level indices
75      REAL(wp), DIMENSION(jpi,jpj,jpk,jpts,jpt), INTENT(inout) :: pts        ! active tracers and RHS of tracer equation
76      !
77      INTEGER  ::   ji, jj, jk, jn              ! dummy loop indices 
78      INTEGER  ::   ikt, ikb                    ! local integers
79      REAL(wp) ::   zfact, z1_e3t, zdep, ztim   ! local scalar
80      REAL(wp), ALLOCATABLE, DIMENSION(:,:,:) ::  ztrdt, ztrds
81      !!----------------------------------------------------------------------
82      !
83      IF( ln_timing )   CALL timing_start('tra_sbc')
84      !
85      IF( kt == nit000 ) THEN
86         IF(lwp) WRITE(numout,*)
87         IF(lwp) WRITE(numout,*) 'tra_sbc : TRAcer Surface Boundary Condition'
88         IF(lwp) WRITE(numout,*) '~~~~~~~ '
89      ENDIF
90      !
91      IF( l_trdtra ) THEN                    !* Save ta and sa trends
92         ALLOCATE( ztrdt(jpi,jpj,jpk) , ztrds(jpi,jpj,jpk) ) 
93         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs)
94         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs)
95      ENDIF
96      !
97!!gm  This should be moved into sbcmod.F90 module ? (especially now that ln_traqsr is read in namsbc namelist)
98      IF( .NOT.ln_traqsr ) THEN     ! no solar radiation penetration
99         qns(:,:) = qns(:,:) + qsr(:,:)      ! total heat flux in qns
100         qsr(:,:) = 0._wp                     ! qsr set to zero
101      ENDIF
102
103      !----------------------------------------
104      !        EMP, SFX and QNS effects
105      !----------------------------------------
106      !                             !==  Set before sbc tracer content fields  ==!
107      IF( kt == nit000 ) THEN             !* 1st time-step
108         IF( ln_rstart .AND.    &               ! Restart: read in restart file
109              & iom_varid( numror, 'sbc_hc_b', ldstop = .FALSE. ) > 0 ) THEN
110            IF(lwp) WRITE(numout,*) '          nit000-1 sbc tracer content field read in the restart file'
111            zfact = 0.5_wp
112            sbc_tsc(:,:,:) = 0._wp
113            CALL iom_get( numror, jpdom_autoglo, 'sbc_hc_b', sbc_tsc_b(:,:,jp_tem), ldxios = lrxios )   ! before heat content sbc trend
114            CALL iom_get( numror, jpdom_autoglo, 'sbc_sc_b', sbc_tsc_b(:,:,jp_sal), ldxios = lrxios )   ! before salt content sbc trend
115         ELSE                                   ! No restart or restart not found: Euler forward time stepping
116            zfact = 1._wp
117            sbc_tsc(:,:,:) = 0._wp
118            sbc_tsc_b(:,:,:) = 0._wp
119         ENDIF
120      ELSE                                !* other time-steps: swap of forcing fields
121         zfact = 0.5_wp
122         sbc_tsc_b(:,:,:) = sbc_tsc(:,:,:)
123      ENDIF
124      !                             !==  Now sbc tracer content fields  ==!
125      DO jj = 2, jpj
126         DO ji = fs_2, fs_jpim1   ! vector opt.
127            sbc_tsc(ji,jj,jp_tem) = r1_rau0_rcp * qns(ji,jj)   ! non solar heat flux
128            sbc_tsc(ji,jj,jp_sal) = r1_rau0     * sfx(ji,jj)   ! salt flux due to freezing/melting
129         END DO
130      END DO
131      IF( ln_linssh ) THEN                !* linear free surface 
132         DO jj = 2, jpj                         !==>> add concentration/dilution effect due to constant volume cell
133            DO ji = fs_2, fs_jpim1   ! vector opt.
134               sbc_tsc(ji,jj,jp_tem) = sbc_tsc(ji,jj,jp_tem) + r1_rau0 * emp(ji,jj) * pts(ji,jj,1,jp_tem,Kmm)
135               sbc_tsc(ji,jj,jp_sal) = sbc_tsc(ji,jj,jp_sal) + r1_rau0 * emp(ji,jj) * pts(ji,jj,1,jp_sal,Kmm)
136            END DO
137         END DO                                 !==>> output c./d. term
138         IF( iom_use('emp_x_sst') )   CALL iom_put( "emp_x_sst", emp (:,:) * pts(:,:,1,jp_tem,Kmm) )
139         IF( iom_use('emp_x_sss') )   CALL iom_put( "emp_x_sss", emp (:,:) * pts(:,:,1,jp_sal,Kmm) )
140      ENDIF
141      !
142      DO jn = 1, jpts               !==  update tracer trend  ==!
143         DO jj = 2, jpj
144            DO ji = fs_2, fs_jpim1   ! vector opt. 
145               pts(ji,jj,1,jn,Krhs) = pts(ji,jj,1,jn,Krhs) + zfact * ( sbc_tsc_b(ji,jj,jn) + sbc_tsc(ji,jj,jn) ) / e3t(ji,jj,1,Kmm)
146            END DO
147         END DO
148      END DO
149      !                 
150      IF( lrst_oce ) THEN           !==  write sbc_tsc in the ocean restart file  ==!
151         IF( lwxios ) CALL iom_swap(      cwxios_context          )
152         CALL iom_rstput( kt, nitrst, numrow, 'sbc_hc_b', sbc_tsc(:,:,jp_tem), ldxios = lwxios )
153         CALL iom_rstput( kt, nitrst, numrow, 'sbc_sc_b', sbc_tsc(:,:,jp_sal), ldxios = lwxios )
154         IF( lwxios ) CALL iom_swap(      cxios_context          )
155      ENDIF
156      !
157      !----------------------------------------
158      !        River Runoff effects
159      !----------------------------------------
160      !
161      IF( ln_rnf ) THEN         ! input of heat and salt due to river runoff
162         zfact = 0.5_wp
163         DO jj = 2, jpj 
164            DO ji = fs_2, fs_jpim1
165               IF( rnf(ji,jj) /= 0._wp ) THEN
166                  zdep = zfact / h_rnf(ji,jj)
167                  DO jk = 1, nk_rnf(ji,jj)
168                                        pts(ji,jj,jk,jp_tem,Krhs) = pts(ji,jj,jk,jp_tem,Krhs)                                  &
169                                           &                      +  ( rnf_tsc_b(ji,jj,jp_tem) + rnf_tsc(ji,jj,jp_tem) ) * zdep
170                     IF( ln_rnf_sal )   pts(ji,jj,jk,jp_sal,Krhs) = pts(ji,jj,jk,jp_sal,Krhs)                                  &
171                                           &                      +  ( rnf_tsc_b(ji,jj,jp_sal) + rnf_tsc(ji,jj,jp_sal) ) * zdep 
172                  END DO
173               ENDIF
174            END DO 
175         END DO 
176      ENDIF
177
178      IF( iom_use('rnf_x_sst') )   CALL iom_put( "rnf_x_sst", rnf*pts(:,:,1,jp_tem,Kmm) )   ! runoff term on sst
179      IF( iom_use('rnf_x_sss') )   CALL iom_put( "rnf_x_sss", rnf*pts(:,:,1,jp_sal,Kmm) )   ! runoff term on sss
180
181#if defined key_asminc
182      !
183      !----------------------------------------
184      !        Assmilation effects
185      !----------------------------------------
186      !
187      IF( ln_sshinc ) THEN         ! input of heat and salt due to assimilation
188          !
189         IF( ln_linssh ) THEN
190            DO jj = 2, jpj 
191               DO ji = fs_2, fs_jpim1
192                  ztim = ssh_iau(ji,jj) / e3t(ji,jj,1,Kmm)
193                  pts(ji,jj,1,jp_tem,Krhs) = pts(ji,jj,1,jp_tem,Krhs) + pts(ji,jj,1,jp_tem,Kmm) * ztim
194                  pts(ji,jj,1,jp_sal,Krhs) = pts(ji,jj,1,jp_sal,Krhs) + pts(ji,jj,1,jp_sal,Kmm) * ztim
195               END DO
196            END DO
197         ELSE
198            DO jj = 2, jpj 
199               DO ji = fs_2, fs_jpim1
200                  ztim = ssh_iau(ji,jj) / ( ht(ji,jj) + 1. - ssmask(ji, jj) )
201                  pts(ji,jj,:,jp_tem,Krhs) = pts(ji,jj,:,jp_tem,Krhs) + pts(ji,jj,:,jp_tem,Kmm) * ztim
202                  pts(ji,jj,:,jp_sal,Krhs) = pts(ji,jj,:,jp_sal,Krhs) + pts(ji,jj,:,jp_sal,Kmm) * ztim
203               END DO 
204            END DO 
205         ENDIF
206         !
207      ENDIF
208      !
209#endif
210      !
211      IF( l_trdtra )   THEN                      ! save the horizontal diffusive trends for further diagnostics
212         ztrdt(:,:,:) = pts(:,:,:,jp_tem,Krhs) - ztrdt(:,:,:)
213         ztrds(:,:,:) = pts(:,:,:,jp_sal,Krhs) - ztrds(:,:,:)
214         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_tem, jptra_nsr, ztrdt )
215         CALL trd_tra( kt, Kmm, Krhs, 'TRA', jp_sal, jptra_nsr, ztrds )
216         DEALLOCATE( ztrdt , ztrds ) 
217      ENDIF
218      !
219      IF(ln_ctl)   CALL prt_ctl( tab3d_1=pts(:,:,:,jp_tem,Krhs), clinfo1=' sbc  - Ta: ', mask1=tmask,   &
220         &                       tab3d_2=pts(:,:,:,jp_sal,Krhs), clinfo2=       ' Sa: ', mask2=tmask, clinfo3='tra' )
221      !
222      IF( ln_timing )   CALL timing_stop('tra_sbc')
223      !
224   END SUBROUTINE tra_sbc
225
226   !!======================================================================
227END MODULE trasbc
Note: See TracBrowser for help on using the repository browser.