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

source: branches/2017/dev_r8624_AGRIF3_VVL/NEMOGCM/NEMO/NST_SRC/agrif_top_update.F90 @ 8762

Last change on this file since 8762 was 8762, checked in by jchanut, 6 years ago

AGRIF + vvl: Final changes, update SETTE tests (these are ok except SAS) - #1965

  • Property svn:keywords set to Id
File size: 5.0 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   USE wrk_nemo 
20
21   IMPLICIT NONE
22   PRIVATE
23
24   PUBLIC Agrif_Update_Trc
25
26   INTEGER, PUBLIC ::   nbcline_trc = 0   !: ???
27
28   !!----------------------------------------------------------------------
29   !! NEMO/NST 3.7 , NEMO Consortium (2015)
30   !! $Id$
31   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
32   !!----------------------------------------------------------------------
33CONTAINS
34
35   SUBROUTINE Agrif_Update_Trc( )
36      !!----------------------------------------------------------------------
37      !!                   *** ROUTINE Agrif_Update_Trc ***
38      !!----------------------------------------------------------------------
39      !
40      IF (Agrif_Root()) RETURN 
41      !
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( tabres, i1, i2, j1, j2, k1, k2, n1, n2, before )
68      !!----------------------------------------------------------------------
69      !!                      *** ROUTINE updateTRC ***
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) ::   tabres
73      LOGICAL                                    , INTENT(in   ) ::   before
74      !!
75      INTEGER :: ji,jj,jk,jn
76      REAL(wp) :: ztb, ztnu, ztno
77      !!----------------------------------------------------------------------
78      !
79      !
80      IF (before) THEN
81         DO jn = n1,n2
82            DO jk=k1,k2
83               DO jj=j1,j2
84                  DO ji=i1,i2
85!> jc tmp
86                     tabres(ji,jj,jk,jn) = trn(ji,jj,jk,jn)  * e3t_n(ji,jj,jk) / e3t_0(ji,jj,jk)
87!                     tabres(ji,jj,jk,jn) = trn(ji,jj,jk,jn)  * e3t_n(ji,jj,jk)
88!< jc tmp
89                  END DO
90               END DO
91            END DO
92         END DO
93      ELSE
94!> jc tmp
95         DO jn = n1,n2
96            tabres(i1:i2,j1:j2,k1:k2,jn) =  tabres(i1:i2,j1:j2,k1:k2,jn) * e3t_0(i1:i2,j1:j2,k1:k2) &
97                                         & * tmask(i1:i2,j1:j2,k1:k2)
98         ENDDO
99!< jc tmp
100         IF (.NOT.(lk_agrif_fstep.AND.(neuler==0))) THEN
101            ! Add asselin part
102            DO jn = n1,n2
103               DO jk=k1,k2
104                  DO jj=j1,j2
105                     DO ji=i1,i2
106                        IF( tabres(ji,jj,jk,jn) .NE. 0. ) THEN
107                           ztb  = trb(ji,jj,jk,jn) * e3t_b(ji,jj,jk) ! fse3t_b prior update should be used
108                           ztnu = tabres(ji,jj,jk,jn)
109                           ztno = trn(ji,jj,jk,jn) * e3t_a(ji,jj,jk)
110                           trb(ji,jj,jk,jn) = ( ztb + atfp * ( ztnu - ztno) )  & 
111                                     &        * tmask(ji,jj,jk) / e3t_b(ji,jj,jk)
112                        ENDIF
113                     ENDDO
114                  ENDDO
115               ENDDO
116            ENDDO
117         ENDIF
118         DO jn = n1,n2
119            DO jk=k1,k2
120               DO jj=j1,j2
121                  DO ji=i1,i2
122                     IF( tabres(ji,jj,jk,jn) .NE. 0. ) THEN
123                        trn(ji,jj,jk,jn) = tabres(ji,jj,jk,jn) / e3t_n(ji,jj,jk)
124                     END IF
125                  END DO
126               END DO
127            END DO
128         END DO
129         !
130         IF  ((neuler==0).AND.(Agrif_Nb_Step()==0) ) THEN
131            trb(i1:i2,j1:j2,k1:k2,n1:n2)  = trn(i1:i2,j1:j2,k1:k2,n1:n2)
132         ENDIF
133         !
134      ENDIF
135      !
136   END SUBROUTINE updateTRC
137
138#else
139CONTAINS
140   SUBROUTINE agrif_top_update_empty
141      !!---------------------------------------------
142      !!   *** ROUTINE agrif_Top_update_empty ***
143      !!---------------------------------------------
144      WRITE(*,*)  'agrif_top_update : You should not have seen this print! error?'
145   END SUBROUTINE agrif_top_update_empty
146#endif
147
148   !!======================================================================
149END MODULE agrif_top_update
Note: See TracBrowser for help on using the repository browser.