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.F90 in NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap/src/TOP – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap/src/TOP/trcstp.F90 @ 11463

Last change on this file since 11463 was 11427, checked in by davestorkey, 5 years ago

dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps_rewrite_time_filterswap :
Restore independent time level indices for TOP in order to enable the option for
TOP to have a different timestep to OCE (nn_dttrc > 1). But note that this version of
the code only works for nn_dttrc=1. Also sort out the time-level swapping for OFF.
This commit passes the GYRE_PISCES and ORCA2_OFF_PISCES tests but fails restartability
and bit-comparison with the control for ORCA2_ICE_PISCES.

  • Property svn:keywords set to Id
File size: 12.6 KB
Line 
1MODULE trcstp
2   !!======================================================================
3   !!                       ***  MODULE trcstp  ***
4   !! Time-stepping    : time loop of opa for passive tracer
5   !!======================================================================
6   !! History :  1.0  !  2004-03  (C. Ethe)  Original
7   !!----------------------------------------------------------------------
8#if defined key_top
9   !!----------------------------------------------------------------------
10   !!   trc_stp       : passive tracer system time-stepping
11   !!----------------------------------------------------------------------
12   USE oce_trc        ! ocean dynamics and active tracers variables
13   USE sbc_oce
14   USE trc
15   USE trctrp         ! passive tracers transport
16   USE trcsms         ! passive tracers sources and sinks
17   USE trcwri
18   USE trcrst
19   USE trcsub         !
20   USE trdtrc_oce
21   USE trdmxl_trc
22   USE sms_pisces,  ONLY : ln_check_mass
23   !
24   USE prtctl_trc     ! Print control for debbuging
25   USE iom            !
26   USE in_out_manager !
27
28   IMPLICIT NONE
29   PRIVATE
30
31   PUBLIC   trc_stp    ! called by step
32
33   LOGICAL  ::   llnew                   ! ???
34   REAL(wp) ::   rdt_sampl               ! ???
35   INTEGER  ::   nb_rec_per_day, ktdcy   ! ???
36   REAL(wp) ::   rsecfst, rseclast       ! ???
37   REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   qsr_arr   ! save qsr during TOP time-step
38
39   !!----------------------------------------------------------------------
40   !! time level indices
41   !!----------------------------------------------------------------------
42   INTEGER, PUBLIC :: Nbb_trc, Nnn_trc, Naa_trc, Nrhs_trc      !! used by trc_init
43
44   !!----------------------------------------------------------------------
45   !! NEMO/TOP 4.0 , NEMO Consortium (2018)
46   !! $Id$
47   !! Software governed by the CeCILL license (see ./LICENSE)
48   !!----------------------------------------------------------------------
49CONTAINS
50
51   SUBROUTINE trc_stp( kt, Kbb_oce, Kmm_oce, Krhs_oce, Kaa_oce )
52      !!-------------------------------------------------------------------
53      !!                     ***  ROUTINE trc_stp  ***
54      !!                     
55      !! ** Purpose :   Time loop of opa for passive tracer
56      !!
57      !! ** Method  :   Compute the passive tracers trends
58      !!                Update the passive tracers
59      !!-------------------------------------------------------------------
60      INTEGER, INTENT( in ) :: kt                  ! ocean time-step index
61      INTEGER, INTENT( in ) :: Kbb_oce, Kmm_oce, Krhs_oce, Kaa_oce ! time level indices
62      !
63      INTEGER ::   jk, jn   ! dummy loop indices
64      REAL(wp)::   ztrai    ! local scalar
65      LOGICAL ::   ll_trcstat ! local logical
66      CHARACTER (len=25) ::   charout   !
67      !!-------------------------------------------------------------------
68      !
69      IF( ln_timing )   CALL timing_start('trc_stp')
70      !
71      IF( ( neuler == 0 .AND. kt == nittrc000 ) .OR. ln_top_euler ) THEN     ! at nittrc000
72         r2dttrc =  rdttrc           ! = rdttrc (use or restarting with Euler time stepping)
73      ELSEIF( kt <= nittrc000 + nn_dttrc ) THEN          ! at nittrc000 or nittrc000+1
74         r2dttrc = 2. * rdttrc       ! = 2 rdttrc (leapfrog)
75      ENDIF
76      !
77      ll_trcstat  = ( ln_ctl .OR. sn_cfctl%l_trcstat ) .AND. &
78     &              ( ( MOD( kt, sn_cfctl%ptimincr ) == 0 ) .OR. ( kt == nitend ) )
79      IF( kt == nittrc000 .AND. lk_trdmxl_trc )  CALL trd_mxl_trc_init    ! trends: Mixed-layer
80      !
81      IF( .NOT.ln_linssh ) THEN                                           ! update ocean volume due to ssh temporal evolution
82         DO jk = 1, jpk
83            cvol(:,:,jk) = e1e2t(:,:) * e3t(:,:,jk,Kmm_oce) * tmask(:,:,jk)
84         END DO
85         IF ( ln_ctl .OR. kt == nitrst .OR. ( ln_check_mass .AND. kt == nitend )              &
86            & .OR. iom_use( "pno3tot" ) .OR. iom_use( "ppo4tot" ) .OR. iom_use( "psiltot" )   &
87            & .OR. iom_use( "palktot" ) .OR. iom_use( "pfertot" ) )                           &
88            &     areatot = glob_sum( 'trcstp', cvol(:,:,:) )
89      ENDIF
90      !
91      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt )
92      !   
93      IF( nn_dttrc == 1 )  THEN
94         IF(lwp) WRITE(numout,*) "Kbb_oce, Kmm_oce, Kaa_oce, Krhs_oce : ",Kbb_oce, Kmm_oce, Kaa_oce, Krhs_oce
95         IF(lwp) WRITE(numout,*) "Nbb_trc, Nnn_trc, Naa_trc, Nrhs_trc : ",Nbb_trc, Nnn_trc, Naa_trc, Nrhs_trc
96         IF(lwp) CALL FLUSH(numout)
97         CALL mppsync()     
98         IF( Kmm_oce /= Nnn_trc .OR. Kaa_oce /= Naa_trc .OR. Krhs_oce /= Nrhs_trc ) THEN
99            ! The nn_dttrc == 1 case depends on the OCE and TRC time indices being the same always.
100            ! If this is not the case then something has gone wrong.
101            CALL ctl_stop( 'trc_stp : nn_dttrc = 1 but OCE and TRC time indices are different! Something has gone wrong.' )
102         ENDIF
103      ELSE
104         CALL trc_sub_stp( kt, Nbb_trc, Nnn_trc, Nrhs_trc )  ! averaging physical variables for sub-stepping
105      ENDIF
106      !   
107      IF( MOD( kt , nn_dttrc ) == 0 ) THEN      ! only every nn_dttrc time step
108         !
109         IF(ln_ctl) THEN
110            WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear
111            CALL prt_ctl_trc_info(charout)
112         ENDIF
113         !
114         tr(:,:,:,:,Nrhs_trc) = 0.e0
115         !
116                                   CALL trc_rst_opn  ( kt )       ! Open tracer restart file
117         IF( lrst_trc )            CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar
118                                   CALL trc_wri      ( kt,          Nnn_trc                    )  ! output of passive tracers with iom I/O manager
119                                   CALL trc_sms      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc          )  ! tracers: sinks and sources
120                                   CALL trc_trp      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc, Naa_trc )  ! transport of passive tracers
121         IF( kt == nittrc000 ) THEN
122            CALL iom_close( numrtr )       ! close input tracer restart file
123            IF(lwm) CALL FLUSH( numont )   ! flush namelist output
124         ENDIF
125         IF( lrst_trc )            CALL trc_rst_wri  ( kt, Nbb_trc, Nnn_trc, Nrhs_trc )       ! write tracer restart file
126         IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,          Nnn_trc           )       ! trends: Mixed-layer
127         !
128         IF( nn_dttrc /= 1   )     CALL trc_sub_reset( kt, Nbb_trc, Nnn_trc, Nrhs_trc )       ! resetting physical variables when sub-stepping
129         !
130      ENDIF
131      !
132      IF (ll_trcstat) THEN
133         ztrai = 0._wp                                                   !  content of all tracers
134         DO jn = 1, jptra
135            ztrai = ztrai + glob_sum( 'trcstp', tr(:,:,:,jn,Nnn_trc) * cvol(:,:,:)   )
136         END DO
137         IF( lwm ) WRITE(numstr,9300) kt,  ztrai / areatot
138      ENDIF
1399300  FORMAT(i10,D23.16)
140      !
141      IF( ln_timing )   CALL timing_stop('trc_stp')
142      !
143   END SUBROUTINE trc_stp
144
145   SUBROUTINE trc_mean_qsr( kt )
146      !!----------------------------------------------------------------------
147      !!             ***  ROUTINE trc_mean_qsr  ***
148      !!
149      !! ** Purpose :  Compute daily mean qsr for biogeochemical model in case
150      !!               of diurnal cycle
151      !!
152      !! ** Method  : store in TOP the qsr every hour ( or every time-step if the latter
153      !!              is greater than 1 hour ) and then, compute the  mean with
154      !!              a moving average over 24 hours.
155      !!              In coupled mode, the sampling is done at every coupling frequency
156      !!----------------------------------------------------------------------
157      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
158      !
159      INTEGER  ::   jn   ! dummy loop indices
160      REAL(wp) ::   zkt, zrec     ! local scalars
161      CHARACTER(len=1) ::   cl1   ! 1 character
162      CHARACTER(len=2) ::   cl2   ! 2 characters
163      !!----------------------------------------------------------------------
164      !
165      IF( ln_timing )   CALL timing_start('trc_mean_qsr')
166      !
167      IF( kt == nittrc000 ) THEN
168         IF( ln_cpl )  THEN 
169            rdt_sampl = rday / ncpl_qsr_freq
170            nb_rec_per_day = ncpl_qsr_freq
171         ELSE 
172            rdt_sampl = MAX( 3600., rdttrc )
173            nb_rec_per_day = INT( rday / rdt_sampl )
174         ENDIF
175         !
176         IF(lwp) THEN
177            WRITE(numout,*) 
178            WRITE(numout,*) ' Sampling frequency dt = ', rdt_sampl, 's','   Number of sampling per day  nrec = ', nb_rec_per_day
179            WRITE(numout,*) 
180         ENDIF
181         !
182         ALLOCATE( qsr_arr(jpi,jpj,nb_rec_per_day ) )
183         !
184         !                                            !* Restart: read in restart file
185         IF( ln_rsttr .AND. nn_rsttr /= 0 .AND. iom_varid( numrtr, 'qsr_mean' , ldstop = .FALSE. ) > 0  &
186           &                              .AND. iom_varid( numrtr, 'qsr_arr_1', ldstop = .FALSE. ) > 0  &
187           &                              .AND. iom_varid( numrtr, 'ktdcy'    , ldstop = .FALSE. ) > 0  &
188           &                              .AND. iom_varid( numrtr, 'nrdcy'    , ldstop = .FALSE. ) > 0  ) THEN
189
190            CALL iom_get( numrtr, 'ktdcy', zkt ) 
191            rsecfst = INT( zkt ) * rdttrc
192            IF(lwp) WRITE(numout,*) 'trc_qsr_mean:   qsr_mean read in the restart file at time-step rsecfst =', rsecfst, ' s '
193            CALL iom_get( numrtr, jpdom_autoglo, 'qsr_mean', qsr_mean )   !  A mean of qsr
194            CALL iom_get( numrtr, 'nrdcy', zrec )   !  Number of record per days
195            IF( INT( zrec ) == nb_rec_per_day ) THEN
196               DO jn = 1, nb_rec_per_day 
197                  IF( jn <= 9 )  THEN
198                    WRITE(cl1,'(i1)') jn
199                    CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )   !  A mean of qsr
200                  ELSE
201                    WRITE(cl2,'(i2.2)') jn
202                    CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )   !  A mean of qsr
203                  ENDIF
204              END DO
205            ELSE
206               DO jn = 1, nb_rec_per_day
207                  qsr_arr(:,:,jn) = qsr_mean(:,:)
208               ENDDO
209            ENDIF
210         ELSE                                         !* no restart: set from nit000 values
211            IF(lwp) WRITE(numout,*) 'trc_qsr_mean:   qsr_mean set to nit000 values'
212            rsecfst  = kt * rdttrc
213            !
214            qsr_mean(:,:) = qsr(:,:)
215            DO jn = 1, nb_rec_per_day
216               qsr_arr(:,:,jn) = qsr_mean(:,:)
217            END DO
218         ENDIF
219         !
220      ENDIF
221      !
222      rseclast = kt * rdttrc
223      !
224      llnew   = ( rseclast - rsecfst ) .ge.  rdt_sampl    !   new shortwave to store
225      IF( llnew ) THEN
226          ktdcy = kt
227          IF( lwp .AND. kt < nittrc000 + 100 ) WRITE(numout,*) ' New shortwave to sample for TOP at time kt = ', ktdcy, &
228             &                      ' time = ', rseclast/3600.,'hours '
229          rsecfst = rseclast
230          DO jn = 1, nb_rec_per_day - 1
231             qsr_arr(:,:,jn) = qsr_arr(:,:,jn+1)
232          ENDDO
233          qsr_arr (:,:,nb_rec_per_day) = qsr(:,:)
234          qsr_mean(:,:                ) = SUM( qsr_arr(:,:,:), 3 ) / nb_rec_per_day
235      ENDIF
236      !
237      IF( lrst_trc ) THEN    !* Write the mean of qsr in restart file
238         IF(lwp) WRITE(numout,*)
239         IF(lwp) WRITE(numout,*) 'trc_mean_qsr : write qsr_mean in restart file  kt =', kt
240         IF(lwp) WRITE(numout,*) '~~~~~~~'
241         zkt  = REAL( ktdcy, wp )
242         zrec = REAL( nb_rec_per_day, wp )
243         CALL iom_rstput( kt, nitrst, numrtw, 'ktdcy', zkt  )
244         CALL iom_rstput( kt, nitrst, numrtw, 'nrdcy', zrec )
245          DO jn = 1, nb_rec_per_day 
246             IF( jn <= 9 )  THEN
247               WRITE(cl1,'(i1)') jn
248               CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )
249             ELSE
250               WRITE(cl2,'(i2.2)') jn
251               CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )
252             ENDIF
253         END DO
254         CALL iom_rstput( kt, nitrst, numrtw, 'qsr_mean', qsr_mean(:,:) )
255      ENDIF
256      !
257      IF( ln_timing )   CALL timing_stop('trc_mean_qsr')
258      !
259   END SUBROUTINE trc_mean_qsr
260
261#else
262   !!----------------------------------------------------------------------
263   !!   Default key                                     NO passive tracers
264   !!----------------------------------------------------------------------
265CONTAINS
266   SUBROUTINE trc_stp( kt )        ! Empty routine
267      WRITE(*,*) 'trc_stp: You should not have seen this print! error?', kt
268   END SUBROUTINE trc_stp
269#endif
270
271   !!======================================================================
272END MODULE trcstp
Note: See TracBrowser for help on using the repository browser.