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.
agrif_top_update.F90 in branches/UKMO/2015_V36_STABLE_CO6_CO5_zenv_pomsdwl/NEMOGCM/NEMO/NST_SRC – NEMO

source: branches/UKMO/2015_V36_STABLE_CO6_CO5_zenv_pomsdwl/NEMOGCM/NEMO/NST_SRC/agrif_top_update.F90 @ 5650

Last change on this file since 5650 was 5650, checked in by deazer, 9 years ago

Removal of svn keywords.

File size: 3.6 KB
RevLine 
[628]1#define TWO_WAY
2
[636]3MODULE agrif_top_update
4
[1206]5#if defined key_agrif && defined key_top
[636]6   USE par_oce
7   USE oce
8   USE dom_oce
[782]9   USE agrif_oce
[1271]10   USE trc
[3294]11   USE wrk_nemo 
[628]12
[636]13   IMPLICIT NONE
14   PRIVATE
[628]15
[636]16   PUBLIC Agrif_Update_Trc
[628]17
[1300]18   INTEGER, PUBLIC :: nbcline_trc = 0
[628]19
[1156]20   !!----------------------------------------------------------------------
[2528]21   !! NEMO/NST 3.3 , NEMO Consortium (2010)
[1156]22   !! $Id$
[2528]23   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[1156]24   !!----------------------------------------------------------------------
25
[636]26   CONTAINS
27
28   SUBROUTINE Agrif_Update_Trc( kt )
29      !!---------------------------------------------
30      !!   *** ROUTINE Agrif_Update_Trc ***
31      !!---------------------------------------------
[2715]32      !!
[636]33      INTEGER, INTENT(in) :: kt
[2715]34      REAL(wp), POINTER, DIMENSION(:,:,:,:) :: ztra
35
[636]36 
37      IF ((Agrif_NbStepint() .NE. (Agrif_irhot()-1)).AND.(kt /= 0)) RETURN
38
39#if defined TWO_WAY
[3680]40      CALL wrk_alloc( jpi, jpj, jpk, jptra, ztra )
[2715]41
[628]42      Agrif_UseSpecialValueInUpdate = .TRUE.
43      Agrif_SpecialValueFineGrid = 0.
[636]44 
[1300]45     IF (MOD(nbcline_trc,nbclineupdate) == 0) THEN
[2715]46         CALL Agrif_Update_Variable(ztra,trn_id, procname=updateTRC)
[628]47      ELSE
[2715]48         CALL Agrif_Update_Variable(ztra,trn_id,locupdate=(/0,2/), procname=updateTRC)
[628]49      ENDIF
50
51      Agrif_UseSpecialValueInUpdate = .FALSE.
[1300]52      nbcline_trc = nbcline_trc + 1
[2715]53
[3680]54      CALL wrk_dealloc( jpi, jpj, jpk, jptra, ztra )
[628]55#endif
56
[636]57   END SUBROUTINE Agrif_Update_Trc
[628]58
[3680]59   SUBROUTINE updateTRC(tabres,i1,i2,j1,j2,k1,k2,n1,n2,before)
[636]60      !!---------------------------------------------
61      !!   *** ROUTINE UpdateTrc ***
62      !!---------------------------------------------
[3680]63      INTEGER, INTENT(in) :: i1,i2,j1,j2,k1,k2,n1,n2
64      REAL, DIMENSION(i1:i2,j1:j2,k1:k2,n1:n2), INTENT(inout) :: tabres
[636]65      LOGICAL, INTENT(in) :: before
66   
[3680]67      INTEGER :: ji,jj,jk,jn
[628]68
[3680]69         IF( before ) THEN
70            DO jn = n1, n2
71               DO jk = k1, k2
72                  DO jj = j1, j2
73                     DO ji = i1, i2
74                        tabres(ji,jj,jk,jn) = trn(ji,jj,jk,jn)
[1300]75                     ENDDO
[636]76                  ENDDO
77               ENDDO
[628]78            ENDDO
[636]79         ELSE
[4491]80            IF (.NOT.(lk_agrif_fstep.AND.(neuler==0))) THEN
81            ! Add asselin part
82               DO jn = n1, n2
83                  DO jk = k1, k2
84                     DO jj = j1, j2
85                        DO ji = i1, i2
86                           IF( tabres(ji,jj,jk,jn) .NE. 0. ) THEN
87                              trb(ji,jj,jk,jn) = trb(ji,jj,jk,jn) & 
88                                 & + atfp * ( tabres(ji,jj,jk,jn) &
89                                               - trn(ji,jj,jk,jn) ) * tmask(ji,jj,jk)
90                           ENDIF
91                        ENDDO
92                     ENDDO
93                  ENDDO
94               ENDDO
95            ENDIF
96
[3680]97            DO jn = n1, n2
98               DO jk = k1, k2
99                  DO jj = j1, j2
100                     DO ji = i1, i2
101                        IF( tabres(ji,jj,jk,jn) .NE. 0. ) THEN
102                           trn(ji,jj,jk,jn) = tabres(ji,jj,jk,jn) * tmask(ji,jj,jk)
[1300]103                        ENDIF
104                     ENDDO
[636]105                  ENDDO
106               ENDDO
107            ENDDO
108         ENDIF
[628]109
[636]110   END SUBROUTINE updateTRC
[628]111
112#else
[636]113CONTAINS
114   SUBROUTINE agrif_top_update_empty
115      !!---------------------------------------------
116      !!   *** ROUTINE agrif_Top_update_empty ***
117      !!---------------------------------------------
118      WRITE(*,*)  'agrif_top_update : You should not have seen this print! error?'
119   END SUBROUTINE agrif_top_update_empty
[628]120#endif
[636]121END Module agrif_top_update
Note: See TracBrowser for help on using the repository browser.