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 branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC – NEMO

source: branches/UKMO/dev_r5518_GO6_under_ice_relax_dr_hook/NEMOGCM/NEMO/TOP_SRC/trcstp.F90 @ 11738

Last change on this file since 11738 was 11738, checked in by marc, 5 years ago

The Dr Hook changes from my perl code.

File size: 12.1 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 prtctl_trc       ! Print control for debbuging
18   USE trcdia
19   USE trcwri
20   USE trcrst
21   USE trcstat
22   USE trdtrc_oce
23   USE trdmxl_trc
24   USE iom
25   USE in_out_manager
26   USE trcsub
27
28   USE yomhook, ONLY: lhook, dr_hook
29   USE parkind1, ONLY: jprb, jpim
30
31   IMPLICIT NONE
32   PRIVATE
33
34   PUBLIC   trc_stp    ! called by step
35
36   REAL(wp), DIMENSION(:,:,:), SAVE, ALLOCATABLE ::   qsr_arr ! save qsr during TOP time-step
37   REAL(wp) :: rdt_sampl
38   INTEGER  :: nb_rec_per_day
39   INTEGER  :: isecfst, iseclast
40   LOGICAL  :: llnew
41
42   !! * Substitutions
43#  include "domzgr_substitute.h90"
44   !!----------------------------------------------------------------------
45   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
46   !! $Id$
47   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
48   !!----------------------------------------------------------------------
49CONTAINS
50
51   SUBROUTINE trc_stp( kt )
52      !!-------------------------------------------------------------------
53      !!                     ***  ROUTINE trc_stp  ***
54      !!                     
55      !! ** Purpose : Time loop of opa for passive tracer
56      !!
57      !! ** Method  :
58      !!              Compute the passive tracers trends
59      !!              Update the passive tracers
60      !!-------------------------------------------------------------------
61
62      USE dom_oce, ONLY: narea
63
64      INTEGER, INTENT( in ) ::  kt      ! ocean time-step index
65      INTEGER               ::  jk, jn  ! dummy loop indices
66      REAL(wp)              ::  ztrai
67      CHARACTER (len=25)    ::  charout 
68      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
69      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
70      REAL(KIND=jprb)               :: zhook_handle
71
72      CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_STP'
73
74      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
75
76      !!-------------------------------------------------------------------
77      !
78      IF( nn_timing == 1 )   CALL timing_start('trc_stp')
79      !
80      IF( kt == nittrc000 .AND. lk_trdmxl_trc )  CALL trd_mxl_trc_init    ! trends: Mixed-layer
81      !
82      IF( lk_vvl ) THEN                                                   ! update ocean volume due to ssh temporal evolution
83         DO jk = 1, jpk
84            cvol(:,:,jk) = e1e2t(:,:) * fse3t(:,:,jk) * tmask(:,:,jk)
85         END DO
86         IF( lk_degrad )  cvol(:,:,:) = cvol(:,:,:) * facvol(:,:,:)       ! degrad option: reduction by facvol
87         areatot         = glob_sum( cvol(:,:,:) )
88      ENDIF
89      !
90      IF( l_trcdm2dc )   CALL trc_mean_qsr( kt )
91      !   
92      IF( nn_dttrc /= 1 )   CALL trc_sub_stp( kt )  ! averaging physical variables for sub-stepping
93      !   
94      IF( MOD( kt , nn_dttrc ) == 0 ) THEN      ! only every nn_dttrc time step
95         !
96         IF(ln_ctl) THEN
97            WRITE(charout,FMT="('kt =', I4,'  d/m/y =',I2,I2,I4)") kt, nday, nmonth, nyear
98            CALL prt_ctl_trc_info(charout)
99         ENDIF
100         !
101         tra(:,:,:,:) = 0.e0
102         !
103                                   CALL trc_rst_opn  ( kt )       ! Open tracer restart file
104         IF( lrst_trc )            CALL trc_rst_cal  ( kt, 'WRITE' )   ! calendar
105         IF( lk_iomput ) THEN  ;   CALL trc_wri      ( kt )       ! output of passive tracers with iom I/O manager
106         ELSE                  ;   CALL trc_dia      ( kt )       ! output of passive tracers with old I/O manager
107         ENDIF
108                                   CALL trc_sms      ( kt )       ! tracers: sinks and sources
109# if defined key_debug_medusa
110         IF(lwp) WRITE(numout,*) ' MEDUSA trc_stp SMS complete at kt =', kt
111         CALL trc_rst_stat
112         CALL trc_rst_tra_stat
113         CALL flush(numout)
114# endif
115                                   CALL trc_trp      ( kt )       ! transport of passive tracers
116# if defined key_debug_medusa
117         IF(lwp) WRITE(numout,*) ' MEDUSA trc_stp transport complete at kt =', kt
118         CALL trc_rst_stat
119         CALL trc_rst_tra_stat
120         CALL flush(numout)
121# endif
122         IF( kt == nittrc000 ) THEN
123            CALL iom_close( numrtr )       ! close input tracer restart file
124            IF(lwm) CALL FLUSH( numont )   ! flush namelist output
125         ENDIF
126         IF( lrst_trc )            CALL trc_rst_wri  ( kt )       ! write tracer restart file
127         IF( lk_trdmxl_trc  )      CALL trd_mxl_trc  ( kt )       ! trends: Mixed-layer
128         !
129         IF( nn_dttrc /= 1   )     CALL trc_sub_reset( kt )       ! resetting physical variables when sub-stepping
130         !
131      ENDIF
132      !
133      IF (ln_ctl) THEN 
134         ! The following code is very expensive since it involves multiple
135         ! reproducible global sums over all tracer fields and is potentially 
136         ! called on every timestep. The results it produces are purely for
137         ! informational purposes and do not affect model evolution.
138         ! Hence we restrict its use by protecting it with the ln_ctl RTL
139         ! which should normally only be used under debugging conditions
140         ! and not in operational runs. We also need to restrict output 
141         ! to the master PE since there's no point duplicating the same results
142         ! on all processors.   
143         ztrai = 0._wp                                                   !  content of all tracers
144         DO jn = 1, jptra
145            ztrai = ztrai + glob_sum( trn(:,:,:,jn) * cvol(:,:,:)   )
146         END DO
147         IF( numstr /= -1 ) WRITE(numstr,9300) kt,  ztrai / areatot
1489300     FORMAT(i10,D23.16)
149      ENDIF
150      !
151      IF( nn_timing == 1 )   CALL timing_stop('trc_stp')
152      !
153      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
154   END SUBROUTINE trc_stp
155
156   SUBROUTINE trc_mean_qsr( kt )
157      !!----------------------------------------------------------------------
158      !!             ***  ROUTINE trc_mean_qsr  ***
159      !!
160      !! ** Purpose :  Compute daily mean qsr for biogeochemical model in case
161      !!               of diurnal cycle
162      !!
163      !! ** Method  : store in TOP the qsr every hour ( or every time-step if the latter
164      !!              is greater than 1 hour ) and then, compute the  mean with
165      !!              a moving average over 24 hours.
166      !!              In coupled mode, the sampling is done at every coupling frequency
167      !!----------------------------------------------------------------------
168      INTEGER, INTENT(in) ::   kt
169      INTEGER  :: jn
170      REAL(wp) :: zsecfst
171      CHARACTER(len=1)               ::   cl1                      ! 1 character
172      CHARACTER(len=2)               ::   cl2                      ! 2 characters
173      INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
174      INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
175      REAL(KIND=jprb)               :: zhook_handle
176
177      CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_MEAN_QSR'
178
179      IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
180
181
182      IF( kt == nittrc000 ) THEN
183         IF( ln_cpl )  THEN 
184            rdt_sampl = 86400. / ncpl_qsr_freq
185            nb_rec_per_day = ncpl_qsr_freq
186         ELSE 
187            rdt_sampl = MAX( 3600., rdt * nn_dttrc )
188            nb_rec_per_day = INT( 86400 / rdt_sampl )
189         ENDIF
190         !
191         IF( lwp ) THEN
192            WRITE(numout,*) 
193            WRITE(numout,*) ' Sampling frequency dt = ', rdt_sampl, 's','   Number of sampling per day  nrec = ', nb_rec_per_day
194            WRITE(numout,*) 
195         ENDIF
196         !
197         ALLOCATE( qsr_arr(jpi,jpj,nb_rec_per_day ) )
198         !
199         !                                            !* Restart: read in restart file
200         IF( ln_rsttr .AND. nn_rsttr /= 0 .AND. iom_varid( numrtr, 'qsr_mean' , ldstop = .FALSE. ) > 0 &
201                                          .AND. iom_varid( numrtr, 'qsr_arr_1', ldstop = .FALSE. ) > 0 &
202                                          .AND. iom_varid( numrtr, 'zsecfst'  , ldstop = .FALSE. ) > 0 ) THEN
203            IF(lwp) WRITE(numout,*) 'trc_qsr_mean:   qsr_mean read in the restart file'
204            CALL iom_get( numrtr, jpdom_autoglo, 'qsr_mean', qsr_mean )   !  A mean of qsr
205            CALL iom_get( numrtr, 'zsecfst', zsecfst )   !  A mean of qsr
206            isecfst = INT( zsecfst )
207            DO jn = 1, nb_rec_per_day 
208             IF( jn <= 9 )  THEN
209               WRITE(cl1,'(i1)') jn
210               CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )   !  A mean of qsr
211             ELSE
212               WRITE(cl2,'(i2.2)') jn
213               CALL iom_get( numrtr, jpdom_autoglo, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )   !  A mean of qsr
214             ENDIF
215           ENDDO
216         ELSE                                         !* no restart: set from nit000 values
217            IF(lwp) WRITE(numout,*) 'trc_qsr_mean:   qsr_mean set to nit000 values'
218            isecfst  = nsec_year + nsec1jan000   !   number of seconds between Jan. 1st 00h of nit000 year and the middle of time step
219            !
220            qsr_mean(:,:) = qsr(:,:)
221            DO jn = 1, nb_rec_per_day
222               qsr_arr(:,:,jn) = qsr_mean(:,:)
223            ENDDO
224         ENDIF
225         !
226      ENDIF
227      !
228      iseclast = nsec_year + nsec1jan000
229      !
230      llnew   = ( iseclast - isecfst )  > INT( rdt_sampl )   !   new shortwave to store
231      IF( llnew ) THEN
232          IF( lwp ) WRITE(numout,*) ' New shortwave to sample for TOP at time kt = ', kt, &
233             &                      ' time = ', (iseclast+rdt*nn_dttrc/2.)/3600.,'hours '
234          isecfst = iseclast
235          DO jn = 1, nb_rec_per_day - 1
236             qsr_arr(:,:,jn) = qsr_arr(:,:,jn+1)
237          ENDDO
238          qsr_arr (:,:,nb_rec_per_day) = qsr(:,:)
239          qsr_mean(:,:                ) = SUM( qsr_arr(:,:,:), 3 ) / nb_rec_per_day
240      ENDIF
241      !
242      IF( lrst_trc ) THEN    !* Write the mean of qsr in restart file
243         IF(lwp) WRITE(numout,*)
244         IF(lwp) WRITE(numout,*) 'trc_mean_qsr : write qsr_mean in restart file  kt =', kt
245         IF(lwp) WRITE(numout,*) '~~~~~~~'
246          DO jn = 1, nb_rec_per_day 
247             IF( jn <= 9 )  THEN
248               WRITE(cl1,'(i1)') jn
249               CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl1, qsr_arr(:,:,jn) )
250             ELSE
251               WRITE(cl2,'(i2.2)') jn
252               CALL iom_rstput( kt, nitrst, numrtw, 'qsr_arr_'//cl2, qsr_arr(:,:,jn) )
253             ENDIF
254         ENDDO
255         CALL iom_rstput( kt, nitrst, numrtw, 'qsr_mean', qsr_mean(:,:) )
256         zsecfst = REAL( isecfst, wp )
257         CALL iom_rstput( kt, nitrst, numrtw, 'zsecfst', zsecfst )
258      ENDIF
259      !
260      IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
261   END SUBROUTINE trc_mean_qsr
262
263#else
264   !!----------------------------------------------------------------------
265   !!   Default key                                     NO passive tracers
266   !!----------------------------------------------------------------------
267CONTAINS
268   SUBROUTINE trc_stp( kt )        ! Empty routine
269   INTEGER(KIND=jpim), PARAMETER :: zhook_in = 0
270   INTEGER(KIND=jpim), PARAMETER :: zhook_out = 1
271   REAL(KIND=jprb)               :: zhook_handle
272
273   CHARACTER(LEN=*), PARAMETER :: RoutineName='TRC_STP'
274
275   IF (lhook) CALL dr_hook(RoutineName,zhook_in,zhook_handle)
276
277      WRITE(*,*) 'trc_stp: You should not have seen this print! error?', kt
278   IF (lhook) CALL dr_hook(RoutineName,zhook_out,zhook_handle)
279   END SUBROUTINE trc_stp
280#endif
281
282   !!======================================================================
283END MODULE trcstp
Note: See TracBrowser for help on using the repository browser.