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 trunk/NEMO/TOP_SRC/TRP – NEMO

source: trunk/NEMO/TOP_SRC/TRP/trcnxt.F90 @ 202

Last change on this file since 202 was 202, checked in by opalod, 19 years ago

CT : UPDATE142 : Check the consistency between passive tracers transport modules (in TRP directory) and those used for the active tracers

  • Property svn:eol-style set to native
  • Property svn:executable set to *
  • Property svn:keywords set to Author Date Id Revision
File size: 6.5 KB
Line 
1MODULE trcnxt
2   !!======================================================================
3   !!                       ***  MODULE  trcnxt  ***
4   !! Ocean passive tracers:  time stepping on passives tracers
5   !!======================================================================
6#if defined key_passivetrc   
7   !!----------------------------------------------------------------------
8   !!   trc_nxt     : time stepping on passive tracers
9   !!----------------------------------------------------------------------
10   !! * Modules used
11   USE oce_trc         ! ocean dynamics and tracers variables
12   USE trc             ! ocean passive tracers variables
13   USE lbclnk          ! ocean lateral boundary conditions (or mpp link)
14   USE trctrp_lec      ! pasive tracers transport
15
16   IMPLICIT NONE
17   PRIVATE
18
19   !! * Routine accessibility
20   PUBLIC trc_nxt          ! routine called by step.F90
21   !!----------------------------------------------------------------------
22   !!   OPA 9.0 , LODYC-IPSL   (2003)
23   !!----------------------------------------------------------------------
24
25CONTAINS
26
27   SUBROUTINE trc_nxt( kt )
28      !!----------------------------------------------------------------------
29      !!                   ***  ROUTINE trcnxt  ***
30      !!
31      !! ** Purpose :   Compute the passive tracers fields at the
32      !!      next time-step from their temporal trends and swap the fields.
33      !!
34      !! ** Method  :   Apply lateral boundary conditions on (ua,va) through
35      !!      call to lbc_lnk routine
36      !!   default:
37      !!      arrays swap
38      !!         (trn) = (tra) ; (tra) = (0,0)
39      !!         (trb) = (trn)
40      !!
41      !!   For Arakawa or TVD Scheme :
42      !!      A Asselin time filter applied on now tracers (trn) to avoid
43      !!      the divergence of two consecutive time-steps and tr arrays
44      !!      to prepare the next time_step:
45      !!         (trb) = (trn) + atfp [ (trb) + (tra) - 2 (trn) ]
46      !!         (trn) = (tra) ; (tra) = (0,0)
47      !!
48      !!
49      !! ** Action  : - update trb, trn
50      !!
51      !! History :
52      !!   7.0  !  91-11  (G. Madec)  Original code
53      !!        !  93-03  (M. Guyon)  symetrical conditions
54      !!        !  95-02  (M. Levy)   passive tracers
55      !!        !  96-02  (G. Madec & M. Imbard)  opa release 8.0
56      !!   8.0  !  96-04  (A. Weaver)  Euler forward step
57      !!   8.2  !  99-02  (G. Madec, N. Grima)  semi-implicit pressure grad.
58      !!   8.5  !  02-08  (G. Madec)  F90: Free form and module
59      !!        !  02-11  (C. Talandier, A-M Treguier) Open boundaries
60      !!   9.0  !  04-03  (C. Ethe) passive tracers
61      !!----------------------------------------------------------------------
62      !! * Arguments
63      INTEGER, INTENT( in ) ::   kt         ! ocean time-step index
64      !! * Local declarations
65      INTEGER ::   ji, jj, jk,jn   ! dummy loop indices
66      REAL(wp) ::   zfact, ztra    ! temporary scalar
67      !!----------------------------------------------------------------------
68
69      IF( kt == nittrc000 ) THEN
70         WRITE(numout,*)
71         WRITE(numout,*) 'trc_nxt : time stepping on passive tracers'
72      ENDIF
73
74
75      DO jn = 1, jptra
76
77         ! 0. Lateral boundary conditions on tra (T-point, unchanged sign)
78         ! ---------------------------------============
79         CALL lbc_lnk( tra(:,:,:,jn), 'T', 1. )   
80         
81         !                                                ! ===============
82         DO jk = 1, jpk                                   ! Horizontal slab
83            !                                             ! ===============
84            ! 1. Leap-frog scheme (only in explicit case, otherwise the
85            ! -------------------  time stepping is already done in trczdf)
86            IF( l_trczdf_exp .AND. ( ln_trcadv_cen2 .OR. ln_trcadv_tvd) ) THEN
87               zfact = 2. * rdttra(jk) * FLOAT(ndttrc) 
88               IF( neuler == 0 .AND. kt == nittrc000 ) zfact = rdttra(jk) * FLOAT(ndttrc) 
89               tra(:,:,jk,jn) = ( trb(:,:,jk,jn) + zfact * tra(:,:,jk,jn) ) * tmask(:,:,jk)
90            ENDIF
91
92         END DO
93
94#if defined key_obc
95        IF(lwp) WRITE(numout,cform_err)
96        IF(lwp) WRITE(numout,*) '          Passive tracers and Open Boundary condition can not be used together '
97        IF(lwp) WRITE(numout,*) '          Check in trc_nxt routine'
98        nstop = nstop + 1
99#endif
100
101         DO jk = 1, jpk 
102
103            ! 2. Time filter and swap of arrays
104            ! ---------------------------------
105            IF ( ln_trcadv_cen2 .OR. ln_trcadv_tvd  ) THEN
106
107               IF( neuler == 0 .AND. kt == nittrc000 ) THEN
108                  DO jj = 1, jpj
109                     DO ji = 1, jpi
110                        trb(ji,jj,jk,jn) = trn(ji,jj,jk,jn)
111                        trn(ji,jj,jk,jn) = tra(ji,jj,jk,jn)
112                        tra(ji,jj,jk,jn) = 0.
113                     END DO
114                  END DO
115               ELSE
116                  DO jj = 1, jpj
117                     DO ji = 1, jpi
118                        trb(ji,jj,jk,jn) = atfp  * ( trb(ji,jj,jk,jn) + tra(ji,jj,jk,jn) ) + atfp1 * trn(ji,jj,jk,jn)
119                        trn(ji,jj,jk,jn) = tra(ji,jj,jk,jn)
120                        tra(ji,jj,jk,jn) = 0.
121                     END DO
122                  END DO
123               ENDIF
124
125            ELSE
126!  case of smolar scheme or muscl
127               DO jj = 1, jpj
128                  DO ji = 1, jpi
129                     trb(ji,jj,jk,jn) = tra(ji,jj,jk,jn)
130                     trn(ji,jj,jk,jn) = tra(ji,jj,jk,jn)
131                     tra(ji,jj,jk,jn) = 0.
132                  END DO
133               END DO
134
135            ENDIF
136            !                                             ! ===============
137         END DO                                           !   End of slab
138         !                                                ! ===============
139         IF(l_ctl) THEN         ! print mean field (used for debugging)
140            ztra = SUM( trn(2:nictl,2:njctl,1:jpkm1,jn)*tmask(2:nictl,2:njctl,1:jpkm1) ) 
141            WRITE(numout,*) ' trc/nxt  - ',ctrcnm(jn),' : ', ztra
142         ENDIF
143
144      END DO
145
146   END SUBROUTINE trc_nxt
147
148#else
149   !!----------------------------------------------------------------------
150   !!   Default option                                         Empty module
151   !!----------------------------------------------------------------------
152CONTAINS
153   SUBROUTINE trc_nxt( kt ) 
154      INTEGER, INTENT(in) :: kt
155      WRITE(*,*) 'trc_nxt: You should not have seen this print! error?', kt
156   END SUBROUTINE trc_nxt
157#endif
158   !!======================================================================
159END MODULE trcnxt
Note: See TracBrowser for help on using the repository browser.