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

source: branches/2017/dev_METO_MERCATOR_2017/NEMOGCM/NEMO/NST_SRC/agrif_top_update.F90 @ 8993

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

Merged Mercator branch in

  • Property svn:keywords set to Id
File size: 4.8 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   !!----------------------------------------------------------------------
27   !! NEMO/NST 3.7 , NEMO Consortium (2015)
28   !! $Id$
29   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt)
30   !!----------------------------------------------------------------------
31CONTAINS
32
33   SUBROUTINE Agrif_Update_Trc( )
34      !!----------------------------------------------------------------------
35      !!                   *** ROUTINE Agrif_Update_Trc ***
36      !!----------------------------------------------------------------------
37      !
38      IF (Agrif_Root()) RETURN 
39      !
40#if defined TWO_WAY   
41      Agrif_UseSpecialValueInUpdate = .TRUE.
42      Agrif_SpecialValueFineGrid    = 0._wp
43      !
44# if ! defined DECAL_FEEDBACK
45      CALL Agrif_Update_Variable(trn_id, procname=updateTRC )
46!      CALL Agrif_Update_Variable( trn_id, locupdate=(/0,2/), procname=updateTRC )
47# else
48      CALL Agrif_Update_Variable(trn_id, locupdate=(/1,0/),procname=updateTRC )
49!      CALL Agrif_Update_Variable( trn_id, locupdate=(/1,2/), procname=updateTRC )
50# endif
51      !
52      Agrif_UseSpecialValueInUpdate = .FALSE.
53      !
54#endif
55      !
56   END SUBROUTINE Agrif_Update_Trc
57
58
59   SUBROUTINE updateTRC( tabres, i1, i2, j1, j2, k1, k2, n1, n2, before )
60      !!----------------------------------------------------------------------
61      !!                      *** ROUTINE updateTRC ***
62      !!----------------------------------------------------------------------
63      INTEGER                                    , INTENT(in   ) ::   i1, i2, j1, j2, k1, k2, n1, n2
64      REAL(wp),DIMENSION(i1:i2,j1:j2,k1:k2,n1:n2), INTENT(inout) ::   tabres
65      LOGICAL                                    , INTENT(in   ) ::   before
66      !!
67      INTEGER :: ji,jj,jk,jn
68      REAL(wp) :: ztb, ztnu, ztno
69      !!----------------------------------------------------------------------
70      !
71      !
72      IF (before) THEN
73         DO jn = n1,n2
74            DO jk=k1,k2
75               DO jj=j1,j2
76                  DO ji=i1,i2
77!> jc tmp
78                     tabres(ji,jj,jk,jn) = trn(ji,jj,jk,jn)  * e3t_n(ji,jj,jk) / e3t_0(ji,jj,jk)
79!                     tabres(ji,jj,jk,jn) = trn(ji,jj,jk,jn)  * e3t_n(ji,jj,jk)
80!< jc tmp
81                  END DO
82               END DO
83            END DO
84         END DO
85      ELSE
86!> jc tmp
87         DO jn = n1,n2
88            tabres(i1:i2,j1:j2,k1:k2,jn) =  tabres(i1:i2,j1:j2,k1:k2,jn) * e3t_0(i1:i2,j1:j2,k1:k2) &
89                                         & * tmask(i1:i2,j1:j2,k1:k2)
90         ENDDO
91!< jc tmp
92         IF (.NOT.(lk_agrif_fstep.AND.(neuler==0))) THEN
93            ! Add asselin part
94            DO jn = n1,n2
95               DO jk=k1,k2
96                  DO jj=j1,j2
97                     DO ji=i1,i2
98                        IF( tabres(ji,jj,jk,jn) .NE. 0. ) THEN
99                           ztb  = trb(ji,jj,jk,jn) * e3t_b(ji,jj,jk) ! fse3t_b prior update should be used
100                           ztnu = tabres(ji,jj,jk,jn)
101                           ztno = trn(ji,jj,jk,jn) * e3t_a(ji,jj,jk)
102                           trb(ji,jj,jk,jn) = ( ztb + atfp * ( ztnu - ztno) )  & 
103                                     &        * tmask(ji,jj,jk) / e3t_b(ji,jj,jk)
104                        ENDIF
105                     ENDDO
106                  ENDDO
107               ENDDO
108            ENDDO
109         ENDIF
110         DO jn = n1,n2
111            DO jk=k1,k2
112               DO jj=j1,j2
113                  DO ji=i1,i2
114                     IF( tabres(ji,jj,jk,jn) .NE. 0. ) THEN
115                        trn(ji,jj,jk,jn) = tabres(ji,jj,jk,jn) / e3t_n(ji,jj,jk)
116                     END IF
117                  END DO
118               END DO
119            END DO
120         END DO
121         !
122         IF  ((neuler==0).AND.(Agrif_Nb_Step()==0) ) THEN
123            trb(i1:i2,j1:j2,k1:k2,n1:n2)  = trn(i1:i2,j1:j2,k1:k2,n1:n2)
124         ENDIF
125         !
126      ENDIF
127      !
128   END SUBROUTINE updateTRC
129
130#else
131CONTAINS
132   SUBROUTINE agrif_top_update_empty
133      !!---------------------------------------------
134      !!   *** ROUTINE agrif_Top_update_empty ***
135      !!---------------------------------------------
136      WRITE(*,*)  'agrif_top_update : You should not have seen this print! error?'
137   END SUBROUTINE agrif_top_update_empty
138#endif
139
140   !!======================================================================
141END MODULE agrif_top_update
Note: See TracBrowser for help on using the repository browser.