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/src/TOP – NEMO

source: NEMO/branches/2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps/src/TOP/trcstp.F90 @ 11506

Last change on this file since 11506 was 11506, checked in by acc, 5 years ago

Branch 2019/dev_r10721_KERNEL-02_Storkey_Coward_IMMERSE_first_steps. Small correction to trcstp.F90 to restore SETTE restartability (GYRE_PISCES, at least) with the current state of the branch. Next stage will be to remove the TOP-specific time indices (Nnn_trc etc.)

  • Property svn:keywords set to Id
File size: 11.8 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   !!            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 oce_trc        ! ocean dynamics and active tracers variables
14   USE sbc_oce
15   USE trc
16   USE trctrp         ! passive tracers transport
17   USE trcsms         ! passive tracers sources and sinks
18   USE trcwri
19   USE trcrst
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 + 1 ) 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( Kmm_oce /= Nnn_trc .OR. Kaa_oce /= Naa_trc .OR. Krhs_oce /= Nrhs_trc ) THEN
94         ! The OCE and TRC time indices should be the same always.
95         ! If this is not the case then something has gone wrong.
96         CALL ctl_stop( 'trc_stp : OCE and TRC time indices are different! Something has gone wrong.' )
97      ENDIF
98      !   
99      !
100      IF(ln_ctl) THEN
101         WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear
102         CALL prt_ctl_trc_info(charout)
103      ENDIF
104      !
105      tr(:,:,:,:,Nrhs_trc) = 0.e0
106      !
107      CALL trc_rst_opn  ( kt )       ! Open tracer restart file
108      IF( lrst_trc )            CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar
109      CALL trc_wri      ( kt,          Nnn_trc                    )  ! output of passive tracers with iom I/O manager
110      CALL trc_sms      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc          )  ! tracers: sinks and sources
111      CALL trc_trp      ( kt, Nbb_trc, Nnn_trc, Nrhs_trc, Naa_trc )  ! transport of passive tracers
112      IF( kt == nittrc000 ) THEN
113         CALL iom_close( numrtr )       ! close input tracer restart file
114         IF(lwm) CALL FLUSH( numont )   ! flush namelist output
115      ENDIF
116      IF( lrst_trc )            CALL trc_rst_wri  ( kt, Nbb_trc, Nnn_trc, Nrhs_trc )       ! write tracer restart file
117      IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt,          Nnn_trc           )       ! trends: Mixed-layer
118      !
119      IF (ll_trcstat) THEN
120         ztrai = 0._wp                                                   !  content of all tracers
121         DO jn = 1, jptra
122            ztrai = ztrai + glob_sum( 'trcstp', tr(:,:,:,jn,Nnn_trc) * cvol(:,:,:)   )
123         END DO
124         IF( lwm ) WRITE(numstr,9300) kt,  ztrai / areatot
125      ENDIF
1269300  FORMAT(i10,D23.16)
127      !
128      IF( ln_timing )   CALL timing_stop('trc_stp')
129      !
130   END SUBROUTINE trc_stp
131
132   SUBROUTINE trc_mean_qsr( kt )
133      !!----------------------------------------------------------------------
134      !!             ***  ROUTINE trc_mean_qsr  ***
135      !!
136      !! ** Purpose :  Compute daily mean qsr for biogeochemical model in case
137      !!               of diurnal cycle
138      !!
139      !! ** Method  : store in TOP the qsr every hour ( or every time-step if the latter
140      !!              is greater than 1 hour ) and then, compute the  mean with
141      !!              a moving average over 24 hours.
142      !!              In coupled mode, the sampling is done at every coupling frequency
143      !!----------------------------------------------------------------------
144      INTEGER, INTENT( in ) ::   kt   ! ocean time-step index
145      !
146      INTEGER  ::   jn   ! dummy loop indices
147      REAL(wp) ::   zkt, zrec     ! local scalars
148      CHARACTER(len=1) ::   cl1   ! 1 character
149      CHARACTER(len=2) ::   cl2   ! 2 characters
150      !!----------------------------------------------------------------------
151      !
152      IF( ln_timing )   CALL timing_start('trc_mean_qsr')
153      !
154      IF( kt == nittrc000 ) THEN
155         IF( ln_cpl )  THEN 
156            rdt_sampl = rday / ncpl_qsr_freq
157            nb_rec_per_day = ncpl_qsr_freq
158         ELSE 
159            rdt_sampl = MAX( 3600., rdttrc )
160            nb_rec_per_day = INT( rday / rdt_sampl )
161         ENDIF
162         !
163         IF(lwp) THEN
164            WRITE(numout,*) 
165            WRITE(numout,*) ' Sampling frequency dt = ', rdt_sampl, 's','   Number of sampling per day  nrec = ', nb_rec_per_day
166            WRITE(numout,*) 
167         ENDIF
168         !
169         ALLOCATE( qsr_arr(jpi,jpj,nb_rec_per_day ) )
170         !
171         !                                            !* Restart: read in restart file
172         IF( ln_rsttr .AND. nn_rsttr /= 0 .AND. iom_varid( numrtr, 'qsr_mean' , ldstop = .FALSE. ) > 0  &
173           &                              .AND. iom_varid( numrtr, 'qsr_arr_1', ldstop = .FALSE. ) > 0  &
174           &                              .AND. iom_varid( numrtr, 'ktdcy'    , ldstop = .FALSE. ) > 0  &
175           &                              .AND. iom_varid( numrtr, 'nrdcy'    , ldstop = .FALSE. ) > 0  ) THEN
176
177            CALL iom_get( numrtr, 'ktdcy', zkt ) 
178            rsecfst = INT( zkt ) * rdttrc
179            IF(lwp) WRITE(numout,*) 'trc_qsr_mean:   qsr_mean read in the restart file at time-step rsecfst =', rsecfst, ' s '
180            CALL iom_get( numrtr, jpdom_autoglo, 'qsr_mean', qsr_mean )   !  A mean of qsr
181            CALL iom_get( numrtr, 'nrdcy', zrec )   !  Number of record per days
182            IF( INT( zrec ) == nb_rec_per_day ) THEN
183               DO jn = 1, nb_rec_per_day 
184                  IF( jn <= 9 )  THEN
185                    WRITE(cl1,'(i1)') jn
186                    CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )   !  A mean of qsr
187                  ELSE
188                    WRITE(cl2,'(i2.2)') jn
189                    CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )   !  A mean of qsr
190                  ENDIF
191              END DO
192            ELSE
193               DO jn = 1, nb_rec_per_day
194                  qsr_arr(:,:,jn) = qsr_mean(:,:)
195               ENDDO
196            ENDIF
197         ELSE                                         !* no restart: set from nit000 values
198            IF(lwp) WRITE(numout,*) 'trc_qsr_mean:   qsr_mean set to nit000 values'
199            rsecfst  = kt * rdttrc
200            !
201            qsr_mean(:,:) = qsr(:,:)
202            DO jn = 1, nb_rec_per_day
203               qsr_arr(:,:,jn) = qsr_mean(:,:)
204            END DO
205         ENDIF
206         !
207      ENDIF
208      !
209      rseclast = kt * rdttrc
210      !
211      llnew   = ( rseclast - rsecfst ) .ge.  rdt_sampl    !   new shortwave to store
212      IF( llnew ) THEN
213          ktdcy = kt
214          IF( lwp .AND. kt < nittrc000 + 100 ) WRITE(numout,*) ' New shortwave to sample for TOP at time kt = ', ktdcy, &
215             &                      ' time = ', rseclast/3600.,'hours '
216          rsecfst = rseclast
217          DO jn = 1, nb_rec_per_day - 1
218             qsr_arr(:,:,jn) = qsr_arr(:,:,jn+1)
219          ENDDO
220          qsr_arr (:,:,nb_rec_per_day) = qsr(:,:)
221          qsr_mean(:,:                ) = SUM( qsr_arr(:,:,:), 3 ) / nb_rec_per_day
222      ENDIF
223      !
224      IF( lrst_trc ) THEN    !* Write the mean of qsr in restart file
225         IF(lwp) WRITE(numout,*)
226         IF(lwp) WRITE(numout,*) 'trc_mean_qsr : write qsr_mean in restart file  kt =', kt
227         IF(lwp) WRITE(numout,*) '~~~~~~~'
228         zkt  = REAL( ktdcy, wp )
229         zrec = REAL( nb_rec_per_day, wp )
230         CALL iom_rstput( kt, nitrst, numrtw, 'ktdcy', zkt  )
231         CALL iom_rstput( kt, nitrst, numrtw, 'nrdcy', zrec )
232          DO jn = 1, nb_rec_per_day 
233             IF( jn <= 9 )  THEN
234               WRITE(cl1,'(i1)') jn
235               CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )
236             ELSE
237               WRITE(cl2,'(i2.2)') jn
238               CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )
239             ENDIF
240         END DO
241         CALL iom_rstput( kt, nitrst, numrtw, 'qsr_mean', qsr_mean(:,:) )
242      ENDIF
243      !
244      IF( ln_timing )   CALL timing_stop('trc_mean_qsr')
245      !
246   END SUBROUTINE trc_mean_qsr
247
248#else
249   !!----------------------------------------------------------------------
250   !!   Default key                                     NO passive tracers
251   !!----------------------------------------------------------------------
252CONTAINS
253   SUBROUTINE trc_stp( kt )        ! Empty routine
254      WRITE(*,*) 'trc_stp: You should not have seen this print! error?', kt
255   END SUBROUTINE trc_stp
256#endif
257
258   !!======================================================================
259END MODULE trcstp
Note: See TracBrowser for help on using the repository browser.