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 trunk/NEMOGCM/NEMO/NST_SRC – NEMO

source: trunk/NEMOGCM/NEMO/NST_SRC/agrif_top_update.F90 @ 2528

Last change on this file since 2528 was 2528, checked in by rblod, 13 years ago

Update NEMOGCM from branch nemo_v3_3_beta

  • Property svn:keywords set to Id
File size: 2.8 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
[628]11
[636]12   IMPLICIT NONE
13   PRIVATE
[628]14
[636]15   PUBLIC Agrif_Update_Trc
[628]16
[1300]17   INTEGER, PUBLIC :: nbcline_trc = 0
[628]18
[1156]19   !!----------------------------------------------------------------------
[2528]20   !! NEMO/NST 3.3 , NEMO Consortium (2010)
[1156]21   !! $Id$
[2528]22   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
[1156]23   !!----------------------------------------------------------------------
24
[636]25   CONTAINS
26
27   SUBROUTINE Agrif_Update_Trc( kt )
28      !!---------------------------------------------
29      !!   *** ROUTINE Agrif_Update_Trc ***
30      !!---------------------------------------------
31      INTEGER, INTENT(in) :: kt
32 
33      REAL(wp), DIMENSION(jpi,jpj,jpk,jptra) :: ztra
34
35      IF ((Agrif_NbStepint() .NE. (Agrif_irhot()-1)).AND.(kt /= 0)) RETURN
36
37#if defined TWO_WAY
[628]38      Agrif_UseSpecialValueInUpdate = .TRUE.
39      Agrif_SpecialValueFineGrid = 0.
[636]40 
[1300]41     IF (MOD(nbcline_trc,nbclineupdate) == 0) THEN
[636]42         CALL Agrif_Update_Variable(ztra,trn, procname=updateTRC)
[628]43      ELSE
[636]44         CALL Agrif_Update_Variable(ztra,trn,locupdate=(/0,2/), procname=updateTRC)
[628]45      ENDIF
46
47      Agrif_UseSpecialValueInUpdate = .FALSE.
[1300]48      nbcline_trc = nbcline_trc + 1
[628]49#endif
50
[636]51   END SUBROUTINE Agrif_Update_Trc
[628]52
[1300]53   SUBROUTINE updateTRC(tabres,i1,i2,j1,j2,k1,k2,l1,l2,before)
[636]54      !!---------------------------------------------
55      !!   *** ROUTINE UpdateTrc ***
56      !!---------------------------------------------
[628]57#  include "domzgr_substitute.h90"
58
[1300]59      INTEGER, INTENT(in) :: i1,i2,j1,j2,k1,k2,l1,l2
60      REAL, DIMENSION(i1:i2,j1:j2,k1:k2,l1:l2), INTENT(inout) :: tabres
[636]61      LOGICAL, INTENT(in) :: before
62   
[1300]63      INTEGER :: ji,jj,jk,jl
[628]64
[636]65         IF (before) THEN
[1300]66            DO jl=l1,l2
67               DO jk=k1,k2
68                  DO jj=j1,j2
69                     DO ji=i1,i2
70                        tabres(ji,jj,jk,jl) = trn(ji,jj,jk,jl)
71                     ENDDO
[636]72                  ENDDO
73               ENDDO
[628]74            ENDDO
[636]75         ELSE
[1300]76            DO jl=l1,l2
77               DO jk=k1,k2
78                  DO jj=j1,j2
79                     DO ji=i1,i2
80                        IF (tabres(ji,jj,jk,jl).NE.0.) THEN
81                           trn(ji,jj,jk,jl) = tabres(ji,jj,jk,jl) * tmask(ji,jj,jk)
82                        ENDIF
83                     ENDDO
[636]84                  ENDDO
85               ENDDO
86            ENDDO
87         ENDIF
[628]88
[636]89   END SUBROUTINE updateTRC
[628]90
91#else
[636]92CONTAINS
93   SUBROUTINE agrif_top_update_empty
94      !!---------------------------------------------
95      !!   *** ROUTINE agrif_Top_update_empty ***
96      !!---------------------------------------------
97      WRITE(*,*)  'agrif_top_update : You should not have seen this print! error?'
98   END SUBROUTINE agrif_top_update_empty
[628]99#endif
[636]100END Module agrif_top_update
Note: See TracBrowser for help on using the repository browser.