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

source: branches/2017/dev_merge_2017/NEMOGCM/NEMO/NST_SRC/agrif_top_update.F90 @ 9019

Last change on this file since 9019 was 9019, checked in by timgraham, 6 years ago

Merge of dev_CNRS_2017 into branch

  • Property svn:keywords set to Id
File size: 4.7 KB
Line 
1#define TWO_WAY
2#undef DECAL_FEEDBACK
3
4MODULE agrif_top_update
5   !!======================================================================
6   !!                ***  MODULE agrif_top_update  ***
7   !! AGRIF :   update package for passive tracers (TOP)
8   !!======================================================================
9   !! History : 
10   !!----------------------------------------------------------------------
11#if defined key_agrif && defined key_top
12   !!----------------------------------------------------------------------
13   !!   'key_agrif'                                              AGRIF zoom
14   !!   'key_TOP'                                           on-line tracers
15   !!----------------------------------------------------------------------
16   USE par_oce
17   USE oce
18   USE dom_oce
19   USE agrif_oce
20   USE par_trc
21   USE trc
22
23   IMPLICIT NONE
24   PRIVATE
25
26   PUBLIC Agrif_Update_Trc
27
28   INTEGER, PUBLIC ::   nbcline_trc = 0   !: ???
29
30   !!----------------------------------------------------------------------
31   !! NEMO/NST 4.0 , NEMO Consortium (2017)
32   !! $Id$
33   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
34   !!----------------------------------------------------------------------
35CONTAINS
36
37   SUBROUTINE Agrif_Update_Trc( kt )
38      !!----------------------------------------------------------------------
39      !!                   *** ROUTINE Agrif_Update_Trc ***
40      !!----------------------------------------------------------------------
41      INTEGER, INTENT(in) ::   kt
42      !!----------------------------------------------------------------------
43      !
44      IF((Agrif_NbStepint() .NE. (Agrif_irhot()-1)).AND.(kt /= 0)) RETURN
45#if defined TWO_WAY   
46      Agrif_UseSpecialValueInUpdate = .TRUE.
47      Agrif_SpecialValueFineGrid    = 0._wp
48      !
49      IF( MOD(nbcline_trc,nbclineupdate) == 0 ) THEN
50# if ! defined DECAL_FEEDBACK
51         CALL Agrif_Update_Variable(trn_id, procname=updateTRC )
52# else
53         CALL Agrif_Update_Variable(trn_id, locupdate=(/1,0/),procname=updateTRC )
54# endif
55      ELSE
56# if ! defined DECAL_FEEDBACK
57         CALL Agrif_Update_Variable( trn_id, locupdate=(/0,2/), procname=updateTRC )
58# else
59         CALL Agrif_Update_Variable( trn_id, locupdate=(/1,2/), procname=updateTRC )
60# endif
61      ENDIF
62      !
63      Agrif_UseSpecialValueInUpdate = .FALSE.
64      nbcline_trc = nbcline_trc + 1
65#endif
66      !
67   END SUBROUTINE Agrif_Update_Trc
68
69
70   SUBROUTINE updateTRC( ptab, i1, i2, j1, j2, k1, k2, n1, n2, before )
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
77      !!
78      INTEGER ::   ji, jj, jk, jn
79      !!----------------------------------------------------------------------
80      !
81      IF( before ) THEN
82         ptab(i1:i2,j1:j2,k1:k2,n1:n2) = trn(i1:i2,j1:j2,k1:k2,n1:n2)
83      ELSE
84         IF( .NOT.(lk_agrif_fstep.AND.(neuler==0)) ) THEN
85            ! Add asselin part
86            DO jn = n1,n2
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)
94                        ENDIF
95                     END DO
96                  END DO
97               END DO
98            END DO
99         ENDIF
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
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      !
113   END SUBROUTINE updateTRC
114
115#else
116   !!----------------------------------------------------------------------
117   !!   Empty module                                           no TOP AGRIF
118   !!----------------------------------------------------------------------
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
123#endif
124
125   !!======================================================================
126END MODULE agrif_top_update
Note: See TracBrowser for help on using the repository browser.