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_all_update.F90 in NEMO/trunk/src/NST – NEMO

source: NEMO/trunk/src/NST/agrif_all_update.F90

Last change on this file was 15119, checked in by jchanut, 3 years ago

#2638, changes to accomodate nn_hls=2 and AGRIF zooms crossing cyclic boundaries. E-W case ok, update for North-Fold still needed.

  • Property svn:keywords set to Id
File size: 6.1 KB
Line 
1MODULE agrif_all_update
2   !!======================================================================
3   !!                   ***  MODULE  agrif_all_update  ***
4   !! AGRIF: Main update driver for ocean, ice and passive tracers
5   !!======================================================================
6   !! History :  4.0  !  2018-06  (J. Chanut)  Original code
7   !!----------------------------------------------------------------------
8#if defined key_agrif 
9   !!----------------------------------------------------------------------
10   !!   'key_agrif'                                              AGRIF zoom
11   !!----------------------------------------------------------------------
12   USE dom_oce
13   USE agrif_oce
14   USE agrif_oce_update
15#if defined key_top
16   USE agrif_top_update
17#endif
18#if defined key_si3
19   USE agrif_ice_update
20#endif
21
22   IMPLICIT NONE
23   PRIVATE
24
25   PUBLIC   Agrif_Update_All
26
27   !!----------------------------------------------------------------------
28   !! NEMO/NST 4.0 , NEMO Consortium (2018)
29   !! $Id$
30   !! Software governed by the CeCILL license (see ./LICENSE)
31   !!----------------------------------------------------------------------
32CONTAINS
33
34   SUBROUTINE Agrif_Update_All( )
35      !!----------------------------------------------------------------------
36      !!                 *** ROUTINE Agrif_Update_All ***
37      !!
38      !! ** Purpose :: Update nested grids for all components (Ocean, Sea Ice, TOP)
39      !!               Order of update matters here !
40      !!----------------------------------------------------------------------
41      IF (( .NOT.ln_agrif_2way ).OR.(Agrif_Root())) RETURN
42      !
43      IF (lwp.AND.lk_agrif_debug) Write(*,*) ' --> START AGRIF UPDATE from grid Number',Agrif_Fixed()
44      !
45      CALL Agrif_Update_ssh()                      ! Update sea level
46      !
47      IF (.NOT.ln_linssh) CALL Agrif_Update_vvl()  ! Update scale factors
48      !
49      CALL Agrif_Update_tra()                      ! Update temperature/salinity
50      !
51#if defined key_top
52      CALL Agrif_Update_Trc()                      ! Update passive tracers
53#endif
54      !
55      CALL Agrif_Update_dyn()                      ! Update dynamics
56      !
57! JC remove update because this precludes from perfect restartability
58!!      CALL Agrif_Update_tke()                  ! Update tke
59
60#if defined key_si3
61      CALL agrif_update_ice()                      ! Update sea ice
62#endif
63      !
64      Agrif_UseSpecialValueInUpdate = .FALSE.
65      !
66      ! If zooms are crossing or are coincident with cyclic boundaries
67      ! need to update ghost points on parent edges:
68      IF ( (Agrif_Parent(l_Iperio).OR.Agrif_Parent(l_NFold)).AND. &
69         & (( Agrif_Ix() <= 1  ).OR.( Agrif_Iy() + nbcellsy/AGRIF_Irhoy() >=  Agrif_Parent(Nj0glo) - 1 ))) THEN
70         CALL Agrif_ChildGrid_To_ParentGrid()
71         CALL finalize_lbc_for_agrif 
72         CALL Agrif_ParentGrid_To_ChildGrid()
73      ENDIF
74
75      IF (lwp.AND.lk_agrif_debug) Write(*,*) ' <-- END AGRIF UPDATE from grid Number',Agrif_Fixed()
76
77   END SUBROUTINE agrif_Update_All
78
79   SUBROUTINE finalize_lbc_for_agrif
80      !!---------------------------------------------
81      !!  *** ROUTINE finalize lbc_for-agrif ***
82      !!---------------------------------------------
83      USE lbclnk 
84#if defined key_qco
85      USE domqco
86#endif
87      !
88      CALL lbc_lnk( 'finalize_lbc_for_agrif', uu(:,:,:,       Kmm_a), 'U', -1._wp,  &
89           &                                  vv(:,:,:,       Kmm_a), 'V', -1._wp,  &
90           &                                  uu(:,:,:,       Kbb_a), 'U', -1._wp,  &
91           &                                  vv(:,:,:,       Kbb_a), 'V', -1._wp,  &
92           &                                  ts(:,:,:,jp_tem,Kmm_a), 'T',  1._wp,  & 
93           &                                  ts(:,:,:,jp_sal,Kmm_a), 'T',  1._wp,  & 
94           &                                  ts(:,:,:,jp_tem,Kbb_a), 'T',  1._wp,  & 
95           &                                  ts(:,:,:,jp_sal,Kbb_a), 'T', 1._wp    )
96      CALL lbc_lnk( 'finalize_lbc_for_agrif', ssh(:,:,  Kmm_a), 'T', 1._wp, &
97           &                                  ssh(:,:,  Kbb_a), 'T', 1._wp, &
98           &                                  uu_b(:,:, Kmm_a), 'U',-1._wp, &
99           &                                  uu_b(:,:, Kbb_a), 'U',-1._wp, &
100           &                                  vv_b(:,:, Kmm_a), 'V',-1._wp, &
101           &                                  vv_b(:,:, Kbb_a), 'V',-1._wp, &
102           &                                  ub2_b(:,:),   'U',-1._wp,     &
103           &                                  ub2_i_b(:,:), 'U',-1._wp,     &
104           &                                  vb2_b(:,:),   'V',-1._wp,     &
105           &                                  vb2_i_b(:,:), 'V',-1._wp      ) 
106
107#if defined key_qco
108      CALL dom_qco_zgr( Kbb_a, Kmm_a ) 
109#endif
110#if defined key_si3
111      CALL lbc_lnk( 'finalize_lbc_for_agrif',  a_i, 'T',1._wp,  v_i,'T',1._wp,                 &
112           &                                   v_s, 'T',1._wp, sv_i,'T',1._wp, oa_i,'T',1._wp, &
113           &                                   a_ip,'T',1._wp, v_ip,'T',1._wp, v_il,'T',1._wp )
114      CALL lbc_lnk( 'finalize_lbc_for_agrif', t_su,'T',1._wp )
115      CALL lbc_lnk( 'finalize_lbc_for_agrif',  e_s,'T',1._wp )
116      CALL lbc_lnk( 'finalize_lbc_for_agrif',  e_i,'T',1._wp )
117      CALL lbc_lnk( 'finalize_lbc_for_agrif', u_ice, 'U', -1._wp, v_ice, 'V', -1._wp )
118#endif
119#if defined key_top
120      CALL lbc_lnk( 'finalize_lbc_for_agrif', tr(:,:,:,:,Kmm_a), 'T',1._wp )
121      CALL lbc_lnk( 'finalize_lbc_for_agrif', tr(:,:,:,:,Kbb_a), 'T',1._wp )
122#endif
123      !
124   END SUBROUTINE finalize_lbc_for_agrif 
125
126#else
127   !!----------------------------------------------------------------------
128   !!   Empty module                                          no AGRIF zoom
129   !!----------------------------------------------------------------------
130CONTAINS
131   SUBROUTINE Agrif_Update_all( )
132      WRITE(*,*)  'Agrif_Update_All : You should not have seen this print! error?'
133   END SUBROUTINE Agrif_Update_all
134#endif
135
136   !!======================================================================
137END MODULE agrif_all_update
138
Note: See TracBrowser for help on using the repository browser.