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.
trcnxt.F90 in branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/TOP_SRC/TRP – NEMO

source: branches/UKMO/dev_r5518_GO6_package/NEMOGCM/NEMO/TOP_SRC/TRP/trcnxt.F90 @ 10149

Last change on this file since 10149 was 9163, checked in by frrh, 6 years ago

Add code from Julien Palmieri's Met Office GMED ticket 338.
This incorporates code from branches/NERC/dev_r5518_GO6_package_trdtrc
revisions 8454:9020 inclusive.

File size: 9.6 KB
Line 
1MODULE trcnxt
2   !!======================================================================
3   !!                       ***  MODULE  trcnxt  ***
4   !! Ocean passive tracers:  time stepping on passives tracers
5   !!======================================================================
6   !! History :  7.0  !  1991-11  (G. Madec)  Original code
7   !!                 !  1993-03  (M. Guyon)  symetrical conditions
8   !!                 !  1995-02  (M. Levy)   passive tracers
9   !!                 !  1996-02  (G. Madec & M. Imbard)  opa release 8.0
10   !!            8.0  !  1996-04  (A. Weaver)  Euler forward step
11   !!            8.2  !  1999-02  (G. Madec, N. Grima)  semi-implicit pressure grad.
12   !!  NEMO      1.0  !  2002-08  (G. Madec)  F90: Free form and module
13   !!                 !  2002-08  (G. Madec)  F90: Free form and module
14   !!                 !  2002-11  (C. Talandier, A-M Treguier) Open boundaries
15   !!                 !  2004-03  (C. Ethe) passive tracers
16   !!                 !  2007-02  (C. Deltel) Diagnose ML trends for passive tracers
17   !!            2.0  !  2006-02  (L. Debreu, C. Mazauric) Agrif implementation
18   !!            3.0  !  2008-06  (G. Madec)  time stepping always done in trazdf
19   !!            3.1  !  2009-02  (G. Madec, R. Benshila)  re-introduce the vvl option
20   !!            3.3  !  2010-06  (C. Ethe, G. Madec) Merge TRA-TRC
21   !!----------------------------------------------------------------------
22#if defined key_top
23   !!----------------------------------------------------------------------
24   !!   'key_top'                                                TOP models
25   !!----------------------------------------------------------------------
26   !!   trc_nxt     : time stepping on passive tracers
27   !!----------------------------------------------------------------------
28   USE oce_trc         ! ocean dynamics and tracers variables
29   USE domvvl          ! variable volume 
30   USE trc             ! ocean passive tracers variables
31   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
32   USE prtctl_trc      ! Print control for debbuging
33   USE trcnam_trp      ! passive tracers transport namelist variables
34   USE trd_oce
35   USE trdtra
36   USE tranxt
37# if defined key_agrif
38   USE agrif_top_interp
39# endif
40
41   IMPLICIT NONE
42   PRIVATE
43
44   PUBLIC   trc_nxt          ! routine called by step.F90
45   PUBLIC   trc_nxt_alloc    ! routine called by nemogcm.F90
46
47   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:) ::   r2dt
48
49   !! * Substitutions
50#  include "domzgr_substitute.h90"
51   !!----------------------------------------------------------------------
52   !! NEMO/TOP 3.3 , NEMO Consortium (2010)
53   !! $Id$
54   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt)
55   !!----------------------------------------------------------------------
56CONTAINS
57
58   INTEGER FUNCTION trc_nxt_alloc()
59      !!----------------------------------------------------------------------
60      !!                   ***  ROUTINE trc_nxt_alloc  ***
61      !!----------------------------------------------------------------------
62      ALLOCATE( r2dt(jpk), STAT=trc_nxt_alloc )
63      !
64      IF( trc_nxt_alloc /= 0 )   CALL ctl_warn('trc_nxt_alloc : failed to allocate array')
65      !
66   END FUNCTION trc_nxt_alloc
67
68
69   SUBROUTINE trc_nxt( kt )
70      !!----------------------------------------------------------------------
71      !!                   ***  ROUTINE trcnxt  ***
72      !!
73      !! ** Purpose :   Compute the passive tracers fields at the
74      !!      next time-step from their temporal trends and swap the fields.
75      !!
76      !! ** Method  :   Apply lateral boundary conditions on (ua,va) through
77      !!      call to lbc_lnk routine
78      !!   default:
79      !!      arrays swap
80      !!         (trn) = (tra) ; (tra) = (0,0)
81      !!         (trb) = (trn)
82      !!
83      !!   For Arakawa or TVD Scheme :
84      !!      A Asselin time filter applied on now tracers (trn) to avoid
85      !!      the divergence of two consecutive time-steps and tr arrays
86      !!      to prepare the next time_step:
87      !!         (trb) = (trn) + atfp [ (trb) + (tra) - 2 (trn) ]
88      !!         (trn) = (tra) ; (tra) = (0,0)
89      !!
90      !!
91      !! ** Action  : - update trb, trn
92      !!----------------------------------------------------------------------
93      INTEGER, INTENT( in ) ::   kt     ! ocean time-step index
94      !
95      INTEGER  ::   jk, jn   ! dummy loop indices
96      REAL(wp) ::   zfact            ! temporary scalar
97      CHARACTER (len=22) :: charout
98      REAL(wp), POINTER, DIMENSION(:,:,:,:) ::  ztrdt 
99      !!----------------------------------------------------------------------
100      !
101      IF( nn_timing == 1 )  CALL timing_start('trc_nxt')
102      !
103      IF( kt == nittrc000 .AND. lwp ) THEN
104         WRITE(numout,*)
105         WRITE(numout,*) 'trc_nxt : time stepping on passive tracers'
106      ENDIF
107
108#if defined key_agrif
109      CALL Agrif_trc                   ! AGRIF zoom boundaries
110#endif
111      ! Update after tracer on domain lateral boundaries
112      DO jn = 1, jptra
113         CALL lbc_lnk( tra(:,:,:,jn), 'T', 1. )   
114      END DO
115
116
117#if defined key_bdy
118!!      CALL bdy_trc( kt )               ! BDY open boundaries
119#endif
120
121
122      ! set time step size (Euler/Leapfrog)
123      IF( neuler == 0 .AND. kt ==  nittrc000 ) THEN  ;  r2dt(:) =     rdttrc(:)   ! at nittrc000             (Euler)
124      ELSEIF( kt <= nittrc000 + nn_dttrc )     THEN  ;  r2dt(:) = 2.* rdttrc(:)   ! at nit000 or nit000+1 (Leapfrog)
125      ENDIF
126
127      ! trends computation initialisation
128      IF( l_trdtrc )  THEN
129         CALL wrk_alloc( jpi, jpj, jpk, jptra, ztrdt )  !* store now fields before applying the Asselin filter
130         ztrdt(:,:,jpk,:) = 0._wp
131         IF( ln_trcldf_iso ) THEN                       ! diagnose the "pure" Kz diffusive trend
132            DO jn = 1, jptra
133               CALL trd_tra( kt, 'TRC', jn, jptra_zdfp, ztrdt(:,:,:,jn) )
134            ENDDO
135         ENDIF
136         ! total trend for the non-time-filtered variables.
137         ! G Nurser 23 Mar 2017. Recalculate trend as Delta(e3t*T)/e3tn; e3tn
138         ! cancel from tsn terms
139         IF( lk_vvl ) THEN
140            DO jn = 1, jptra
141               DO jk = 1, jpkm1
142                  zfact = 1.0 / rdttrc(jk)
143                  ztrdt(:,:,jk,jn) = ( tra(:,:,jk,jn)*fse3t_a(:,:,jk) / fse3t_n(:,:,jk) - &
144                                       trn(:,:,jk,jn) ) * zfact
145               END DO
146            END DO
147         ELSE
148            DO jn = 1, jptra
149               DO jk = 1, jpkm1
150                  zfact = 1.0 / rdttrc(jk)
151                  ztrdt(:,:,jk,jn) = ( tra(:,:,jk,jn) - trn(:,:,jk,jn) ) * zfact
152               END DO
153            END DO
154         END IF
155         DO jn = 1, jptra
156            CALL trd_tra( kt, 'TRC', jn, jptra_tot, ztrdt(:,:,:,jn) )
157         ENDDO
158         IF( .NOT.lk_vvl )  THEN
159            ! Store now fields before applying the Asselin filter
160            ! in order to calculate Asselin filter trend later.
161            ztrdt(:,:,:,:)  = trn(:,:,:,:)
162         ENDIF
163      ENDIF
164      ! Leap-Frog + Asselin filter time stepping
165      IF( neuler == 0 .AND. kt == nittrc000 ) THEN        ! Euler time-stepping at first time-step
166         !                                                ! (only swap)
167         DO jn = 1, jptra
168            DO jk = 1, jpkm1
169               trn(:,:,jk,jn) = tra(:,:,jk,jn)
170            END DO
171         END DO
172         IF (l_trdtrc.AND.lk_vvl) THEN      ! Zero Asselin filter contribution
173                                            ! must be explicitly written out since for vvl
174                                            ! Asselin filter is output by
175                                            ! tra_nxt_vvl that is not called on
176                                            ! this time step
177            ztrdt(:,:,:,:) = 0._wp
178            DO jn = 1, jptra
179               CALL trd_tra( kt, 'TRC', jn, jptra_atf, ztrdt(:,:,:,jn) )
180            ENDDO
181         END IF
182
183         !                                             
184      ELSE
185         ! Leap-Frog + Asselin filter time stepping
186         IF( lk_vvl ) THEN   ;   CALL tra_nxt_vvl( kt, nittrc000, rdttrc, 'TRC', trb, trn, tra,      &
187           &                                                                sbc_trc, sbc_trc_b, jptra )      ! variable volume level (vvl)
188         ELSE                ;   CALL tra_nxt_fix( kt, nittrc000,         'TRC', trb, trn, tra, jptra )      ! fixed    volume level
189         ENDIF
190      ENDIF
191
192      ! trends computation
193      IF( l_trdtrc.AND..NOT.lk_vvl) THEN                                      ! trends
194         DO jn = 1, jptra
195            DO jk = 1, jpkm1
196               zfact = 1.e0 / r2dt(jk) 
197               ztrdt(:,:,jk,jn) = ( trb(:,:,jk,jn) - ztrdt(:,:,jk,jn) ) * zfact 
198            END DO
199            CALL trd_tra( kt, 'TRC', jn, jptra_atf, ztrdt(:,:,:,jn) )
200         END DO
201      END IF
202      !
203      IF( l_trdtrc)  CALL wrk_dealloc( jpi, jpj, jpk, jptra, ztrdt ) 
204      !
205      IF(ln_ctl)   THEN  ! print mean trends (used for debugging)
206         WRITE(charout, FMT="('nxt')")
207         CALL prt_ctl_trc_info(charout)
208         CALL prt_ctl_trc(tab4d=trn, mask=tmask, clinfo=ctrcnm)
209      ENDIF
210      !
211      IF( nn_timing == 1 )  CALL timing_stop('trc_nxt')
212      !
213   END SUBROUTINE trc_nxt
214
215#else
216   !!----------------------------------------------------------------------
217   !!   Default option                                         Empty module
218   !!----------------------------------------------------------------------
219CONTAINS
220   SUBROUTINE trc_nxt( kt ) 
221      INTEGER, INTENT(in) :: kt
222      WRITE(*,*) 'trc_nxt: You should not have seen this print! error?', kt
223   END SUBROUTINE trc_nxt
224#endif
225   !!======================================================================
226END MODULE trcnxt
Note: See TracBrowser for help on using the repository browser.