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.
trcstp_rk3.F90 in NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP – NEMO

source: NEMO/branches/2021/dev_r14318_RK3_stage1/src/TOP/trcstp_rk3.F90 @ 15281

Last change on this file since 15281 was 15281, checked in by techene, 3 years ago

#2715 RK3 bug correction

File size: 17.0 KB
Line 
1MODULE trcstp_rk3
2   !!======================================================================
3   !!                       ***  MODULE trcstp_rk3  ***
4   !! Time-stepping    : time loop of opa for passive tracer
5   !!======================================================================
6   !! History :  1.0  !  2004-03  (C. Ethe)  Original
7   !!            4.1  !  2019-08  (A. Coward, D. Storkey) rewrite in preparation for new timestepping scheme
8   !!----------------------------------------------------------------------
9#if defined key_top
10   !!----------------------------------------------------------------------
11   !!   trc_stp       : passive tracer system time-stepping
12   !!----------------------------------------------------------------------
13   USE par_trc        ! need jptra, number of passive tracers
14   USE oce_trc        ! ocean dynamics and active tracers variables
15   USE sbc_oce
16   USE trc
17   USE trctrp         ! passive tracers transport
18   USE trcsms         ! passive tracers sources and sinks
19   USE trcwri
20   USE trcrst
21   USE trdtrc_oce
22   USE trdmxl_trc
23   USE sms_pisces,  ONLY : ln_check_mass
24   !
25   USE prtctl         ! Print control for debbuging
26   USE iom            !
27   USE in_out_manager !
28
29   IMPLICIT NONE
30   PRIVATE
31
32   PUBLIC   trc_stp_start   ! called by stprk3_stg
33   PUBLIC   trc_stp_end     ! called by stprk3_stg
34
35   LOGICAL  ::   llnew                   ! ???
36   LOGICAL  ::   l_trcstat               ! flag for tracer statistics
37   REAL(wp) ::   rdt_sampl               ! ???
38   INTEGER  ::   nb_rec_per_day, ktdcy   ! ???
39   REAL(wp) ::   rsecfst, rseclast       ! ???
40   REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   qsr_arr   ! save qsr during TOP time-step
41
42#  include "domzgr_substitute.h90"
43   !!----------------------------------------------------------------------
44   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
45   !! $Id: trcstp.F90 14086 2020-12-04 11:37:14Z cetlod $
46   !! Software governed by the CeCILL license (see ./LICENSE)
47   !!----------------------------------------------------------------------
48CONTAINS
49 
50   SUBROUTINE trc_stp_start( kt, Kbb, Kmm, Krhs, Kaa )
51      !!-------------------------------------------------------------------
52      !!                     ***  ROUTINE trc_stp_start  ***
53      !!                     
54      !! ** Purpose :   Time loop of opa for passive tracer
55      !!
56      !! ** Method  :   Compute the passive tracers trends
57      !!                Update the passive tracers
58      !!-------------------------------------------------------------------
59      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index
60      INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs, Kaa ! time level indices
61      !
62      INTEGER ::   jk, jn   ! dummy loop indices
63      CHARACTER (len=25) ::   charout   !
64      !!-------------------------------------------------------------------
65      !
66      IF( ln_timing )   CALL timing_start('trc_stp_start')
67      !
68      l_trcstat  = ( sn_cfctl%l_trcstat ) .AND. &
69           &       ( ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) )
70!!st should be in init of top
71      IF( kt == nittrc000 )                      CALL trc_stp_ctl   ! control
72      IF( kt == nittrc000 .AND. lk_trdmxl_trc )  CALL trd_mxl_trc_init    ! trends: Mixed-layer
73!!st-gm
74!!st-gm a faire uniquement au stage 3
75!!st      !
76      IF( .NOT.ln_linssh ) THEN                                           ! update ocean volume due to ssh temporal evolution
77         DO jk = 1, jpk
78            cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk)
79         END DO
80         IF( l_trcstat .OR. kt == nitrst .OR. ( ln_check_mass .AND. kt == nitend ) )   &
81            &     areatot = glob_sum( 'trcstp', cvol(:,:,:) )
82      ENDIF
83      !
84      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt )
85      !   
86      !
87      IF(sn_cfctl%l_prttrc) THEN
88         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear
89         CALL prt_ctl_info( charout, cdcomp = 'top' )
90      ENDIF
91      !
92!!st      tr(:,:,:,:,Krhs) = 0._wp
93      !
94      CALL trc_rst_opn  ( kt )                            ! Open tracer restart file
95      IF( lrst_trc )  CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar
96!!st cf. stage 3      CALL trc_wri      ( kt,      Kmm            )       ! output of passive tracers with iom I/O manager
97      !
98      IF( ln_timing )   CALL timing_stop('trc_stp_start')
99      !
100   END SUBROUTINE trc_stp_start
101
102
103   SUBROUTINE trc_stp( kt, Kbb, Kmm, Krhs, Kaa )
104      !!-------------------------------------------------------------------
105      !!                     ***  ROUTINE trc_stp  ***
106      !!                     
107      !! ** Purpose :   Time loop of opa for passive tracer
108      !!
109      !! ** Method  :   Compute the passive tracers trends
110      !!                Update the passive tracers
111      !!-------------------------------------------------------------------
112      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index
113      INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs, Kaa ! time level indices
114      !
115      INTEGER ::   jk, jn   ! dummy loop indices
116      REAL(wp)::   ztrai    ! local scalar
117      CHARACTER (len=25) ::   charout   !
118      !!-------------------------------------------------------------------
119      !
120      IF( ln_timing )   CALL timing_start('trc_stp')
121      !
122      IF( l_1st_euler .OR. ln_top_euler ) THEN     ! at nittrc000
123         rDt_trc =  rn_Dt           ! = rn_Dt (use or restarting with Euler time stepping)
124      ELSEIF( kt <= nittrc000 + 1 ) THEN                                     ! at nittrc000 or nittrc000+1
125         rDt_trc = 2. * rn_Dt       ! = 2 rn_Dt (leapfrog)
126      ENDIF
127      !
128      IF( .NOT.ln_linssh ) THEN                                           ! update ocean volume due to ssh temporal evolution
129         DO jk = 1, jpk
130            cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk)
131         END DO
132         IF ( l_trcstat .OR. kt == nitrst .OR. ( ln_check_mass .AND. kt == nitend )   &
133            & .OR. iom_use( "pno3tot" ) .OR. iom_use( "ppo4tot" ) .OR. iom_use( "psiltot" )   &
134            & .OR. iom_use( "palktot" ) .OR. iom_use( "pfertot" ) )                           &
135            &     areatot = glob_sum( 'trcstp', cvol(:,:,:) )
136      ENDIF
137      !
138      tr(:,:,:,:,Krhs) = 0._wp
139      !
140      CALL trc_wri      ( kt,      Kmm            )       ! output of passive tracers with iom I/O manager
141      CALL trc_sms      ( kt, Kbb, Kmm, Krhs      )       ! tracers: sinks and sources
142      CALL trc_trp      ( kt, Kbb, Kmm, Krhs, Kaa )       ! transport of passive tracers
143           !
144           ! Note passive tracers have been time-filtered in trc_trp but the time level
145           ! indices will not be swapped until after tra_atf/dyn_atf/ssh_atf in stp. Subsequent calls here
146           ! anticipate this update which will be: Nrhs= Nbb ; Nbb = Nnn ; Nnn = Naa ; Naa = Nrhs
147           ! and use the filtered levels explicitly.
148           !
149      IF( kt == nittrc000 ) THEN
150         CALL iom_close( numrtr )                         ! close input tracer restart file
151         IF(lrxios) CALL iom_context_finalize(      cr_toprst_cxt          )
152         IF(lwm) CALL FLUSH( numont )                     ! flush namelist output
153      ENDIF
154      IF( lrst_trc )            CALL trc_rst_wri  ( kt, Kbb, Kmm, Kaa  )       ! write tracer restart file
155      IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,      Kaa       )       ! trends: Mixed-layer
156      !
157      IF( ln_top_euler ) THEN 
158         ! For Euler timestepping for TOP we need to copy the "after" to the "now" fields
159         ! here then after the (leapfrog) swapping of the time-level indices in OCE/step.F90 we have
160         ! "before" fields = "now" fields.
161         tr(:,:,:,:,Kmm) = tr(:,:,:,:,Kaa)
162      ENDIF
163      !
164      IF (l_trcstat) THEN
165         ztrai = 0._wp                                                   !  content of all tracers
166         DO jn = 1, jptra
167            ztrai = ztrai + glob_sum( 'trcstp', tr(:,:,:,jn,Kaa) * cvol(:,:,:)   )
168         END DO
169         IF( lwm ) WRITE(numstr,9300) kt,  ztrai / areatot
170      ENDIF
1719300  FORMAT(i10,D23.16)
172      !
173      IF( ln_timing )   CALL timing_stop('trc_stp')
174      !
175   END SUBROUTINE trc_stp
176
177
178   SUBROUTINE trc_stp_end( kt, Kbb, Kmm, Kaa )
179      !!-------------------------------------------------------------------
180      !!                     ***  ROUTINE trc_stp_end  ***
181      !!                     
182      !! ** Purpose :   Time loop of opa for passive tracer
183      !!
184      !! ** Method  :   Compute the passive tracers trends
185      !!                Update the passive tracers
186      !!-------------------------------------------------------------------
187      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index
188      INTEGER, INTENT( in ) :: Kbb, Kmm, Kaa ! time level indices
189      !
190      INTEGER ::   jk, jn   ! dummy loop indices
191      REAL(wp)::   ztrai    ! local scalar
192      CHARACTER (len=25) ::   charout   !
193      !!-------------------------------------------------------------------
194      !
195      IF( ln_timing )   CALL timing_start('trc_stp_end')
196      !
197            !
198           ! Note passive tracers have been time-filtered in trc_trp but the time level
199           ! indices will not be swapped until after tra_atf/dyn_atf/ssh_atf in stp. Subsequent calls here
200           ! anticipate this update which will be: Nrhs= Nbb ; Nbb = Nnn ; Nnn = Naa ; Naa = Nrhs
201           ! and use the filtered levels explicitly.
202           !
203      IF( kt == nittrc000 ) THEN
204         CALL iom_close( numrtr )                         ! close input tracer restart file
205         IF(lrxios) CALL iom_context_finalize(      cr_toprst_cxt          )
206         IF(lwm) CALL FLUSH( numont )                     ! flush namelist output
207      ENDIF
208      IF( lrst_trc )            CALL trc_rst_wri  ( kt, Kbb, Kmm, Kaa )       ! write tracer restart file
209      IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,           Kaa )       ! trends: Mixed-layer
210      !
211      IF (l_trcstat) THEN
212         ztrai = 0._wp                                                   !  content of all tracers
213         DO jn = 1, jptra
214            ztrai = ztrai + glob_sum( 'trcstp_rk3', tr(:,:,:,jn,Kaa) * cvol(:,:,:)   ) !!st cvol@Kmm weird !!
215         END DO
216         IF( lwm ) WRITE(numstr,9300) kt,  ztrai / areatot
217      ENDIF
218      !
2199300  FORMAT(i10,D23.16)
220      !
221      CALL trc_wri      ( kt,      Kaa            )       ! output of passive tracers with iom I/O manager (!!st Kbb car après le swap des indices !!st-correction FAUX on est avant : le swap a lieu après le CALL à stp_RK3_stg(3) )
222      !
223      IF( ln_timing )   CALL timing_stop('trc_stp_end')
224      !
225   END SUBROUTINE trc_stp_end
226
227
228   SUBROUTINE trc_stp_ctl
229      !!----------------------------------------------------------------------
230      !!                     ***  ROUTINE trc_stp_ctl  ***
231      !! ** Purpose :        Control  + ocean volume
232      !!----------------------------------------------------------------------
233      !
234      ! Define logical parameter ton control dirunal cycle in TOP
235      l_trcdm2dc = ln_dm2dc .OR. ( ln_cpl .AND. ncpl_qsr_freq /= 1 .AND. ncpl_qsr_freq /= 0 )
236      l_trcdm2dc = l_trcdm2dc .AND. .NOT. l_offline
237      !
238      IF( l_trcdm2dc .AND. lwp )   CALL ctl_warn( 'Coupling with passive tracers and used of diurnal cycle.',   &
239         &                           'Computation of a daily mean shortwave for some biogeochemical models ' )
240      !
241   END SUBROUTINE trc_stp_ctl
242
243
244   SUBROUTINE trc_mean_qsr( kt )
245      !!----------------------------------------------------------------------
246      !!             ***  ROUTINE trc_mean_qsr  ***
247      !!
248      !! ** Purpose :  Compute daily mean qsr for biogeochemical model in case
249      !!               of diurnal cycle
250      !!
251      !! ** Method  : store in TOP the qsr every hour ( or every time-step if the latter
252      !!              is greater than 1 hour ) and then, compute the  mean with
253      !!              a moving average over 24 hours.
254      !!              In coupled mode, the sampling is done at every coupling frequency
255      !!----------------------------------------------------------------------
256      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
257      !
258      INTEGER  ::   jn   ! dummy loop indices
259      REAL(wp) ::   zkt, zrec     ! local scalars
260      CHARACTER(len=1) ::   cl1   ! 1 character
261      CHARACTER(len=2) ::   cl2   ! 2 characters
262      !!----------------------------------------------------------------------
263      !
264      IF( ln_timing )   CALL timing_start('trc_mean_qsr')
265      !
266      IF( kt == nittrc000 ) THEN
267         IF( ln_cpl )  THEN 
268            rdt_sampl = rday / ncpl_qsr_freq
269            nb_rec_per_day = ncpl_qsr_freq
270         ELSE 
271            rdt_sampl = MAX( 3600., rn_Dt )
272            nb_rec_per_day = INT( rday / rdt_sampl )
273         ENDIF
274         !
275         IF(lwp) THEN
276            WRITE(numout,*) 
277            WRITE(numout,*) ' Sampling frequency dt = ', rdt_sampl, 's','   Number of sampling per day  nrec = ', nb_rec_per_day
278            WRITE(numout,*) 
279         ENDIF
280         !
281         ALLOCATE( qsr_arr(jpi,jpj,nb_rec_per_day ) )
282         !
283         !                                            !* Restart: read in restart file
284         IF( ln_rsttr .AND. nn_rsttr /= 0 .AND. iom_varid( numrtr, 'qsr_mean' , ldstop = .FALSE. ) > 0  &
285           &                              .AND. iom_varid( numrtr, 'qsr_arr_1', ldstop = .FALSE. ) > 0  &
286           &                              .AND. iom_varid( numrtr, 'ktdcy'    , ldstop = .FALSE. ) > 0  &
287           &                              .AND. iom_varid( numrtr, 'nrdcy'    , ldstop = .FALSE. ) > 0  ) THEN
288            CALL iom_get( numrtr, 'ktdcy', zkt ) 
289            rsecfst = INT( zkt ) * rn_Dt
290            IF(lwp) WRITE(numout,*) 'trc_qsr_mean:   qsr_mean read in the restart file at time-step rsecfst =', rsecfst, ' s '
291            CALL iom_get( numrtr, jpdom_auto, 'qsr_mean', qsr_mean )   !  A mean of qsr
292            CALL iom_get( numrtr, 'nrdcy', zrec )   !  Number of record per days
293            IF( INT( zrec ) == nb_rec_per_day ) THEN
294               DO jn = 1, nb_rec_per_day 
295                  IF( jn <= 9 )  THEN
296                    WRITE(cl1,'(i1)') jn
297                    CALL iom_get( numrtr, jpdom_auto, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )   !  A mean of qsr
298                  ELSE
299                    WRITE(cl2,'(i2.2)') jn
300                    CALL iom_get( numrtr, jpdom_auto, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )   !  A mean of qsr
301                  ENDIF
302              END DO
303            ELSE
304               DO jn = 1, nb_rec_per_day
305                  qsr_arr(:,:,jn) = qsr_mean(:,:)
306               END DO
307            ENDIF
308         ELSE                                         !* no restart: set from nit000 values
309            IF(lwp) WRITE(numout,*) 'trc_qsr_mean:   qsr_mean set to nit000 values'
310            rsecfst  = kt * rn_Dt
311            !
312            qsr_mean(:,:) = qsr(:,:)
313            DO jn = 1, nb_rec_per_day
314               qsr_arr(:,:,jn) = qsr_mean(:,:)
315            END DO
316         ENDIF
317         !
318      ENDIF
319      !
320      rseclast = kt * rn_Dt
321      !
322      llnew   = ( rseclast - rsecfst ) >=  rdt_sampl    !   new shortwave to store
323      IF( llnew ) THEN
324          ktdcy = kt
325          IF( lwp .AND. kt < nittrc000 + 100 ) WRITE(numout,*) ' New shortwave to sample for TOP at time kt = ', ktdcy, &
326             &                      ' time = ', rseclast/3600.,'hours '
327          rsecfst = rseclast
328          DO jn = 1, nb_rec_per_day - 1
329             qsr_arr(:,:,jn) = qsr_arr(:,:,jn+1)
330          END DO
331          qsr_arr (:,:,nb_rec_per_day) = qsr(:,:)
332          qsr_mean(:,:                ) = SUM( qsr_arr(:,:,:), 3 ) / nb_rec_per_day
333      ENDIF
334      !
335      IF( lrst_trc ) THEN    !* Write the mean of qsr in restart file
336         IF(lwp) WRITE(numout,*)
337         IF(lwp) WRITE(numout,*) 'trc_mean_qsr : write qsr_mean in restart file  kt =', kt
338         IF(lwp) WRITE(numout,*) '~~~~~~~'
339         zkt  = REAL( ktdcy, wp )
340         zrec = REAL( nb_rec_per_day, wp )
341         CALL iom_rstput( kt, nitrst, numrtw, 'ktdcy', zkt  )
342         CALL iom_rstput( kt, nitrst, numrtw, 'nrdcy', zrec )
343          DO jn = 1, nb_rec_per_day 
344             IF( jn <= 9 )  THEN
345               WRITE(cl1,'(i1)') jn
346               CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )
347             ELSE
348               WRITE(cl2,'(i2.2)') jn
349               CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )
350             ENDIF
351         END DO
352         CALL iom_rstput( kt, nitrst, numrtw, 'qsr_mean', qsr_mean(:,:) )
353      ENDIF
354      !
355      IF( ln_timing )   CALL timing_stop('trc_mean_qsr')
356      !
357   END SUBROUTINE trc_mean_qsr
358
359#else
360   !!----------------------------------------------------------------------
361   !!   Default key                                     NO passive tracers
362   !!----------------------------------------------------------------------
363CONTAINS
364   SUBROUTINE trc_stp( kt )        ! Empty routine
365      WRITE(*,*) 'trc_stp: You should not have seen this print! error?', kt
366   END SUBROUTINE trc_stp
367#endif
368
369   !!======================================================================
370END MODULE trcstp_rk3
Note: See TracBrowser for help on using the repository browser.