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

source: branches/2011/dev_NEMO_MERGE_2011/NEMOGCM/NEMO/NST_SRC/agrif_top_update.F90 @ 8486

Last change on this file since 8486 was 3186, checked in by smasson, 13 years ago

dev_NEMO_MERGE_2011: replace the old wrk_nemo with the new wrk_nemo

  • Property svn:keywords set to Id
File size: 3.0 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
[3186]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
[3184]40      CALL wrk_alloc( jpi, jpj, jpk, jpts, 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
[3184]54      CALL wrk_dealloc( jpi, jpj, jpk, jpts, ztra )
[628]55#endif
56
[636]57   END SUBROUTINE Agrif_Update_Trc
[628]58
[1300]59   SUBROUTINE updateTRC(tabres,i1,i2,j1,j2,k1,k2,l1,l2,before)
[636]60      !!---------------------------------------------
61      !!   *** ROUTINE UpdateTrc ***
62      !!---------------------------------------------
[628]63#  include "domzgr_substitute.h90"
64
[1300]65      INTEGER, INTENT(in) :: i1,i2,j1,j2,k1,k2,l1,l2
66      REAL, DIMENSION(i1:i2,j1:j2,k1:k2,l1:l2), INTENT(inout) :: tabres
[636]67      LOGICAL, INTENT(in) :: before
68   
[1300]69      INTEGER :: ji,jj,jk,jl
[628]70
[636]71         IF (before) THEN
[1300]72            DO jl=l1,l2
73               DO jk=k1,k2
74                  DO jj=j1,j2
75                     DO ji=i1,i2
76                        tabres(ji,jj,jk,jl) = trn(ji,jj,jk,jl)
77                     ENDDO
[636]78                  ENDDO
79               ENDDO
[628]80            ENDDO
[636]81         ELSE
[1300]82            DO jl=l1,l2
83               DO jk=k1,k2
84                  DO jj=j1,j2
85                     DO ji=i1,i2
86                        IF (tabres(ji,jj,jk,jl).NE.0.) THEN
87                           trn(ji,jj,jk,jl) = tabres(ji,jj,jk,jl) * tmask(ji,jj,jk)
88                        ENDIF
89                     ENDDO
[636]90                  ENDDO
91               ENDDO
92            ENDDO
93         ENDIF
[628]94
[636]95   END SUBROUTINE updateTRC
[628]96
97#else
[636]98CONTAINS
99   SUBROUTINE agrif_top_update_empty
100      !!---------------------------------------------
101      !!   *** ROUTINE agrif_Top_update_empty ***
102      !!---------------------------------------------
103      WRITE(*,*)  'agrif_top_update : You should not have seen this print! error?'
104   END SUBROUTINE agrif_top_update_empty
[628]105#endif
[636]106END Module agrif_top_update
Note: See TracBrowser for help on using the repository browser.