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

source: branches/2017/dev_r7881_ENHANCE09_RK3/NEMOGCM/NEMO/NST_SRC/agrif_top_update.F90 @ 8866

Last change on this file since 8866 was 8586, checked in by gm, 7 years ago

#1911 (ENHANCE-09): PART I.3 - phasing with branch dev_r8183_ICEMODEL revision 8575

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