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

source: branches/2017/dev_r7881_no_wrk_alloc/NEMOGCM/NEMO/NST_SRC/agrif_top_update.F90 @ 8016

Last change on this file since 8016 was 8016, checked in by timgraham, 7 years ago

Delete some remaining "USE wrk_array" lines

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