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 @ 15321

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

#2605 #2715 some cleanning

File size: 13.1 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   !!            4.x  !  2021-08  (S. Techene, G. Madec) preparation and finalisation for RK3 time-stepping only
9   !!----------------------------------------------------------------------
10#if defined key_top
11   !!----------------------------------------------------------------------
12   !!   trc_stp_start : prepare  passive tracer system time-stepping
13   !!   trc_stp_end   : finalise passive tracer system time-stepping
14   !!----------------------------------------------------------------------
15   USE par_trc        ! need jptra, number of passive tracers
16   USE oce_trc        ! ocean dynamics and active tracers variables
17   USE sbc_oce
18   USE trc
19   USE trctrp         ! passive tracers transport
20   USE trcsms         ! passive tracers sources and sinks
21   USE trcwri
22   USE trcrst
23   USE trdtrc_oce
24   USE trdmxl_trc
25   USE sms_pisces,  ONLY : ln_check_mass
26   !
27   USE prtctl         ! Print control for debbuging
28   USE iom            !
29   USE in_out_manager !
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   trc_stp_start   ! called by stprk3_stg
35   PUBLIC   trc_stp_end     ! called by stprk3_stg
36
37   LOGICAL  ::   llnew                   ! ???
38   LOGICAL  ::   l_trcstat               ! flag for tracer statistics
39   REAL(wp) ::   rdt_sampl               ! ???
40   INTEGER  ::   nb_rec_per_day, ktdcy   ! ???
41   REAL(wp) ::   rsecfst, rseclast       ! ???
42   REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   qsr_arr   ! save qsr during TOP time-step
43
44#  include "domzgr_substitute.h90"
45   !!----------------------------------------------------------------------
46   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
47   !! $Id: trcstp.F90 14086 2020-12-04 11:37:14Z cetlod $
48   !! Software governed by the CeCILL license (see ./LICENSE)
49   !!----------------------------------------------------------------------
50CONTAINS
51 
52   SUBROUTINE trc_stp_start( kt, Kbb, Kmm, Krhs, Kaa )
53      !!-------------------------------------------------------------------
54      !!                     ***  ROUTINE trc_stp_start  ***
55      !!                     
56      !! ** Purpose :   Prepare time loop of opa for passive tracer
57      !!
58      !! ** Method  :   Compute the passive tracers trends
59      !!                Update the passive tracers
60      !!                Manage restart file
61      !!-------------------------------------------------------------------
62      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index
63      INTEGER, INTENT( in ) :: Kbb, Kmm, Krhs, Kaa ! time level indices
64      !
65      INTEGER ::   jk, jn   ! dummy loop indices
66      CHARACTER (len=25) ::   charout   !
67      !!-------------------------------------------------------------------
68      !
69      IF( ln_timing )   CALL timing_start('trc_stp_start')
70      !
71      l_trcstat  = ( sn_cfctl%l_trcstat ) .AND. &
72           &       ( ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) )
73      !
74      IF( kt == nittrc000 )                      CALL trc_stp_ctl   ! control
75      IF( kt == nittrc000 .AND. lk_trdmxl_trc )  CALL trd_mxl_trc_init    ! trends: Mixed-layer
76      !
77      IF( .NOT.ln_linssh ) THEN                                           ! update ocean volume due to ssh temporal evolution
78         DO jk = 1, jpk
79            cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm) * tmask(:,:,jk)
80         END DO
81         IF( l_trcstat .OR. kt == nitrst .OR. ( ln_check_mass .AND. kt == nitend ) )   &
82            &     areatot = glob_sum( 'trcstp', cvol(:,:,:) )
83      ENDIF
84      !
85      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt )
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      CALL trc_rst_opn  ( kt )                            ! Open tracer restart file
93      IF( lrst_trc )  CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar
94      !
95      IF( ln_timing )   CALL timing_stop('trc_stp_start')
96      !
97   END SUBROUTINE trc_stp_start
98
99
100   SUBROUTINE trc_stp_end( kt, Kbb, Kmm, Kaa )
101      !!-------------------------------------------------------------------
102      !!                     ***  ROUTINE trc_stp_end  ***
103      !!                     
104      !! ** Purpose :   Finalise time loop of opa for passive tracer
105      !!
106      !! ** Method  :   Write restart and outputs
107      !!-------------------------------------------------------------------
108      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index
109      INTEGER, INTENT( in ) :: Kbb, Kmm, Kaa ! time level indices
110      !
111      INTEGER ::   jk, jn   ! dummy loop indices
112      REAL(wp)::   ztrai    ! local scalar
113      CHARACTER (len=25) ::   charout   !
114      !!-------------------------------------------------------------------
115      !
116      IF( ln_timing )   CALL timing_start('trc_stp_end')
117      !
118      !
119           ! Note passive tracers have been time-filtered in trc_trp but the time level
120           ! indices will not be swapped until after tra_atf/dyn_atf/ssh_atf in stp. Subsequent calls here
121           ! anticipate this update which will be: Nrhs= Nbb ; Nbb = Nnn ; Nnn = Naa ; Naa = Nrhs
122           ! and use the filtered levels explicitly.
123           !
124      IF( kt == nittrc000 ) THEN
125         CALL iom_close( numrtr )                         ! close input tracer restart file
126         IF(lrxios) CALL iom_context_finalize(      cr_toprst_cxt          )
127         IF(lwm) CALL FLUSH( numont )                     ! flush namelist output
128      ENDIF
129      IF( lrst_trc )            CALL trc_rst_wri  ( kt, Kbb, Kmm, Kaa )       ! write tracer restart file
130      IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,           Kaa )       ! trends: Mixed-layer
131      !
132      IF (l_trcstat) THEN
133         ztrai = 0._wp                                    !  content of all tracers
134         DO jn = 1, jptra
135            ztrai = ztrai + glob_sum( 'trcstp_rk3', tr(:,:,:,jn,Kaa) * cvol(:,:,:)   ) !!st cvol@Kmm weird !!
136         END DO
137         IF( lwm ) WRITE(numstr,9300) kt,  ztrai / areatot
138      ENDIF
139      !
1409300  FORMAT(i10,D23.16)
141      !
142      CALL trc_wri      ( kt,      Kaa            )       ! output of passive tracers with iom I/O manager before time level swap
143      !
144      IF( ln_timing )   CALL timing_stop('trc_stp_end')
145      !
146   END SUBROUTINE trc_stp_end
147
148
149   SUBROUTINE trc_stp_ctl
150      !!----------------------------------------------------------------------
151      !!                     ***  ROUTINE trc_stp_ctl  ***
152      !! ** Purpose :        Control  + ocean volume
153      !!----------------------------------------------------------------------
154      !
155      ! Define logical parameter ton control dirunal cycle in TOP
156      l_trcdm2dc = ln_dm2dc .OR. ( ln_cpl .AND. ncpl_qsr_freq /= 1 .AND. ncpl_qsr_freq /= 0 )
157      l_trcdm2dc = l_trcdm2dc .AND. .NOT. l_offline
158      !
159      IF( l_trcdm2dc .AND. lwp )   CALL ctl_warn( 'Coupling with passive tracers and used of diurnal cycle.',   &
160         &                           'Computation of a daily mean shortwave for some biogeochemical models ' )
161      !
162   END SUBROUTINE trc_stp_ctl
163
164
165   SUBROUTINE trc_mean_qsr( kt )
166      !!----------------------------------------------------------------------
167      !!             ***  ROUTINE trc_mean_qsr  ***
168      !!
169      !! ** Purpose :  Compute daily mean qsr for biogeochemical model in case
170      !!               of diurnal cycle
171      !!
172      !! ** Method  : store in TOP the qsr every hour ( or every time-step if the latter
173      !!              is greater than 1 hour ) and then, compute the  mean with
174      !!              a moving average over 24 hours.
175      !!              In coupled mode, the sampling is done at every coupling frequency
176      !!----------------------------------------------------------------------
177      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
178      !
179      INTEGER  ::   jn   ! dummy loop indices
180      REAL(wp) ::   zkt, zrec     ! local scalars
181      CHARACTER(len=1) ::   cl1   ! 1 character
182      CHARACTER(len=2) ::   cl2   ! 2 characters
183      !!----------------------------------------------------------------------
184      !
185      IF( ln_timing )   CALL timing_start('trc_mean_qsr')
186      !
187      IF( kt == nittrc000 ) THEN
188         IF( ln_cpl )  THEN 
189            rdt_sampl = rday / ncpl_qsr_freq
190            nb_rec_per_day = ncpl_qsr_freq
191         ELSE 
192            rdt_sampl = MAX( 3600., rn_Dt )
193            nb_rec_per_day = INT( rday / rdt_sampl )
194         ENDIF
195         !
196         IF(lwp) THEN
197            WRITE(numout,*) 
198            WRITE(numout,*) ' Sampling frequency dt = ', rdt_sampl, 's','   Number of sampling per day  nrec = ', nb_rec_per_day
199            WRITE(numout,*) 
200         ENDIF
201         !
202         ALLOCATE( qsr_arr(jpi,jpj,nb_rec_per_day ) )
203         !
204         !                                            !* Restart: read in restart file
205         IF( ln_rsttr .AND. nn_rsttr /= 0 .AND. iom_varid( numrtr, 'qsr_mean' , ldstop = .FALSE. ) > 0  &
206           &                              .AND. iom_varid( numrtr, 'qsr_arr_1', ldstop = .FALSE. ) > 0  &
207           &                              .AND. iom_varid( numrtr, 'ktdcy'    , ldstop = .FALSE. ) > 0  &
208           &                              .AND. iom_varid( numrtr, 'nrdcy'    , ldstop = .FALSE. ) > 0  ) THEN
209            CALL iom_get( numrtr, 'ktdcy', zkt ) 
210            rsecfst = INT( zkt ) * rn_Dt
211            IF(lwp) WRITE(numout,*) 'trc_qsr_mean:   qsr_mean read in the restart file at time-step rsecfst =', rsecfst, ' s '
212            CALL iom_get( numrtr, jpdom_auto, 'qsr_mean', qsr_mean )   !  A mean of qsr
213            CALL iom_get( numrtr, 'nrdcy', zrec )   !  Number of record per days
214            IF( INT( zrec ) == nb_rec_per_day ) THEN
215               DO jn = 1, nb_rec_per_day 
216                  IF( jn <= 9 )  THEN
217                    WRITE(cl1,'(i1)') jn
218                    CALL iom_get( numrtr, jpdom_auto, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )   !  A mean of qsr
219                  ELSE
220                    WRITE(cl2,'(i2.2)') jn
221                    CALL iom_get( numrtr, jpdom_auto, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )   !  A mean of qsr
222                  ENDIF
223              END DO
224            ELSE
225               DO jn = 1, nb_rec_per_day
226                  qsr_arr(:,:,jn) = qsr_mean(:,:)
227               END DO
228            ENDIF
229         ELSE                                         !* no restart: set from nit000 values
230            IF(lwp) WRITE(numout,*) 'trc_qsr_mean:   qsr_mean set to nit000 values'
231            rsecfst  = kt * rn_Dt
232            !
233            qsr_mean(:,:) = qsr(:,:)
234            DO jn = 1, nb_rec_per_day
235               qsr_arr(:,:,jn) = qsr_mean(:,:)
236            END DO
237         ENDIF
238         !
239      ENDIF
240      !
241      rseclast = kt * rn_Dt
242      !
243      llnew   = ( rseclast - rsecfst ) >=  rdt_sampl    !   new shortwave to store
244      IF( llnew ) THEN
245          ktdcy = kt
246          IF( lwp .AND. kt < nittrc000 + 100 ) WRITE(numout,*) ' New shortwave to sample for TOP at time kt = ', ktdcy, &
247             &                      ' time = ', rseclast/3600.,'hours '
248          rsecfst = rseclast
249          DO jn = 1, nb_rec_per_day - 1
250             qsr_arr(:,:,jn) = qsr_arr(:,:,jn+1)
251          END DO
252          qsr_arr (:,:,nb_rec_per_day) = qsr(:,:)
253          qsr_mean(:,:                ) = SUM( qsr_arr(:,:,:), 3 ) / nb_rec_per_day
254      ENDIF
255      !
256      IF( lrst_trc ) THEN    !* Write the mean of qsr in restart file
257         IF(lwp) WRITE(numout,*)
258         IF(lwp) WRITE(numout,*) 'trc_mean_qsr : write qsr_mean in restart file  kt =', kt
259         IF(lwp) WRITE(numout,*) '~~~~~~~'
260         zkt  = REAL( ktdcy, wp )
261         zrec = REAL( nb_rec_per_day, wp )
262         CALL iom_rstput( kt, nitrst, numrtw, 'ktdcy', zkt  )
263         CALL iom_rstput( kt, nitrst, numrtw, 'nrdcy', zrec )
264          DO jn = 1, nb_rec_per_day 
265             IF( jn <= 9 )  THEN
266               WRITE(cl1,'(i1)') jn
267               CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )
268             ELSE
269               WRITE(cl2,'(i2.2)') jn
270               CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )
271             ENDIF
272         END DO
273         CALL iom_rstput( kt, nitrst, numrtw, 'qsr_mean', qsr_mean(:,:) )
274      ENDIF
275      !
276      IF( ln_timing )   CALL timing_stop('trc_mean_qsr')
277      !
278   END SUBROUTINE trc_mean_qsr
279
280#else
281   !!----------------------------------------------------------------------
282   !!   Default key                                     NO passive tracers
283   !!----------------------------------------------------------------------
284CONTAINS
285   SUBROUTINE trc_stp( kt )        ! Empty routine
286      WRITE(*,*) 'trc_stp: You should not have seen this print! error?', kt
287   END SUBROUTINE trc_stp
288#endif
289
290   !!======================================================================
291END MODULE trcstp_rk3
Note: See TracBrowser for help on using the repository browser.